aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Pretty.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Pretty.hs')
-rw-r--r--src/Text/Pandoc/Pretty.hs36
1 files changed, 16 insertions, 20 deletions
diff --git a/src/Text/Pandoc/Pretty.hs b/src/Text/Pandoc/Pretty.hs
index b5600ad39..40a7d018c 100644
--- a/src/Text/Pandoc/Pretty.hs
+++ b/src/Text/Pandoc/Pretty.hs
@@ -78,6 +78,7 @@ module Text.Pandoc.Pretty (
where
import Control.Monad.State.Strict
+import Control.Monad (when)
import Data.Char (isSpace)
import Data.Foldable (toList)
import Data.List (intersperse)
@@ -144,11 +145,10 @@ hcat = mconcat
-- between them.
infixr 6 <+>
(<+>) :: Doc -> Doc -> Doc
-(<+>) x y = if isEmpty x
- then y
- else if isEmpty y
- then x
- else x <> space <> y
+(<+>) x y
+ | isEmpty x = y
+ | isEmpty y = x
+ | otherwise = x <> space <> y
-- | Same as 'cat', but putting breakable spaces between the
-- 'Doc's.
@@ -158,20 +158,18 @@ hsep = foldr (<+>) empty
infixr 5 $$
-- | @a $$ b@ puts @a@ above @b@.
($$) :: Doc -> Doc -> Doc
-($$) x y = if isEmpty x
- then y
- else if isEmpty y
- then x
- else x <> cr <> y
+($$) x y
+ | isEmpty x = y
+ | isEmpty y = x
+ | otherwise = x <> cr <> y
infixr 5 $+$
-- | @a $+$ b@ puts @a@ above @b@, with a blank line between.
($+$) :: Doc -> Doc -> Doc
-($+$) x y = if isEmpty x
- then y
- else if isEmpty y
- then x
- else x <> blankline <> y
+($+$) x y
+ | isEmpty x = y
+ | isEmpty y = x
+ | otherwise = x <> blankline <> y
-- | List version of '$$'.
vcat :: [Doc] -> Doc
@@ -217,9 +215,9 @@ outp off s | off < 0 = do -- offset < 0 means newline characters
outp off s = do -- offset >= 0 (0 might be combining char)
st' <- get
let pref = prefix st'
- when (column st' == 0 && usePrefix st' && not (null pref)) $ do
+ when (column st' == 0 && usePrefix st' && not (null pref)) $
modify $ \st -> st{ output = fromString pref : output st
- , column = column st + realLength pref }
+ , column = column st + realLength pref }
modify $ \st -> st{ output = fromString s : output st
, column = column st + off
, newlines = 0 }
@@ -328,9 +326,7 @@ renderList (BreakingSpace : xs) = do
renderList (AfterBreak s : xs) = do
st <- get
- if newlines st > 0
- then outp (realLength s) s
- else return ()
+ when (newlines st > 0) $ outp (realLength s) s
renderList xs
renderList (Block i1 s1 : Block i2 s2 : xs) =