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/Markdown.hs21
-rw-r--r--src/Text/Pandoc/Writers/Powerpoint/Output.hs10
-rw-r--r--src/Text/Pandoc/Writers/Powerpoint/Presentation.hs6
-rw-r--r--src/Text/Pandoc/Writers/XWiki.hs7
4 files changed, 21 insertions, 23 deletions
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 10ab3dfe1..87e41b766 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -25,7 +25,7 @@ import Data.Char (isAlphaNum)
import Data.Default
import Data.List (find, intersperse, sortBy, transpose)
import qualified Data.Map as M
-import Data.Maybe (fromMaybe, catMaybes)
+import Data.Maybe (fromMaybe, mapMaybe)
import Data.Ord (comparing)
import qualified Data.Set as Set
import Data.Text (Text)
@@ -121,7 +121,7 @@ mmdTitleBlock (Context hashmap) =
| null xs -> empty
| otherwise -> k' <> ":" <> space <>
hcat (intersperse "; " $
- catMaybes $ map fromVal xs)
+ mapMaybe fromVal xs)
(k', SimpleVal x)
| isEmpty x -> empty
| otherwise -> k' <> ":" <> space <>
@@ -256,7 +256,7 @@ keyToMarkdown opts (label', (src, tit), attr) = do
notesToMarkdown :: PandocMonad m => WriterOptions -> [[Block]] -> MD m (Doc Text)
notesToMarkdown opts notes = do
n <- gets stNoteNum
- notes' <- mapM (\(num, note) -> noteToMarkdown opts num note) (zip [n..] notes)
+ notes' <- zipWithM (noteToMarkdown opts) [n..] notes
modify $ \st -> st { stNoteNum = stNoteNum st + length notes }
return $ vsep notes'
@@ -647,8 +647,7 @@ blockToMarkdown' opts (OrderedList (start,sty,delim) items) = do
then m <> T.replicate (3 - T.length m) " "
else m) markers
contents <- inList $
- mapM (\(item, num) -> orderedListItemToMarkdown opts item num) $
- zip markers' items
+ zipWithM (orderedListItemToMarkdown opts) markers' items
return $ (if isTightList items then vcat else vsep) contents <> blankline
blockToMarkdown' opts (DefinitionList items) = do
contents <- inList $ mapM (definitionListItemToMarkdown opts) items
@@ -680,11 +679,11 @@ pipeTable headless aligns rawHeaders rawRows = do
hcat (intersperse (literal "|") $
zipWith3 blockFor aligns widths (map chomp cs))
<> literal "|"
- let toborder (a, w) = literal $ case a of
- AlignLeft -> ":" <> T.replicate (w + 1) "-"
- AlignCenter -> ":" <> T.replicate w "-" <> ":"
- AlignRight -> T.replicate (w + 1) "-" <> ":"
- AlignDefault -> T.replicate (w + 2) "-"
+ let toborder a w = literal $ case a of
+ AlignLeft -> ":" <> T.replicate (w + 1) "-"
+ AlignCenter -> ":" <> T.replicate w "-" <> ":"
+ AlignRight -> T.replicate (w + 1) "-" <> ":"
+ AlignDefault -> T.replicate (w + 2) "-"
-- note: pipe tables can't completely lack a
-- header; for a headerless table, we need a header of empty cells.
-- see jgm/pandoc#1996.
@@ -692,7 +691,7 @@ pipeTable headless aligns rawHeaders rawRows = do
then torow (replicate (length aligns) empty)
else torow rawHeaders
let border = nowrap $ literal "|" <> hcat (intersperse (literal "|") $
- map toborder $ zip aligns widths) <> literal "|"
+ zipWith toborder aligns widths) <> literal "|"
let body = vcat $ map torow rawRows
return $ header $$ border $$ body
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
index 344a5564a..856dbfcd0 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
@@ -249,7 +249,7 @@ presentationToArchiveP p@(Presentation docProps slides) = do
filePaths <- patternsToFilePaths $ inheritedPatterns p
-- make sure all required files are available:
- let missingFiles = filter (\fp -> not (fp `elem` filePaths)) requiredFiles
+ let missingFiles = filter (`notElem` filePaths) requiredFiles
unless (null missingFiles)
(throwError $
PandocSomeError $
@@ -1539,15 +1539,15 @@ slideToSlideRelEntry slide = do
element <- slideToSlideRelElement slide
elemToEntry ("ppt/slides/_rels/" <> idNumToFilePath idNum <> ".rels") element
-linkRelElement :: PandocMonad m => Int -> LinkTarget -> P m Element
-linkRelElement rIdNum (InternalTarget targetId) = do
+linkRelElement :: PandocMonad m => (Int, LinkTarget) -> P m Element
+linkRelElement (rIdNum, InternalTarget targetId) = do
targetIdNum <- getSlideIdNum targetId
return $
mknode "Relationship" [ ("Id", "rId" <> show rIdNum)
, ("Type", "http://schemas.openxmlformats.org/officeDocument/2006/relationships/slide")
, ("Target", "slide" <> show targetIdNum <> ".xml")
] ()
-linkRelElement rIdNum (ExternalTarget (url, _)) = do
+linkRelElement (rIdNum, ExternalTarget (url, _)) = do
return $
mknode "Relationship" [ ("Id", "rId" <> show rIdNum)
, ("Type", "http://schemas.openxmlformats.org/officeDocument/2006/relationships/hyperlink")
@@ -1556,7 +1556,7 @@ linkRelElement rIdNum (ExternalTarget (url, _)) = do
] ()
linkRelElements :: PandocMonad m => M.Map Int LinkTarget -> P m [Element]
-linkRelElements mp = mapM (\(n, lnk) -> linkRelElement n lnk) (M.toList mp)
+linkRelElements mp = mapM linkRelElement (M.toList mp)
mediaRelElement :: MediaInfo -> Element
mediaRelElement mInfo =
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
index 75ce0dd4e..d36c92fa3 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Presentation.hs
@@ -712,8 +712,8 @@ blocksToSlide blks = do
slideLevel <- asks envSlideLevel
blocksToSlide' slideLevel blks' spkNotes
-makeNoteEntry :: Int -> [Block] -> [Block]
-makeNoteEntry n blks =
+makeNoteEntry :: (Int, [Block]) -> [Block]
+makeNoteEntry (n, blks) =
let enum = Str (tshow n <> ".")
in
case blks of
@@ -742,7 +742,7 @@ makeEndNotesSlideBlocks = do
ls -> ls
ident = Shared.uniqueIdent exts title anchorSet
hdr = Header slideLevel (ident, [], []) title
- blks = concatMap (\(n, bs) -> makeNoteEntry n bs) $
+ blks = concatMap makeNoteEntry $
M.toList noteIds
in return $ hdr : blks
diff --git a/src/Text/Pandoc/Writers/XWiki.hs b/src/Text/Pandoc/Writers/XWiki.hs
index 7afe845c7..4f9494933 100644
--- a/src/Text/Pandoc/Writers/XWiki.hs
+++ b/src/Text/Pandoc/Writers/XWiki.hs
@@ -54,10 +54,9 @@ type XWikiReader m = ReaderT WriterState m
-- | Convert Pandoc to XWiki.
writeXWiki :: PandocMonad m => WriterOptions -> Pandoc -> m Text
-writeXWiki _ (Pandoc _ blocks) = do
+writeXWiki _ (Pandoc _ blocks) =
let env = WriterState { listLevel = "" }
- body <- runReaderT (blockListToXWiki blocks) env
- return $ body
+ in runReaderT (blockListToXWiki blocks) env
-- | Concatenates strings with line breaks between them.
vcat :: [Text] -> Text
@@ -219,7 +218,7 @@ inlineToXWiki (Link (id', _, _) txt (src, _)) = do
inlineToXWiki (Image _ alt (source, tit)) = do
alt' <- inlineListToXWiki alt
let
- params = intercalate " " $ filter (not . Text.null) [
+ params = Text.unwords $ filter (not . Text.null) [
if Text.null alt' then "" else "alt=\"" <> alt' <> "\"",
if Text.null tit then "" else "title=\"" <> tit <> "\""
]