diff options
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r-- | src/Text/Pandoc/Readers/CommonMark.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/DocBook.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Docx.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Docx/Parse.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/DokuWiki.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/JATS.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Man.hs | 26 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/RST.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Vimwiki.hs | 18 |
9 files changed, 31 insertions, 32 deletions
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 |