aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/CommonMark.hs2
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs6
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs10
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs2
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs26
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs3
-rw-r--r--src/Text/Pandoc/Writers/Haddock.hs2
-rw-r--r--src/Text/Pandoc/Writers/JATS.hs10
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs12
-rw-r--r--src/Text/Pandoc/Writers/Man.hs4
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs101
-rw-r--r--src/Text/Pandoc/Writers/Ms.hs6
-rw-r--r--src/Text/Pandoc/Writers/ODT.hs2
-rw-r--r--src/Text/Pandoc/Writers/OPML.hs2
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs2
-rw-r--r--src/Text/Pandoc/Writers/Powerpoint/Output.hs29
-rw-r--r--src/Text/Pandoc/Writers/Powerpoint/Presentation.hs8
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs6
-rw-r--r--src/Text/Pandoc/Writers/TEI.hs6
-rw-r--r--src/Text/Pandoc/Writers/XWiki.hs2
20 files changed, 115 insertions, 126 deletions
diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs
index e991cd384..66ded218f 100644
--- a/src/Text/Pandoc/Writers/CommonMark.hs
+++ b/src/Text/Pandoc/Writers/CommonMark.hs
@@ -1,5 +1,3 @@
-{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Writers.CommonMark
Copyright : Copyright (C) 2015-2020 John MacFarlane
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 7bae37a79..0a6313513 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -209,7 +209,7 @@ blockToConTeXt (Div (ident,_,kvs) bs) = do
<> literal lng <> "]" $$ txt $$ "\\stop"
Nothing -> txt
wrapBlank txt = blankline <> txt <> blankline
- (wrapBlank . wrapLang . wrapDir . wrapRef) <$> blockListToConTeXt bs
+ wrapBlank . wrapLang . wrapDir . wrapRef <$> blockListToConTeXt bs
blockToConTeXt (BulletList lst) = do
contents <- mapM listItemToConTeXt lst
return $ ("\\startitemize" <> if isTightList lst
@@ -332,7 +332,7 @@ alignToConTeXt align = case align of
AlignDefault -> empty
listItemToConTeXt :: PandocMonad m => [Block] -> WM m (Doc Text)
-listItemToConTeXt list = (("\\item" $$) . nest 2) <$> blockListToConTeXt list
+listItemToConTeXt list = ("\\item" $$) . nest 2 <$> blockListToConTeXt list
defListItemToConTeXt :: PandocMonad m => ([Inline], [[Block]]) -> WM m (Doc Text)
defListItemToConTeXt (term, defs) = do
@@ -487,7 +487,7 @@ inlineToConTeXt (Span (_,_,kvs) ils) = do
Just lng -> braces ("\\language" <>
brackets (literal lng) <> txt)
Nothing -> txt
- (wrapLang . wrapDir) <$> inlineListToConTeXt ils
+ wrapLang . wrapDir <$> inlineListToConTeXt ils
-- | Craft the section header, inserting the section reference, if supplied.
sectionHeader :: PandocMonad m
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index d3517159f..408d8cc0c 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -179,7 +179,7 @@ blockToDocbook opts (Div (id',"section":_,_) (Header lvl _ ils : xs)) = do
blockToDocbook opts (Div (ident,_,_) [Para lst]) =
let attribs = [("id", ident) | not (T.null ident)] in
if hasLineBreaks lst
- then (flush . nowrap . inTags False "literallayout" attribs)
+ then flush . nowrap . inTags False "literallayout" attribs
<$> inlinesToDocbook opts lst
else inTags True "para" attribs <$> inlinesToDocbook opts lst
blockToDocbook opts (Div (ident,_,_) bs) = do
@@ -206,7 +206,7 @@ blockToDocbook opts (Para [Image attr txt (src,T.stripPrefix "fig:" -> Just _)])
(imageToDocbook opts attr src) $$
inTagsSimple "textobject" (inTagsSimple "phrase" alt))
blockToDocbook opts (Para lst)
- | hasLineBreaks lst = (flush . nowrap . inTagsSimple "literallayout")
+ | hasLineBreaks lst = flush . nowrap . inTagsSimple "literallayout"
<$> inlinesToDocbook opts lst
| otherwise = inTagsIndented "para" <$> inlinesToDocbook opts lst
blockToDocbook opts (LineBlock lns) =
@@ -277,7 +277,7 @@ blockToDocbook opts (Table _ blkCapt specs thead tbody tfoot) = do
head' <- if all null headers
then return empty
else inTagsIndented "thead" <$> tableRowToDocbook opts headers
- body' <- (inTagsIndented "tbody" . vcat) <$>
+ body' <- inTagsIndented "tbody" . vcat <$>
mapM (tableRowToDocbook opts) rows
return $ inTagsIndented tableType $ captionDoc $$
inTags True "tgroup" [("cols", tshow (length aligns))] (
@@ -305,14 +305,14 @@ tableRowToDocbook :: PandocMonad m
-> [[Block]]
-> DB m (Doc Text)
tableRowToDocbook opts cols =
- (inTagsIndented "row" . vcat) <$> mapM (tableItemToDocbook opts) cols
+ inTagsIndented "row" . vcat <$> mapM (tableItemToDocbook opts) cols
tableItemToDocbook :: PandocMonad m
=> WriterOptions
-> [Block]
-> DB m (Doc Text)
tableItemToDocbook opts item =
- (inTags True "entry" [] . vcat) <$> mapM (blockToDocbook opts) item
+ inTags True "entry" [] . vcat <$> mapM (blockToDocbook opts) item
-- | Convert a list of inline elements to Docbook.
inlinesToDocbook :: PandocMonad m => WriterOptions -> [Inline] -> DB m (Doc Text)
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 81dbb6ce0..fa7e2ceea 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -1030,7 +1030,7 @@ blockToOpenXML' opts (Table _ blkCapt specs thead tbody tfoot) = do
let rowwidth = fullrow * sum widths
let mkgridcol w = mknode "w:gridCol"
[("w:w", show (floor (textwidth * w) :: Integer))] ()
- let hasHeader = any (not . null) headers
+ let hasHeader = not $ all null headers
modify $ \s -> s { stInTable = False }
return $
caption' ++
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 63034a577..12004889f 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -62,7 +62,7 @@ import Text.DocTemplates (FromContext(lookupContext), Context(..),
ToContext(toVal), Val(..))
-- A Chapter includes a list of blocks.
-data Chapter = Chapter [Block]
+newtype Chapter = Chapter [Block]
deriving (Show)
data EPUBState = EPUBState {
@@ -711,10 +711,10 @@ pandocToEPUB version opts doc = do
| writerTableOfContents opts ] ++
map chapterRefNode chapterEntries)
, unode "guide" $
- [ unode "reference" !
- [("type","toc"),("title", tocTitle),
- ("href","nav.xhtml")] $ ()
- ] ++
+ (unode "reference" !
+ [("type","toc"),("title", tocTitle),
+ ("href","nav.xhtml")] $ ()
+ ) :
[ unode "reference" !
[("type","cover")
,("title","Cover")
@@ -838,14 +838,12 @@ pandocToEPUB version opts doc = do
] | writerTableOfContents opts
]
else []
- let landmarks = if null landmarkItems
- then []
- else [RawBlock (Format "html") $ TS.pack $ ppElement $
- unode "nav" ! [("epub:type","landmarks")
- ,("id","landmarks")
- ,("hidden","hidden")] $
- [ unode "ol" landmarkItems ]
- ]
+ let landmarks = [RawBlock (Format "html") $ TS.pack $ ppElement $
+ unode "nav" ! [("epub:type","landmarks")
+ ,("id","landmarks")
+ ,("hidden","hidden")] $
+ [ unode "ol" landmarkItems ]
+ | not (null landmarkItems)]
navData <- lift $ writeHtml opts'{ writerVariables =
Context (M.fromList [("navpage", toVal' "true")])
<> cssvars False <> vars }
@@ -940,7 +938,7 @@ metadataElement version md currentTime =
| version == EPUB2 = [dcNode "identifier" !
(("id",id') : maybe [] (\x -> [("opf:scheme", x)]) scheme) $
txt]
- | otherwise = [dcNode "identifier" ! [("id",id')] $ txt] ++
+ | otherwise = (dcNode "identifier" ! [("id",id')] $ txt) :
maybe [] ((\x -> [unode "meta" !
[ ("refines",'#':id')
, ("property","identifier-type")
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 6bb708c37..decc487c1 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
@@ -1025,7 +1024,7 @@ rowListToHtml :: PandocMonad m
-> [TableRow]
-> StateT WriterState m Html
rowListToHtml opts rows =
- (\x -> (nl opts *> mconcat x)) <$>
+ (\x -> nl opts *> mconcat x) <$>
mapM (tableRowToHtml opts) rows
colSpecListToHtml :: PandocMonad m
diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs
index 9d8c5ec41..aaa19ed07 100644
--- a/src/Text/Pandoc/Writers/Haddock.hs
+++ b/src/Text/Pandoc/Writers/Haddock.hs
@@ -28,7 +28,7 @@ import Text.Pandoc.Templates (renderTemplate)
import Text.Pandoc.Writers.Shared
type Notes = [[Block]]
-data WriterState = WriterState { stNotes :: Notes }
+newtype WriterState = WriterState { stNotes :: Notes }
instance Default WriterState
where def = WriterState{ stNotes = [] }
diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs
index 50ce04e03..4dc02d686 100644
--- a/src/Text/Pandoc/Writers/JATS.hs
+++ b/src/Text/Pandoc/Writers/JATS.hs
@@ -216,7 +216,7 @@ imageMimeType src kvs =
(T.takeWhile (/='/') <$> mbMT)
subtype = fromMaybe "" $
lookup "mime-subtype" kvs `mplus`
- ((T.drop 1 . T.dropWhile (/='/')) <$> mbMT)
+ (T.drop 1 . T.dropWhile (/='/') <$> mbMT)
in (maintype, subtype)
languageFor :: [Text] -> Text
@@ -372,7 +372,7 @@ blockToJATS opts (Table _ blkCapt specs th tb tf) =
thead <- if all null headers
then return empty
else inTagsIndented "thead" <$> tableRowToJATS opts True headers
- tbody <- (inTagsIndented "tbody" . vcat) <$>
+ tbody <- inTagsIndented "tbody" . vcat <$>
mapM (tableRowToJATS opts False) rows
return $ inTags True "table" [] $ coltags $$ thead $$ tbody
@@ -389,7 +389,7 @@ tableRowToJATS :: PandocMonad m
-> [[Block]]
-> JATS m (Doc Text)
tableRowToJATS opts isHeader cols =
- (inTagsIndented "tr" . vcat) <$> mapM (tableItemToJATS opts isHeader) cols
+ inTagsIndented "tr" . vcat <$> mapM (tableItemToJATS opts isHeader) cols
tableItemToJATS :: PandocMonad m
=> WriterOptions
@@ -400,7 +400,7 @@ tableItemToJATS opts isHeader [Plain item] =
inTags False (if isHeader then "th" else "td") [] <$>
inlinesToJATS opts item
tableItemToJATS opts isHeader item =
- (inTags False (if isHeader then "th" else "td") [] . vcat) <$>
+ inTags False (if isHeader then "th" else "td") [] . vcat <$>
mapM (blockToJATS opts) item
-- | Convert a list of inline elements to JATS.
@@ -547,7 +547,7 @@ inlineToJATS _ (Image (ident,_,kvs) _ (src, tit)) = do
(T.takeWhile (/='/') <$> mbMT)
let subtype = fromMaybe "" $
lookup "mime-subtype" kvs `mplus`
- ((T.drop 1 . T.dropWhile (/='/')) <$> mbMT)
+ (T.drop 1 . T.dropWhile (/='/') <$> mbMT)
let attr = [("id", ident) | not (T.null ident)] ++
[("mimetype", maintype),
("mime-subtype", subtype),
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 3753604db..071a288e1 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -1049,7 +1049,7 @@ wrapDiv (_,classes,kvs) t = do
let valign = maybe "T" mapAlignment (lookup "align" kvs)
totalwidth = maybe [] (\x -> ["totalwidth=" <> x])
(lookup "totalwidth" kvs)
- onlytextwidth = filter ((==) "onlytextwidth") classes
+ onlytextwidth = filter ("onlytextwidth" ==) classes
options = text $ T.unpack $ T.intercalate "," $
valign : totalwidth ++ onlytextwidth
in inCmd "begin" "columns" <> brackets options
@@ -1458,8 +1458,8 @@ citeArgumentsList (CiteGroup _ _ []) = return empty
citeArgumentsList (CiteGroup pfxs sfxs ids) = do
pdoc <- inlineListToLaTeX pfxs
sdoc <- inlineListToLaTeX sfxs'
- return $ (optargs pdoc sdoc) <>
- (braces (literal (T.intercalate "," (reverse ids))))
+ return $ optargs pdoc sdoc <>
+ braces (literal (T.intercalate "," (reverse ids)))
where sfxs' = stripLocatorBraces $ case sfxs of
(Str t : r) -> case T.uncons t of
Just (x, xs)
@@ -1516,12 +1516,12 @@ citationsToBiblatex (c:cs)
groups <- mapM citeArgumentsList (reverse (foldl' grouper [] (c:cs)))
- return $ text cmd <> (mconcat groups)
+ return $ text cmd <> mconcat groups
where grouper prev cit = case prev of
((CiteGroup oPfx oSfx ids):rest)
- | null oSfx && null pfx -> (CiteGroup oPfx sfx (cid:ids)):rest
- _ -> (CiteGroup pfx sfx [cid]):prev
+ | null oSfx && null pfx -> CiteGroup oPfx sfx (cid:ids) : rest
+ _ -> CiteGroup pfx sfx [cid] : prev
where pfx = citationPrefix cit
sfx = citationSuffix cit
cid = citationId cit
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index 62449431c..4eb0db042 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
{- |
@@ -232,8 +233,7 @@ definitionListItemToMan opts (label, defs) = do
labelText <- inlineListToMan opts $ makeCodeBold label
contents <- if null defs
then return empty
- else liftM vcat $ forM defs $ \blocks ->
- case blocks of
+ else liftM vcat $ forM defs $ \case
(x:xs) -> do
first' <- blockToMan opts $
case x of
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 3e50704ca..323d159b0 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -24,10 +24,9 @@ import Control.Monad.Reader
import Control.Monad.State.Strict
import Data.Char (isAlphaNum)
import Data.Default
-import Data.List (find, intersperse, sortBy, transpose)
+import Data.List (find, intersperse, sortOn, transpose)
import qualified Data.Map as M
import Data.Maybe (fromMaybe, mapMaybe)
-import Data.Ord (comparing)
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
@@ -127,7 +126,7 @@ pandocTitleBlock tit auths dat =
mmdTitleBlock :: Context Text -> Doc Text
mmdTitleBlock (Context hashmap) =
- vcat $ map go $ sortBy (comparing fst) $ M.toList hashmap
+ vcat $ map go $ sortOn fst $ M.toList hashmap
where go (k,v) =
case (text (T.unpack k), v) of
(k', ListVal xs)
@@ -148,15 +147,15 @@ mmdTitleBlock (Context hashmap) =
plainTitleBlock :: Doc Text -> [Doc Text] -> Doc Text -> Doc Text
plainTitleBlock tit auths dat =
tit <> cr <>
- (hcat (intersperse (text "; ") auths)) <> cr <>
+ hcat (intersperse (text "; ") auths) <> cr <>
dat <> cr
yamlMetadataBlock :: Context Text -> Doc Text
-yamlMetadataBlock v = "---" $$ (contextToYaml v) $$ "---"
+yamlMetadataBlock v = "---" $$ contextToYaml v $$ "---"
contextToYaml :: Context Text -> Doc Text
contextToYaml (Context o) =
- vcat $ map keyvalToYaml $ sortBy (comparing fst) $ M.toList o
+ vcat $ map keyvalToYaml $ sortOn fst $ M.toList o
where
keyvalToYaml (k,v) =
case (text (T.unpack k), v) of
@@ -250,7 +249,7 @@ pandocToMarkdown opts (Pandoc meta blocks) = do
-- | Return markdown representation of reference key table.
refsToMarkdown :: PandocMonad m => WriterOptions -> Refs -> MD m (Doc Text)
-refsToMarkdown opts refs = mapM (keyToMarkdown opts) refs >>= return . vcat
+refsToMarkdown opts refs = vcat <$> mapM (keyToMarkdown opts) refs
-- | Return markdown representation of a reference key.
keyToMarkdown :: PandocMonad m
@@ -446,7 +445,7 @@ blockToMarkdown' opts (Plain inlines) = do
then inlines
else case inlines of
(Str t:ys)
- | (null ys || startsWithSpace ys)
+ | null ys || startsWithSpace ys
, beginsWithOrderedListMarker t
-> RawInline (Format "markdown") (escapeMarker t):ys
(Str t:_)
@@ -462,7 +461,7 @@ blockToMarkdown' opts (Para [Image attr alt (src,tgt@(T.stripPrefix "fig:" -> Ju
| isEnabled Ext_raw_html opts &&
not (isEnabled Ext_link_attributes opts) &&
attr /= nullAttr = -- use raw HTML
- ((<> blankline) . literal . T.strip) <$>
+ (<> blankline) . literal . T.strip <$>
writeHtml5String opts{ writerTemplate = Nothing }
(Pandoc nullMeta [Para [Image attr alt (src,tgt)]])
| otherwise = blockToMarkdown opts (Para [Image attr alt (src,tit)])
@@ -472,7 +471,7 @@ blockToMarkdown' opts (LineBlock lns) =
if isEnabled Ext_line_blocks opts
then do
mdLines <- mapM (inlineListToMarkdown opts) lns
- return $ (vcat $ map (hang 2 (literal "| ")) mdLines) <> blankline
+ return $ vcat (map (hang 2 (literal "| ")) mdLines) <> blankline
else blockToMarkdown opts $ linesToPara lns
blockToMarkdown' opts b@(RawBlock f str) = do
variant <- asks envVariant
@@ -582,28 +581,28 @@ blockToMarkdown' opts (CodeBlock attribs str) = do
attrs = if isEnabled Ext_fenced_code_attributes opts
then nowrap $ " " <> attrsToMarkdown attribs
else case attribs of
- (_,(cls:_),_) -> " " <> literal cls
+ (_,cls:_,_) -> " " <> literal cls
_ -> empty
blockToMarkdown' opts (BlockQuote blocks) = do
variant <- asks envVariant
-- if we're writing literate haskell, put a space before the bird tracks
-- so they won't be interpreted as lhs...
- let leader = if isEnabled Ext_literate_haskell opts
- then " > "
- else if variant == PlainText then " " else "> "
+ let leader
+ | isEnabled Ext_literate_haskell opts = " > "
+ | variant == PlainText = " "
+ | otherwise = "> "
contents <- blockListToMarkdown opts blocks
- return $ (prefixed leader contents) <> blankline
+ return $ prefixed leader contents <> blankline
blockToMarkdown' opts t@(Table _ blkCapt specs thead tbody tfoot) = do
let (caption, aligns, widths, headers, rows) = toLegacyTable blkCapt specs thead tbody tfoot
let numcols = maximum (length aligns : length widths :
map length (headers:rows))
caption' <- inlineListToMarkdown opts caption
- let caption'' = if null caption
- then blankline
- else
- if isEnabled Ext_table_captions opts
- then blankline $$ (": " <> caption') $$ blankline
- else blankline $$ caption' $$ blankline
+ let caption''
+ | null caption = blankline
+ | isEnabled Ext_table_captions opts
+ = blankline $$ (": " <> caption') $$ blankline
+ | otherwise = blankline $$ caption' $$ blankline
let hasSimpleCells = onlySimpleTableCells $ headers : rows
let isSimple = hasSimpleCells && all (==0) widths
let isPlainBlock (Plain _) = True
@@ -652,7 +651,7 @@ blockToMarkdown' opts t@(Table _ blkCapt specs thead tbody tfoot) = do
(id,) <$> pipeTable (all null headers) aligns' rawHeaders rawRows
| isEnabled Ext_raw_html opts -> fmap (id,) $
literal <$>
- (writeHtml5String opts{ writerTemplate = Nothing } $ Pandoc nullMeta [t])
+ writeHtml5String opts{ writerTemplate = Nothing } (Pandoc nullMeta [t])
| otherwise -> return (id, literal "[TABLE]")
return $ nst (tbl $$ caption'') $$ blankline
blockToMarkdown' opts (BulletList items) = do
@@ -680,7 +679,7 @@ inList p = local (\env -> env {envInList = True}) p
addMarkdownAttribute :: Text -> Text
addMarkdownAttribute s =
case span isTagText $ reverse $ parseTags s of
- (xs,(TagOpen t attrs:rest)) ->
+ (xs, TagOpen t attrs:rest) ->
renderTags' $ reverse rest ++ (TagOpen t attrs' : reverse xs)
where attrs' = ("markdown","1"):[(x,y) | (x,y) <- attrs,
x /= "markdown"]
@@ -745,17 +744,16 @@ pandocTable opts multiline headless aligns widths rawHeaders rawRows = do
| isSimple = map numChars columns
| otherwise = zipWith relWidth widths columns
let makeRow = hcat . intersperse (lblock 1 (literal " ")) .
- (zipWith3 alignHeader aligns widthsInChars)
+ zipWith3 alignHeader aligns widthsInChars
let rows' = map makeRow rawRows
let head' = makeRow rawHeaders
let underline = mconcat $ intersperse (literal " ") $
map (\width -> literal (T.replicate width "-")) widthsInChars
- let border = if multiline
- then literal (T.replicate (sum widthsInChars +
- length widthsInChars - 1) "-")
- else if headless
- then underline
- else empty
+ let border
+ | multiline = literal (T.replicate (sum widthsInChars +
+ length widthsInChars - 1) "-")
+ | headless = underline
+ | otherwise = empty
let head'' = if headless
then empty
else border <> cr <> head'
@@ -890,18 +888,17 @@ blockListToMarkdown opts blocks = do
isListBlock (OrderedList _ _) = True
isListBlock (DefinitionList _) = True
isListBlock _ = False
- commentSep = if variant == PlainText
- then Null
- else if isEnabled Ext_raw_html opts
- then RawBlock "html" "<!-- -->\n"
- else RawBlock "markdown" "&nbsp;\n"
- mapM (blockToMarkdown opts) (fixBlocks blocks) >>= return . mconcat
+ commentSep
+ | variant == PlainText = Null
+ | isEnabled Ext_raw_html opts = RawBlock "html" "<!-- -->\n"
+ | otherwise = RawBlock "markdown" "&nbsp;\n"
+ mconcat <$> mapM (blockToMarkdown opts) (fixBlocks blocks)
getKey :: Doc Text -> Key
getKey = toKey . render Nothing
findUsableIndex :: [Text] -> Int -> Int
-findUsableIndex lbls i = if (tshow i) `elem` lbls
+findUsableIndex lbls i = if tshow i `elem` lbls
then findUsableIndex lbls (i + 1)
else i
@@ -973,19 +970,19 @@ inlineListToMarkdown opts lst = do
go (if inlist then avoidBadWrapsInList lst else lst)
where go [] = return empty
go (i:is) = case i of
- (Link _ _ _) -> case is of
+ Link {} -> case is of
-- If a link is followed by another link, or '[', '(' or ':'
-- then we don't shortcut
- (Link _ _ _):_ -> unshortcutable
- Space:(Link _ _ _):_ -> unshortcutable
+ Link {}:_ -> unshortcutable
+ Space:Link {}:_ -> unshortcutable
Space:(Str(thead -> Just '[')):_ -> unshortcutable
Space:(RawInline _ (thead -> Just '[')):_ -> unshortcutable
Space:(Cite _ _):_ -> unshortcutable
- SoftBreak:(Link _ _ _):_ -> unshortcutable
+ SoftBreak:Link {}:_ -> unshortcutable
SoftBreak:(Str(thead -> Just '[')):_ -> unshortcutable
SoftBreak:(RawInline _ (thead -> Just '[')):_ -> unshortcutable
SoftBreak:(Cite _ _):_ -> unshortcutable
- LineBreak:(Link _ _ _):_ -> unshortcutable
+ LineBreak:Link {}:_ -> unshortcutable
LineBreak:(Str(thead -> Just '[')):_ -> unshortcutable
LineBreak:(RawInline _ (thead -> Just '[')):_ -> unshortcutable
LineBreak:(Cite _ _):_ -> unshortcutable
@@ -1016,16 +1013,16 @@ avoidBadWrapsInList :: [Inline] -> [Inline]
avoidBadWrapsInList [] = []
avoidBadWrapsInList (s:Str (T.uncons -> Just ('>',cs)):xs) | isSp s =
Str (" >" <> cs) : avoidBadWrapsInList xs
-avoidBadWrapsInList (s:Str (T.uncons -> Just (c, cs)):[])
- | T.null cs && isSp s && c `elem` ['-','*','+'] = Str (T.pack [' ', c]) : []
+avoidBadWrapsInList [s, Str (T.uncons -> Just (c, cs))]
+ | T.null cs && isSp s && c `elem` ['-','*','+'] = [Str $ T.pack [' ', c]]
avoidBadWrapsInList (s:Str (T.uncons -> Just (c, cs)):Space:xs)
| T.null cs && isSp s && c `elem` ['-','*','+'] =
Str (T.pack [' ', c]) : Space : avoidBadWrapsInList xs
avoidBadWrapsInList (s:Str cs:Space:xs)
| isSp s && isOrderedListMarker cs =
Str (" " <> cs) : Space : avoidBadWrapsInList xs
-avoidBadWrapsInList (s:Str cs:[])
- | isSp s && isOrderedListMarker cs = Str (" " <> cs) : []
+avoidBadWrapsInList [s, Str cs]
+ | isSp s && isOrderedListMarker cs = [Str $ " " <> cs]
avoidBadWrapsInList (x:xs) = x : avoidBadWrapsInList xs
isOrderedListMarker :: Text -> Bool
@@ -1105,7 +1102,7 @@ inlineToMarkdown opts (Strikeout lst) = do
else contents
inlineToMarkdown _ (Superscript []) = return empty
inlineToMarkdown opts (Superscript lst) =
- local (\env -> env {envEscapeSpaces = (envVariant env == Markdown)}) $ do
+ local (\env -> env {envEscapeSpaces = envVariant env == Markdown}) $ do
contents <- inlineListToMarkdown opts lst
if isEnabled Ext_superscript opts
then return $ "^" <> contents <> "^"
@@ -1123,7 +1120,7 @@ inlineToMarkdown opts (Superscript lst) =
Nothing -> literal $ "^(" <> rendered <> ")"
inlineToMarkdown _ (Subscript []) = return empty
inlineToMarkdown opts (Subscript lst) =
- local (\env -> env {envEscapeSpaces = (envVariant env == Markdown)}) $ do
+ local (\env -> env {envEscapeSpaces = envVariant env == Markdown}) $ do
contents <- inlineListToMarkdown opts lst
if isEnabled Ext_subscript opts
then return $ "~" <> contents <> "~"
@@ -1167,7 +1164,7 @@ inlineToMarkdown opts (Code attr str) = do
then 0
else maximum $ map T.length tickGroups
let marker = T.replicate (longest + 1) "`"
- let spacer = if (longest == 0) then "" else " "
+ let spacer = if longest == 0 then "" else " "
let attrs = if isEnabled Ext_inline_code_attributes opts && attr /= nullAttr
then attrsToMarkdown attr
else empty
@@ -1296,7 +1293,7 @@ inlineToMarkdown opts lnk@(Link attr txt (src, tit))
| isEnabled Ext_raw_html opts &&
not (isEnabled Ext_link_attributes opts) &&
attr /= nullAttr = -- use raw HTML
- (literal . T.strip) <$>
+ literal . T.strip <$>
writeHtml5String opts{ writerTemplate = Nothing } (Pandoc nullMeta [Plain [lnk]])
| otherwise = do
variant <- asks envVariant
@@ -1337,7 +1334,7 @@ inlineToMarkdown opts img@(Image attr alternate (source, tit))
| isEnabled Ext_raw_html opts &&
not (isEnabled Ext_link_attributes opts) &&
attr /= nullAttr = -- use raw HTML
- (literal . T.strip) <$>
+ literal . T.strip <$>
writeHtml5String opts{ writerTemplate = Nothing } (Pandoc nullMeta [Plain [img]])
| otherwise = do
variant <- asks envVariant
@@ -1352,7 +1349,7 @@ inlineToMarkdown opts img@(Image attr alternate (source, tit))
inlineToMarkdown opts (Note contents) = do
modify (\st -> st{ stNotes = contents : stNotes st })
st <- get
- let ref = literal $ writerIdentifierPrefix opts <> tshow (stNoteNum st + (length $ stNotes st) - 1)
+ let ref = literal $ writerIdentifierPrefix opts <> tshow (stNoteNum st + length (stNotes st) - 1)
if isEnabled Ext_footnotes opts
then return $ "[^" <> ref <> "]"
else return $ "[" <> ref <> "]"
diff --git a/src/Text/Pandoc/Writers/Ms.hs b/src/Text/Pandoc/Writers/Ms.hs
index 561053c88..f3aadde59 100644
--- a/src/Text/Pandoc/Writers/Ms.hs
+++ b/src/Text/Pandoc/Writers/Ms.hs
@@ -67,9 +67,7 @@ pandocToMs opts (Pandoc meta blocks) = do
let authorsMeta = map (escapeStr opts . stringify) $ docAuthors meta
hasHighlighting <- gets stHighlighting
let highlightingMacros = if hasHighlighting
- then case writerHighlightStyle opts of
- Nothing -> mempty
- Just sty -> styleToMs sty
+ then maybe mempty styleToMs $ writerHighlightStyle opts
else mempty
let context = defField "body" main
@@ -523,7 +521,7 @@ msFormatter opts _fmtopts =
where
fmtLine = mconcat . map fmtToken
fmtToken (toktype, tok) =
- "\\*[" <> (tshow toktype) <> " \"" <> (escapeStr opts tok) <> "\"]"
+ "\\*[" <> tshow toktype <> " \"" <> escapeStr opts tok <> "\"]"
highlightCode :: PandocMonad m => WriterOptions -> Attr -> Text -> MS m (Doc Text)
highlightCode opts attr str =
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index 36fa7a4c1..e41fb7176 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -71,7 +71,7 @@ pandocToODT opts doc@(Pandoc meta _) = do
refArchive <-
case writerReferenceDoc opts of
Just f -> liftM toArchive $ lift $ P.readFileLazy f
- Nothing -> lift $ (toArchive . B.fromStrict) <$>
+ Nothing -> lift $ toArchive . B.fromStrict <$>
P.readDataFile "reference.odt"
-- handle formulas and pictures
-- picEntriesRef <- P.newIORef ([] :: [Entry])
diff --git a/src/Text/Pandoc/Writers/OPML.hs b/src/Text/Pandoc/Writers/OPML.hs
index 3edf2daa3..810a94775 100644
--- a/src/Text/Pandoc/Writers/OPML.hs
+++ b/src/Text/Pandoc/Writers/OPML.hs
@@ -40,7 +40,7 @@ writeOPML opts (Pandoc meta blocks) = do
writeMarkdown def (Pandoc nullMeta [Plain ils]))
meta'
let blocks' = makeSections False (Just 1) blocks
- main <- (render colwidth . vcat) <$>
+ main <- render colwidth . vcat <$>
mapM (blockToOPML opts) blocks'
let context = defField "body" main metadata
return $
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index c6b66382b..bd20d2db6 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -387,7 +387,7 @@ blockToOpenDocument o bs
r <- vcat <$> mapM (deflistItemToOpenDocument o) b
setInDefinitionList False
return r
- preformatted s = (flush . vcat) <$> mapM (inPreformattedTags . escapeStringForXML) (T.lines s)
+ preformatted s = flush . vcat <$> mapM (inPreformattedTags . escapeStringForXML) (T.lines s)
mkBlockQuote b = do increaseIndent
i <- paraStyle
[("style:parent-style-name","Quotations")]
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
index 656ef6056..603a84acc 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
@@ -303,11 +303,11 @@ makeSpeakerNotesMap (Presentation _ slides) =
presentationToArchive :: PandocMonad m => WriterOptions -> Presentation -> m Archive
presentationToArchive opts pres = do
- distArchive <- (toArchive . BL.fromStrict) <$>
+ distArchive <- toArchive . BL.fromStrict <$>
P.readDefaultDataFile "reference.pptx"
refArchive <- case writerReferenceDoc opts of
Just f -> toArchive <$> P.readFileLazy f
- Nothing -> (toArchive . BL.fromStrict) <$>
+ Nothing -> toArchive . BL.fromStrict <$>
P.readDataFile "reference.pptx"
utctime <- P.getCurrentTime
@@ -351,10 +351,10 @@ curSlideHasSpeakerNotes =
getLayout :: PandocMonad m => Layout -> P m Element
getLayout layout = do
let layoutpath = case layout of
- (MetadataSlide{}) -> "ppt/slideLayouts/slideLayout1.xml"
- (TitleSlide _) -> "ppt/slideLayouts/slideLayout3.xml"
- (ContentSlide _ _) -> "ppt/slideLayouts/slideLayout2.xml"
- (TwoColumnSlide{}) -> "ppt/slideLayouts/slideLayout4.xml"
+ MetadataSlide{} -> "ppt/slideLayouts/slideLayout1.xml"
+ TitleSlide{} -> "ppt/slideLayouts/slideLayout3.xml"
+ ContentSlide{} -> "ppt/slideLayouts/slideLayout2.xml"
+ TwoColumnSlide{} -> "ppt/slideLayouts/slideLayout4.xml"
refArchive <- asks envRefArchive
distArchive <- asks envDistArchive
parseXml refArchive distArchive layoutpath
@@ -547,7 +547,7 @@ registerMedia fp caption = do
makeMediaEntry :: PandocMonad m => MediaInfo -> P m Entry
makeMediaEntry mInfo = do
- epochtime <- (floor . utcTimeToPOSIXSeconds) <$> asks envUTCTime
+ epochtime <- floor . utcTimeToPOSIXSeconds <$> asks envUTCTime
(imgBytes, _) <- P.fetchItem (T.pack $ mInfoFilePath mInfo)
let ext = fromMaybe "" (mInfoExt mInfo)
let fp = "ppt/media/image" <>
@@ -1473,7 +1473,7 @@ presentationToRelsEntry pres = do
elemToEntry :: PandocMonad m => FilePath -> Element -> P m Entry
elemToEntry fp element = do
- epochtime <- (floor . utcTimeToPOSIXSeconds) <$> asks envUTCTime
+ epochtime <- floor . utcTimeToPOSIXSeconds <$> asks envUTCTime
return $ toEntry fp epochtime $ renderXml element
slideToEntry :: PandocMonad m => Slide -> P m Entry
@@ -1500,8 +1500,7 @@ slideToSpeakerNotesEntry slide = do
slideToSpeakerNotesRelElement :: PandocMonad m => Slide -> P m (Maybe Element)
slideToSpeakerNotesRelElement (Slide _ _ (SpeakerNotes [])) = return Nothing
-slideToSpeakerNotesRelElement slide@(
- Slide{}) = do
+slideToSpeakerNotesRelElement slide@Slide{} = do
idNum <- slideNum slide
return $ Just $
mknode "Relationships"
@@ -1585,10 +1584,10 @@ slideToSlideRelElement :: PandocMonad m => Slide -> P m Element
slideToSlideRelElement slide = do
idNum <- slideNum slide
let target = case slide of
- (Slide _ (MetadataSlide{}) _) -> "../slideLayouts/slideLayout1.xml"
- (Slide _ (TitleSlide _) _) -> "../slideLayouts/slideLayout3.xml"
- (Slide _ (ContentSlide _ _) _) -> "../slideLayouts/slideLayout2.xml"
- (Slide _ (TwoColumnSlide{}) _) -> "../slideLayouts/slideLayout4.xml"
+ (Slide _ MetadataSlide{} _) -> "../slideLayouts/slideLayout1.xml"
+ (Slide _ TitleSlide{} _) -> "../slideLayouts/slideLayout3.xml"
+ (Slide _ ContentSlide{} _) -> "../slideLayouts/slideLayout2.xml"
+ (Slide _ TwoColumnSlide{} _) -> "../slideLayouts/slideLayout4.xml"
speakerNotesRels <- maybeToList <$> speakerNotesSlideRelElement slide
@@ -1819,7 +1818,7 @@ getSpeakerNotesFilePaths = do
presentationToContentTypes :: PandocMonad m => Presentation -> P m ContentTypes
presentationToContentTypes p@(Presentation _ slides) = do
- mediaInfos <- (mconcat . M.elems) <$> gets stMediaIds
+ mediaInfos <- mconcat . M.elems <$> gets stMediaIds
filePaths <- patternsToFilePaths $ inheritedPatterns p
let mediaFps = filter (match (compile "ppt/media/image*")) filePaths
let defaults = [ DefaultContentType "xml" "application/xml"
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
index c6d76424d..affec38aa 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
@@ -537,10 +537,10 @@ withAttr _ sp = sp
blockToShape :: Block -> Pres Shape
blockToShape (Plain ils) = blockToShape (Para ils)
blockToShape (Para (il:_)) | Image attr ils (url, _) <- il =
- (withAttr attr . Pic def (T.unpack url)) <$> inlinesToParElems ils
+ withAttr attr . Pic def (T.unpack url) <$> inlinesToParElems ils
blockToShape (Para (il:_)) | Link _ (il':_) target <- il
, Image attr ils (url, _) <- il' =
- (withAttr attr . Pic def{picPropLink = Just $ ExternalTarget target} (T.unpack url))
+ withAttr attr . Pic def{picPropLink = Just $ ExternalTarget target} (T.unpack url)
<$> inlinesToParElems ils
blockToShape (Table _ blkCapt specs thead tbody tfoot) = do
let (caption, algn, _, hdrCells, rows) = toLegacyTable blkCapt specs thead tbody tfoot
@@ -721,7 +721,7 @@ makeNoteEntry (n, blks) =
let enum = Str (tshow n <> ".")
in
case blks of
- (Para ils : blks') -> (Para $ enum : Space : ils) : blks'
+ (Para ils : blks') -> Para (enum : Space : ils) : blks'
_ -> Para [enum] : blks
forceFontSize :: Pixels -> Pres a -> Pres a
@@ -767,7 +767,7 @@ getMetaSlide = do
mempty
addSpeakerNotesToMetaSlide :: Slide -> [Block] -> Pres (Slide, [Block])
-addSpeakerNotesToMetaSlide (Slide sldId layout@(MetadataSlide{}) spkNotes) blks =
+addSpeakerNotesToMetaSlide (Slide sldId layout@MetadataSlide{} spkNotes) blks =
do let (ntsBlks, blks') = span isNotesDiv blks
spkNotes' <- mconcat <$> mapM blockToSpeakerNotes ntsBlks
return (Slide sldId layout (spkNotes <> spkNotes'), blks')
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 55c1b470b..e3966ed07 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -241,12 +241,12 @@ blockToRTF _ _ b@(RawBlock f str)
| otherwise = do
report $ BlockNotRendered b
return ""
-blockToRTF indent alignment (BulletList lst) = (spaceAtEnd . T.concat) <$>
+blockToRTF indent alignment (BulletList lst) = spaceAtEnd . T.concat <$>
mapM (listItemToRTF alignment indent (bulletMarker indent)) lst
blockToRTF indent alignment (OrderedList attribs lst) =
- (spaceAtEnd . T.concat) <$>
+ spaceAtEnd . T.concat <$>
zipWithM (listItemToRTF alignment indent) (orderedMarkers indent attribs) lst
-blockToRTF indent alignment (DefinitionList lst) = (spaceAtEnd . T.concat) <$>
+blockToRTF indent alignment (DefinitionList lst) = spaceAtEnd . T.concat <$>
mapM (definitionListItemToRTF alignment indent) lst
blockToRTF indent _ HorizontalRule = return $
rtfPar indent 0 AlignCenter "\\emdash\\emdash\\emdash\\emdash\\emdash"
diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs
index ddf1d76e3..a9ee5eece 100644
--- a/src/Text/Pandoc/Writers/TEI.hs
+++ b/src/Text/Pandoc/Writers/TEI.hs
@@ -205,14 +205,14 @@ tableRowToTEI :: PandocMonad m
-> [[Block]]
-> m (Doc Text)
tableRowToTEI opts cols =
- (inTagsIndented "row" . vcat) <$> mapM (tableItemToTEI opts) cols
+ inTagsIndented "row" . vcat <$> mapM (tableItemToTEI opts) cols
tableHeadersToTEI :: PandocMonad m
=> WriterOptions
-> [[Block]]
-> m (Doc Text)
tableHeadersToTEI opts cols =
- (inTags True "row" [("role","label")] . vcat) <$>
+ inTags True "row" [("role","label")] . vcat <$>
mapM (tableItemToTEI opts) cols
tableItemToTEI :: PandocMonad m
@@ -220,7 +220,7 @@ tableItemToTEI :: PandocMonad m
-> [Block]
-> m (Doc Text)
tableItemToTEI opts item =
- (inTags False "cell" [] . vcat) <$> mapM (blockToTEI opts) item
+ inTags False "cell" [] . vcat <$> mapM (blockToTEI opts) item
-- | Convert a list of inline elements to TEI.
inlinesToTEI :: PandocMonad m => WriterOptions -> [Inline] -> m (Doc Text)
diff --git a/src/Text/Pandoc/Writers/XWiki.hs b/src/Text/Pandoc/Writers/XWiki.hs
index cd72d9647..c35235650 100644
--- a/src/Text/Pandoc/Writers/XWiki.hs
+++ b/src/Text/Pandoc/Writers/XWiki.hs
@@ -45,7 +45,7 @@ import Text.Pandoc.Shared
import Text.Pandoc.Writers.MediaWiki (highlightingLangs)
import Text.Pandoc.Writers.Shared (toLegacyTable)
-data WriterState = WriterState {
+newtype WriterState = WriterState {
listLevel :: Text -- String at the beginning of items
}