aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/PDF.hs5
-rw-r--r--src/Text/Pandoc/Readers/CommonMark.hs2
-rw-r--r--src/Text/Pandoc/Readers/DocBook.hs2
-rw-r--r--src/Text/Pandoc/Readers/Docx.hs6
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs3
-rw-r--r--src/Text/Pandoc/Readers/DokuWiki.hs2
-rw-r--r--src/Text/Pandoc/Readers/JATS.hs2
-rw-r--r--src/Text/Pandoc/Readers/Man.hs26
-rw-r--r--src/Text/Pandoc/Readers/RST.hs2
-rw-r--r--src/Text/Pandoc/Readers/Vimwiki.hs18
-rw-r--r--src/Text/Pandoc/Shared.hs7
-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
-rw-r--r--test/Tests/Command.hs6
16 files changed, 59 insertions, 66 deletions
diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs
index bd36f0d33..5ef2bd80c 100644
--- a/src/Text/Pandoc/PDF.hs
+++ b/src/Text/Pandoc/PDF.hs
@@ -440,10 +440,7 @@ html2pdf verbosity program args source = do
-- We read PDF as a strict bytestring to make sure that the
-- temp directory is removed on Windows.
-- See https://github.com/jgm/pandoc/issues/1192.
- then do
- res <- Just . BL.fromChunks . (:[]) <$>
- BS.readFile pdfFile
- return res
+ then Just . BL.fromChunks . (:[]) <$> BS.readFile pdfFile
else return Nothing
return $ case (exit, mbPdf) of
(ExitFailure _, _) -> Left out
diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs
index 40b6f77c9..f4daabc57 100644
--- a/src/Text/Pandoc/Readers/CommonMark.hs
+++ b/src/Text/Pandoc/Readers/CommonMark.hs
@@ -177,7 +177,7 @@ addInlines :: ReaderOptions -> [Node] -> [Inline]
addInlines opts = foldr (addInline opts) []
addInline :: ReaderOptions -> Node -> [Inline] -> [Inline]
-addInline opts (Node _ (TEXT t) _) = (foldr ((++) . toinl) [] clumps ++)
+addInline opts (Node _ (TEXT t) _) = (concatMap toinl clumps ++)
where clumps = T.groupBy samekind t
samekind ' ' ' ' = True
samekind ' ' _ = False
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs
index ade9d27a3..fbd9d595d 100644
--- a/src/Text/Pandoc/Readers/DocBook.hs
+++ b/src/Text/Pandoc/Readers/DocBook.hs
@@ -941,7 +941,7 @@ elementToStr x = x
parseInline :: PandocMonad m => Content -> DB m Inlines
parseInline (Text (CData _ s _)) = return $ text $ T.pack s
parseInline (CRef ref) =
- return $ maybe (text $ T.toUpper $ T.pack ref) (text . T.pack) $ lookupEntity ref
+ return $ text $ maybe (T.toUpper $ T.pack ref) T.pack $ lookupEntity ref
parseInline (Elem e) =
case qName (elName e) of
"equation" -> equation e displayMath
diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index 80fd6285c..c4bb16ec6 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -528,9 +528,9 @@ extraInfo :: (Eq (StyleName a), PandocMonad m, HasStyleName a)
=> (Attr -> i -> i) -> a -> DocxContext m (i -> i)
extraInfo f s = do
opts <- asks docxOptions
- return $ if | isEnabled Ext_styles opts
- -> f ("", [], [("custom-style", fromStyleName $ getStyleName s)])
- | otherwise -> id
+ return $ if isEnabled Ext_styles opts
+ then f ("", [], [("custom-style", fromStyleName $ getStyleName s)])
+ else id
parStyleToTransform :: PandocMonad m => ParagraphStyle -> DocxContext m (Blocks -> Blocks)
parStyleToTransform pPr
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index 8598ada6f..b4a0c1ac9 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -347,8 +347,7 @@ getDocumentXmlPath zf = do
entry <- findEntryByPath "_rels/.rels" zf
relsElem <- (parseXMLDoc . UTF8.toStringLazy . fromEntry) entry
let rels = filterChildrenName (\n -> qName n == "Relationship") relsElem
- rel <- listToMaybe $
- filter (\e -> findAttr (QName "Type" Nothing Nothing) e ==
+ rel <- find (\e -> findAttr (QName "Type" Nothing Nothing) e ==
Just "http://schemas.openxmlformats.org/officeDocument/2006/relationships/officeDocument")
rels
fp <- findAttr (QName "Target" Nothing Nothing) rel
diff --git a/src/Text/Pandoc/Readers/DokuWiki.hs b/src/Text/Pandoc/Readers/DokuWiki.hs
index da6e7df64..727dd1ecc 100644
--- a/src/Text/Pandoc/Readers/DokuWiki.hs
+++ b/src/Text/Pandoc/Readers/DokuWiki.hs
@@ -472,7 +472,7 @@ table = do
let (headerRow, body) = if firstSeparator == '^'
then (head rows, tail rows)
else ([], rows)
- let attrs = const (AlignDefault, 0.0) <$> transpose rows
+ let attrs = (AlignDefault, 0.0) <$ transpose rows
pure $ B.table mempty attrs headerRow body
tableRows :: PandocMonad m => DWParser m [[B.Blocks]]
diff --git a/src/Text/Pandoc/Readers/JATS.hs b/src/Text/Pandoc/Readers/JATS.hs
index 320b9c1dd..4b8eb9098 100644
--- a/src/Text/Pandoc/Readers/JATS.hs
+++ b/src/Text/Pandoc/Readers/JATS.hs
@@ -443,7 +443,7 @@ elementToStr x = x
parseInline :: PandocMonad m => Content -> JATS m Inlines
parseInline (Text (CData _ s _)) = return $ text $ T.pack s
parseInline (CRef ref) =
- return $ maybe (text $ T.toUpper $ T.pack ref) text $ T.pack <$> lookupEntity ref
+ return . text . maybe (T.toUpper $ T.pack ref) T.pack $ lookupEntity ref
parseInline (Elem e) =
case qName (elName e) of
"italic" -> emph <$> innerInlines
diff --git a/src/Text/Pandoc/Readers/Man.hs b/src/Text/Pandoc/Readers/Man.hs
index feacb8450..314643621 100644
--- a/src/Text/Pandoc/Readers/Man.hs
+++ b/src/Text/Pandoc/Readers/Man.hs
@@ -234,22 +234,22 @@ linePartsToInlines = go False
go mono (RoffStr s : xs)
| mono = code s <> go mono xs
| otherwise = text s <> go mono xs
- go mono (Font fs: xs) =
- if litals > 0 && litals >= lbolds && litals >= lmonos
- then emph (go mono (Font fs{ fontItalic = False } :
+ go mono (Font fs: xs)
+ | litals > 0 && litals >= lbolds && litals >= lmonos
+ = emph (go mono (Font fs{ fontItalic = False } :
map (adjustFontSpec (\s -> s{ fontItalic = False }))
itals)) <>
go mono italsrest
- else if lbolds > 0 && lbolds >= lmonos
- then strong (go mono (Font fs{ fontBold = False } :
- map (adjustFontSpec (\s -> s{ fontBold = False }))
- bolds)) <>
- go mono boldsrest
- else if lmonos > 0
- then go True (Font fs{ fontMonospace = False } :
- map (adjustFontSpec (\s -> s { fontMonospace = False }))
- monos) <> go mono monosrest
- else go mono xs
+ | lbolds > 0 && lbolds >= lmonos
+ = strong (go mono (Font fs{ fontBold = False } :
+ map (adjustFontSpec (\s -> s{ fontBold = False }))
+ bolds)) <>
+ go mono boldsrest
+ | lmonos > 0
+ = go True (Font fs{ fontMonospace = False } :
+ map (adjustFontSpec (\s -> s { fontMonospace = False }))
+ monos) <> go mono monosrest
+ | otherwise = go mono xs
where
adjustFontSpec f (Font fspec) = Font (f fspec)
adjustFontSpec _ x = x
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index d2fba4449..68b853ca5 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -952,7 +952,7 @@ unicodeTransform t
$ extractUnicodeChar zs
extractUnicodeChar :: Text -> Maybe (Char, Text)
-extractUnicodeChar s = maybe Nothing (\c -> Just (c,rest)) mbc
+extractUnicodeChar s = fmap (\c -> (c,rest)) mbc
where (ds,rest) = T.span isHexDigit s
mbc = safeRead ("'\\x" <> ds <> "'")
diff --git a/src/Text/Pandoc/Readers/Vimwiki.hs b/src/Text/Pandoc/Readers/Vimwiki.hs
index f7edabc48..d641df8a5 100644
--- a/src/Text/Pandoc/Readers/Vimwiki.hs
+++ b/src/Text/Pandoc/Readers/Vimwiki.hs
@@ -546,21 +546,21 @@ link :: PandocMonad m => VwParser m Inlines
link = try $ do
string "[["
contents <- lookAhead $ manyTillChar anyChar (string "]]")
- case T.any (== '|') contents of
- False -> do
- manyTill anyChar (string "]]")
--- not using try here because [[hell]o]] is not rendered as a link in vimwiki
- let tit = if isURI contents
- then ""
- else "wikilink"
- return $ B.link (procLink contents) tit (B.str contents)
- True -> do
+ if T.any (== '|') contents
+ then do
url <- manyTillChar anyChar $ char '|'
lab <- mconcat <$> manyTill inline (string "]]")
let tit = if isURI url
then ""
else "wikilink"
return $ B.link (procLink url) tit lab
+ else do
+ manyTill anyChar (string "]]")
+-- not using try here because [[hell]o]] is not rendered as a link in vimwiki
+ let tit = if isURI contents
+ then ""
+ else "wikilink"
+ return $ B.link (procLink contents) tit (B.str contents)
image :: PandocMonad m => VwParser m Inlines
image = try $ do
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 69ade7e95..933798534 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -115,8 +115,7 @@ import qualified Data.Bifunctor as Bifunctor
import Data.Char (isAlpha, isLower, isSpace, isUpper, toLower, isAlphaNum,
generalCategory, GeneralCategory(NonSpacingMark,
SpacingCombiningMark, EnclosingMark, ConnectorPunctuation))
-import Data.List (find, intercalate, intersperse, stripPrefix, sortBy)
-import Data.Ord (comparing)
+import Data.List (find, intercalate, intersperse, stripPrefix, sortOn)
import qualified Data.Map as M
import Data.Maybe (mapMaybe, fromMaybe)
import Data.Monoid (Any (..))
@@ -621,7 +620,7 @@ headerLtEq _ _ = False
uniqueIdent :: Extensions -> [Inline] -> Set.Set T.Text -> T.Text
uniqueIdent exts title' usedIdents =
if baseIdent `Set.member` usedIdents
- then case find (\x -> not $ numIdent x `Set.member` usedIdents)
+ then case find (\x -> numIdent x `Set.notMember` usedIdents)
([1..60000] :: [Int]) of
Just x -> numIdent x
Nothing -> baseIdent
@@ -799,7 +798,7 @@ filterIpynbOutput mode = walk go
-> Div (ident, ("output":os), kvs) bs
| otherwise -> Div (ident, ("output":os), kvs) $
walk removeANSI $
- take 1 $ sortBy (comparing rank) bs
+ take 1 $ sortOn rank bs
where
rank (RawBlock (Format "html") _)
| fmt == Format "html" = (1 :: Int)
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 <> "\""
]
diff --git a/test/Tests/Command.hs b/test/Tests/Command.hs
index d76cca71a..f5fd45502 100644
--- a/test/Tests/Command.hs
+++ b/test/Tests/Command.hs
@@ -85,8 +85,8 @@ dropPercent :: String -> String
dropPercent ('%':xs) = dropWhile (== ' ') xs
dropPercent xs = xs
-runCommandTest :: FilePath -> (Int, String) -> TestTree
-runCommandTest pandocpath (num, code) =
+runCommandTest :: FilePath -> Int -> String -> TestTree
+runCommandTest pandocpath num code =
let codelines = lines code
(continuations, r1) = span ("\\" `isSuffixOf`) codelines
(cmd, r2) = (dropPercent (unwords (map init continuations ++ take 1 r1)),
@@ -104,5 +104,5 @@ extractCommandTest pandocpath fp = unsafePerformIO $ do
Pandoc _ blocks <- runIOorExplode (readMarkdown
def{ readerExtensions = pandocExtensions } contents)
let codeblocks = map extractCode $ filter isCodeBlock blocks
- let cases = map (runCommandTest pandocpath) $ zip [1..] codeblocks
+ let cases = zipWith (runCommandTest pandocpath) [1..] codeblocks
return $ testGroup fp cases