aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2021-03-15 10:37:35 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2021-03-15 10:37:35 -0700
commit24191a2a278c0dec30bacd66b78cbb8cc8d91324 (patch)
tree0cba7f763387ae545729ab574a858ce44e9fad30 /src/Text/Pandoc/Writers
parent39934c885144e6e7b443556ac9c9814ab8eaafd2 (diff)
downloadpandoc-24191a2a278c0dec30bacd66b78cbb8cc8d91324.tar.gz
Use foldl' instead of foldl everywhere.
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs8
-rw-r--r--src/Text/Pandoc/Writers/RST.hs4
-rw-r--r--src/Text/Pandoc/Writers/Texinfo.hs4
3 files changed, 8 insertions, 8 deletions
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 2f33cd467..332de1545 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -30,7 +30,7 @@ module Text.Pandoc.Writers.HTML (
) where
import Control.Monad.State.Strict
import Data.Char (ord)
-import Data.List (intercalate, intersperse, partition, delete, (\\))
+import Data.List (intercalate, intersperse, partition, delete, (\\), foldl')
import Data.List.NonEmpty (NonEmpty((:|)))
import Data.Maybe (fromMaybe, isJust, isNothing)
import qualified Data.Set as Set
@@ -544,7 +544,7 @@ tagWithAttributes opts html5 selfClosing tagname attr =
addAttrs :: PandocMonad m
=> WriterOptions -> Attr -> Html -> StateT WriterState m Html
-addAttrs opts attr h = foldl (!) h <$> attrsToHtml opts attr
+addAttrs opts attr h = foldl' (!) h <$> attrsToHtml opts attr
toAttrs :: PandocMonad m
=> [(Text, Text)] -> StateT WriterState m [Attribute]
@@ -926,7 +926,7 @@ blockToHtml opts (OrderedList (startnum, numstyle, _) lst) = do
numstyle']
else [])
l <- ordList opts contents
- return $ foldl (!) l attribs
+ return $ foldl' (!) l attribs
blockToHtml opts (DefinitionList lst) = do
contents <- mapM (\(term, defs) ->
do term' <- liftM H.dt $ inlineListToHtml opts term
@@ -1407,7 +1407,7 @@ inlineToHtml opts inline = do
Just "audio" -> mediaTag H5.audio "Audio"
Just _ -> (H5.embed, [])
_ -> imageTag
- return $ foldl (!) tag $ attributes ++ specAttrs
+ return $ foldl' (!) tag $ attributes ++ specAttrs
-- note: null title included, as in Markdown.pl
(Note contents) -> do
notes <- gets stNotes
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index d01e13db4..54d042332 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -16,7 +16,7 @@ reStructuredText: <http://docutils.sourceforge.net/rst.html>
module Text.Pandoc.Writers.RST ( writeRST, flatten ) where
import Control.Monad.State.Strict
import Data.Char (isSpace)
-import Data.List (transpose, intersperse)
+import Data.List (transpose, intersperse, foldl')
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import Data.Text (Text)
@@ -509,7 +509,7 @@ flatten outer
| null contents = [outer]
| otherwise = combineAll contents
where contents = dropInlineParent outer
- combineAll = foldl combine []
+ combineAll = foldl' combine []
combine :: [Inline] -> Inline -> [Inline]
combine f i =
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index 53da70f84..9d695563f 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -15,7 +15,7 @@ module Text.Pandoc.Writers.Texinfo ( writeTexinfo ) where
import Control.Monad.Except (throwError)
import Control.Monad.State.Strict
import Data.Char (chr, ord)
-import Data.List (maximumBy, transpose)
+import Data.List (maximumBy, transpose, foldl')
import Data.Ord (comparing)
import qualified Data.Set as Set
import Data.Text (Text)
@@ -271,7 +271,7 @@ tableAnyRowToTexinfo :: PandocMonad m
-> [[Block]]
-> TI m (Doc Text)
tableAnyRowToTexinfo itemtype aligns cols =
- (literal itemtype $$) . foldl (\row item -> row $$
+ (literal itemtype $$) . foldl' (\row item -> row $$
(if isEmpty row then empty else text " @tab ") <> item) empty <$> zipWithM alignedBlock aligns cols
alignedBlock :: PandocMonad m