aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/CSV.hs3
-rw-r--r--src/Text/Pandoc/Readers/DocBook.hs4
-rw-r--r--src/Text/Pandoc/Readers/Docx/Combine.hs1
-rw-r--r--src/Text/Pandoc/Readers/EPUB.hs6
-rw-r--r--src/Text/Pandoc/Readers/Ipynb.hs22
-rw-r--r--src/Text/Pandoc/Readers/JATS.hs4
-rw-r--r--src/Text/Pandoc/Readers/Jira.hs4
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs6
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Parsing.hs4
-rw-r--r--src/Text/Pandoc/Readers/Man.hs8
-rw-r--r--src/Text/Pandoc/Readers/Metadata.hs6
-rw-r--r--src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs2
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs2
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs3
14 files changed, 32 insertions, 43 deletions
diff --git a/src/Text/Pandoc/Readers/CSV.hs b/src/Text/Pandoc/Readers/CSV.hs
index 103e211e7..62c94b3a0 100644
--- a/src/Text/Pandoc/Readers/CSV.hs
+++ b/src/Text/Pandoc/Readers/CSV.hs
@@ -2,7 +2,6 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Readers.RST
Copyright : Copyright (C) 2006-2019 John MacFarlane
@@ -31,7 +30,7 @@ readCSV :: PandocMonad m
=> ReaderOptions -- ^ Reader options
-> Text -- ^ Text to parse (assuming @'\n'@ line endings)
-> m Pandoc
-readCSV _opts s = do
+readCSV _opts s =
case parseCSV defaultCSVOptions (crFilter s) of
Right (r:rs) -> return $ B.doc $ B.table capt (zip aligns widths) hdrs rows
where capt = mempty
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs
index fbd9d595d..535ade658 100644
--- a/src/Text/Pandoc/Readers/DocBook.hs
+++ b/src/Text/Pandoc/Readers/DocBook.hs
@@ -741,7 +741,7 @@ parseBlock (Elem e) =
"refsect2" -> sect 2
"refsect3" -> sect 3
"refsection" -> gets dbSectionLevel >>= sect . (+1)
- l@_ | l `elem` admonitionTags -> parseAdmonition $ T.pack l
+ l | l `elem` admonitionTags -> parseAdmonition $ T.pack l
"area" -> skip
"areaset" -> skip
"areaspec" -> skip
@@ -920,7 +920,7 @@ parseBlock (Elem e) =
-- include the label and leave it to styling.
title <- case filterChild (named "title") e of
Just t -> divWith ("", ["title"], []) . plain <$> getInlines t
- Nothing -> return $ mempty
+ Nothing -> return mempty
-- this will ignore the title element if it is present
b <- getBlocks e
-- we also attach the label as a class, so it can be styled properly
diff --git a/src/Text/Pandoc/Readers/Docx/Combine.hs b/src/Text/Pandoc/Readers/Docx/Combine.hs
index 82791d669..cf7b6051d 100644
--- a/src/Text/Pandoc/Readers/Docx/Combine.hs
+++ b/src/Text/Pandoc/Readers/Docx/Combine.hs
@@ -1,7 +1,6 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PatternGuards #-}
-{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Readers.Docx.Combine
diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs
index bcff7e4b8..f7a7de896 100644
--- a/src/Text/Pandoc/Readers/EPUB.hs
+++ b/src/Text/Pandoc/Readers/EPUB.hs
@@ -71,7 +71,7 @@ archiveToEPUB os archive = do
spine <- parseSpine items content
let escapedSpine = map (escapeURI . T.pack . takeFileName . fst) spine
Pandoc _ bs <-
- foldM' (\a b -> ((a <>) . walk (prependHash $ escapedSpine))
+ foldM' (\a b -> ((a <>) . walk (prependHash escapedSpine))
`liftM` parseSpineElem root b) mempty spine
let ast = coverDoc <> Pandoc meta bs
fetchImages (M.elems items) root archive ast
@@ -170,7 +170,7 @@ parseMeta content = do
let coverId = findAttr (emptyName "content") =<< filterChild findCover meta
return (coverId, r)
where
- findCover e = maybe False (== "cover") (findAttr (emptyName "name") e)
+ findCover e = (== Just "cover") (findAttr (emptyName "name") e)
-- http://www.idpf.org/epub/30/spec/epub30-publications.html#sec-metadata-elem
parseMetaItem :: Element -> Meta -> Meta
@@ -294,4 +294,4 @@ findElementE :: PandocMonad m => QName -> Element -> m Element
findElementE e x = mkE ("Unable to find element: " ++ show e) $ findElement e x
mkE :: PandocMonad m => String -> Maybe a -> m a
-mkE s = maybe (throwError . PandocParseError $ T.pack $ s) return
+mkE s = maybe (throwError . PandocParseError $ T.pack s) return
diff --git a/src/Text/Pandoc/Readers/Ipynb.hs b/src/Text/Pandoc/Readers/Ipynb.hs
index 8efc230cc..09d98f667 100644
--- a/src/Text/Pandoc/Readers/Ipynb.hs
+++ b/src/Text/Pandoc/Readers/Ipynb.hs
@@ -1,10 +1,8 @@
{-# LANGUAGE NoImplicitPrelude #-}
-{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Readers.Ipynb
Copyright : Copyright (C) 2019 John MacFarlane
@@ -130,9 +128,9 @@ addAttachment (fname, mimeBundle) = do
outputToBlock :: PandocMonad m => Output a -> m B.Blocks
outputToBlock Stream{ streamName = sName,
- streamText = Source text } = do
+ streamText = Source text } =
return $ B.divWith ("",["output","stream",sName],[])
- $ B.codeBlock $ T.concat $ text
+ $ B.codeBlock $ T.concat text
outputToBlock DisplayData{ displayData = data',
displayMetadata = metadata' } =
B.divWith ("",["output", "display_data"],[]) <$>
@@ -144,11 +142,11 @@ outputToBlock ExecuteResult{ executeCount = ec,
<$> handleData metadata' data'
outputToBlock Err{ errName = ename,
errValue = evalue,
- errTraceback = traceback } = do
+ errTraceback = traceback } =
return $ B.divWith ("",["output","error"],
[("ename",ename),
("evalue",evalue)])
- $ B.codeBlock $ T.unlines $ traceback
+ $ B.codeBlock $ T.unlines traceback
-- We want to display the richest output possible given
-- the output format.
@@ -166,7 +164,7 @@ handleData metadata (MimeBundle mb) =
-- normally metadata maps from mime types to key-value map;
-- but not always...
let meta = case M.lookup mt metadata of
- Just v@(Object{}) ->
+ Just v@Object{} ->
case fromJSON v of
Success m' -> m'
Error _ -> mempty
@@ -183,13 +181,13 @@ handleData metadata (MimeBundle mb) =
| otherwise = return mempty
dataBlock ("text/html", TextualData t)
- = return $ B.rawBlock "html" $ t
+ = return $ B.rawBlock "html" t
dataBlock ("text/latex", TextualData t)
- = return $ B.rawBlock "latex" $ t
+ = return $ B.rawBlock "latex" t
dataBlock ("text/plain", TextualData t) =
- return $ B.codeBlock $ t
+ return $ B.codeBlock t
dataBlock (_, JsonData v) =
return $ B.codeBlockWith ("",["json"],[]) $ T.pack $ toStringLazy $ encode v
@@ -200,11 +198,11 @@ jsonMetaToMeta :: JSONMeta -> M.Map Text MetaValue
jsonMetaToMeta = M.map valueToMetaValue
where
valueToMetaValue :: Value -> MetaValue
- valueToMetaValue x@(Object{}) =
+ valueToMetaValue x@Object{} =
case fromJSON x of
Error s -> MetaString $ T.pack s
Success jm' -> MetaMap $ jsonMetaToMeta jm'
- valueToMetaValue x@(Array{}) =
+ valueToMetaValue x@Array{} =
case fromJSON x of
Error s -> MetaString $ T.pack s
Success xs -> MetaList $ map valueToMetaValue xs
diff --git a/src/Text/Pandoc/Readers/JATS.hs b/src/Text/Pandoc/Readers/JATS.hs
index 4b8eb9098..1ccbd5a41 100644
--- a/src/Text/Pandoc/Readers/JATS.hs
+++ b/src/Text/Pandoc/Readers/JATS.hs
@@ -226,7 +226,7 @@ parseBlock (Elem e) =
terms' <- mapM getInlines terms
items' <- mapM getBlocks items
return (mconcat $ intersperse (str "; ") terms', items')
- parseFigure = do
+ parseFigure =
-- if a simple caption and single graphic, we emit a standard
-- implicit figure. otherwise, we emit a div with the contents
case filterChildren (named "graphic") e of
@@ -238,7 +238,7 @@ parseBlock (Elem e) =
(filterChildren (const True) t)
Nothing -> return mempty
img <- getGraphic (Just (caption, attrValue "id" e)) g
- return $ para $ img
+ return $ para img
_ -> divWith (attrValue "id" e, ["fig"], []) <$> getBlocks e
parseTable = do
let isCaption x = named "title" x || named "caption" x
diff --git a/src/Text/Pandoc/Readers/Jira.hs b/src/Text/Pandoc/Readers/Jira.hs
index 362693af9..46077a4a9 100644
--- a/src/Text/Pandoc/Readers/Jira.hs
+++ b/src/Text/Pandoc/Readers/Jira.hs
@@ -106,8 +106,8 @@ rowToBlocksList (Jira.Row cells) =
splitIntoHeaderAndBody :: [Jira.Row] -> (Jira.Row, [Jira.Row])
splitIntoHeaderAndBody [] = (Jira.Row [], [])
splitIntoHeaderAndBody rows@(first@(Jira.Row cells) : rest) =
- let isHeaderCell (Jira.HeaderCell{}) = True
- isHeaderCell (Jira.BodyCell{}) = False
+ let isHeaderCell Jira.HeaderCell{} = True
+ isHeaderCell Jira.BodyCell{} = False
in if all isHeaderCell cells
then (first, rest)
else (Jira.Row [], rows)
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 69aec212f..0bafa0d19 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -1508,7 +1508,7 @@ include name = do
_ | name == "usepackage" -> addExtension f ".sty"
| otherwise -> addExtension f ".tex"
dirs <- (map T.unpack . splitTextBy (==':') . fromMaybe ".") <$> lookupEnv "TEXINPUTS"
- mapM_ (insertIncluded dirs) (map addExt fs)
+ mapM_ (insertIncluded dirs . addExt) fs
return mempty
insertIncluded :: PandocMonad m
@@ -1559,7 +1559,7 @@ macroDef constructor = do
mbenv <- newenvironment
case mbenv of
Nothing -> return ()
- Just (name, macro1, macro2) -> do
+ Just (name, macro1, macro2) ->
guardDisabled Ext_latex_macros <|>
do updateState $ \s -> s{ sMacros =
M.insert name macro1 (sMacros s) }
@@ -1669,7 +1669,7 @@ newenvironment = do
| mtype == "newenvironment" -> do
report $ MacroAlreadyDefined name pos
return Nothing
- | mtype == "provideenvironment" -> do
+ | mtype == "provideenvironment" ->
return Nothing
_ -> return $ Just (name,
Macro ExpandWhenUsed argspecs optarg startcontents,
diff --git a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
index 5630ed868..a6836c3c1 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
@@ -391,7 +391,7 @@ doMacros = do
updateState $ \st -> st{ sExpanded = True }
doMacros' :: PandocMonad m => Int -> [Tok] -> LP m [Tok]
-doMacros' n inp = do
+doMacros' n inp =
case inp of
Tok spos (CtrlSeq "begin") _ : Tok _ Symbol "{" :
Tok _ Word name : Tok _ Symbol "}" : ts
@@ -456,7 +456,7 @@ doMacros' n inp = do
args <- case optarg of
Nothing -> getargs M.empty argspecs
Just o -> do
- x <- option o $ bracketedToks
+ x <- option o bracketedToks
getargs (M.singleton 1 x) $ drop 1 argspecs
rest <- getInput
return (args, rest)
diff --git a/src/Text/Pandoc/Readers/Man.hs b/src/Text/Pandoc/Readers/Man.hs
index 314643621..3955c6069 100644
--- a/src/Text/Pandoc/Readers/Man.hs
+++ b/src/Text/Pandoc/Readers/Man.hs
@@ -91,8 +91,8 @@ parseBlock = choice [ parseList
parseTable :: PandocMonad m => ManParser m Blocks
parseTable = do
modifyState $ \st -> st { tableCellsPlain = True }
- let isTbl (Tbl{}) = True
- isTbl _ = False
+ let isTbl Tbl{} = True
+ isTbl _ = False
Tbl _opts rows pos <- msatisfy isTbl
case rows of
((as,_):_) -> try (do
@@ -287,7 +287,7 @@ parseInline = try $ do
handleInlineMacro :: PandocMonad m
=> T.Text -> [Arg] -> SourcePos -> ManParser m Inlines
-handleInlineMacro mname args _pos = do
+handleInlineMacro mname args _pos =
case mname of
"UR" -> parseLink args
"MT" -> parseEmailLink args
@@ -366,7 +366,7 @@ parseCodeBlock = try $ do
tok <- mtoken
case tok of
ControlLine "PP" _ _ -> return $ Just "" -- .PP sometimes used for blank line
- ControlLine mname args pos -> do
+ ControlLine mname args pos ->
(Just . query getText <$> handleInlineMacro mname args pos) <|>
do report $ SkippedContent ("." <> mname) pos
return Nothing
diff --git a/src/Text/Pandoc/Readers/Metadata.hs b/src/Text/Pandoc/Readers/Metadata.hs
index 76f30e957..701e65980 100644
--- a/src/Text/Pandoc/Readers/Metadata.hs
+++ b/src/Text/Pandoc/Readers/Metadata.hs
@@ -1,9 +1,7 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RelaxedPolyRec #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE TupleSections #-}
{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE ViewPatterns #-}
{- |
Module : Text.Pandoc.Readers.Metadata
Copyright : Copyright (C) 2006-2019 John MacFarlane
@@ -83,9 +81,7 @@ toMetaValue pBlocks x =
[Plain ils] -> MetaInlines ils
[Para ils] -> MetaInlines ils
xs -> MetaBlocks xs
- asBlocks p = do
- p' <- p
- return $ MetaBlocks (B.toList p')
+ asBlocks p = MetaBlocks . B.toList <$> p
checkBoolean :: Text -> Maybe Bool
checkBoolean t =
diff --git a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs
index 6949da9d8..ea4e09403 100644
--- a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs
+++ b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs
@@ -1,9 +1,7 @@
{-# LANGUAGE NoImplicitPrelude #-}
-{-# LANGUAGE Arrows #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PatternGuards #-}
-{-# LANGUAGE RecordWildCards #-}
{- |
Module : Text.Pandoc.Readers.Odt.Generic.XMLConverter
Copyright : Copyright (C) 2015 Martin Linnemann
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index 8aceebc07..6ad50c5bc 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -626,7 +626,7 @@ orgToPandocTable :: OrgTable
-> Inlines
-> Blocks
orgToPandocTable (OrgTable colProps heads lns) caption =
- let totalWidth = if any isJust (map columnRelWidth colProps)
+ let totalWidth = if any (isJust . columnRelWidth) colProps
then Just . sum $ map (fromMaybe 1 . columnRelWidth) colProps
else Nothing
in B.table caption (map (convertColProp totalWidth) colProps) heads lns
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 5e7aaf910..71dee53bc 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -83,8 +83,7 @@ parseTextile = do
let reversedNotes = stateNotes st'
updateState $ \s -> s { stateNotes = reverse reversedNotes }
-- now parse it for real...
- blocks <- parseBlocks
- return $ Pandoc nullMeta (B.toList blocks) -- FIXME
+ Pandoc nullMeta . B.toList <$> parseBlocks -- FIXME
noteMarker :: PandocMonad m => ParserT Text ParserState m Text
noteMarker = skipMany spaceChar >> string "fn" >> T.pack <$> manyTill digit (char '.')