aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorElliot Bobrow <[email protected]>2022-07-06 13:10:24 -0700
committerGitHub <[email protected]>2022-07-06 22:10:24 +0200
commit7fdc01ac0d91a037b48847939b762654174b4125 (patch)
tree427d3c4cfc26e67e6a72ead286f75ed1738cfe5f /src
parentbefa9d130181ff99d155a6df454c40fba0d9736a (diff)
Use `formatCode` from #7525 in HTML and MediaWiki (#8162)
Move formatting from inside inline code elements to the outside in order to retain formatting.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs14
-rw-r--r--src/Text/Pandoc/Readers/MediaWiki.hs12
2 files changed, 10 insertions, 16 deletions
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 47b6af193..dd0e54c27 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -63,7 +63,7 @@ import Text.Pandoc.Options (
import Text.Pandoc.Parsing hiding ((<|>))
import Text.Pandoc.Shared (
addMetaField, blocksToInlines', escapeURI, extractSpaces,
- htmlSpanLikeElements, renderTags', safeRead, tshow)
+ htmlSpanLikeElements, renderTags', safeRead, tshow, formatCode)
import Text.Pandoc.Walk
import Text.Parsec.Error
import Text.TeXMath (readMathML, writeTeX)
@@ -786,18 +786,20 @@ pSvg = do
pCodeWithClass :: PandocMonad m => Text -> Text -> TagParser m Inlines
pCodeWithClass name class' = try $ do
TagOpen open attr' <- pSatisfy $ tagOpen (== name) (const True)
- result <- manyTill pAny (pCloses open)
let (ids,cs,kvs) = toAttr attr'
cs' = class' : cs
- return . B.codeWith (ids,cs',kvs) .
- T.unwords . T.lines . innerText $ result
+ code open (ids,cs',kvs)
pCode :: PandocMonad m => TagParser m Inlines
pCode = try $ do
(TagOpen open attr') <- pSatisfy $ tagOpen (`elem` ["code","tt"]) (const True)
let attr = toAttr attr'
- result <- manyTill pAny (pCloses open)
- return $ B.codeWith attr $ T.unwords $ T.lines $ innerText result
+ code open attr
+
+code :: PandocMonad m => Text -> Attr -> TagParser m Inlines
+code open attr = do
+ result <- mconcat <$> manyTill inline (pCloses open)
+ return $ formatCode attr result
-- https://developer.mozilla.org/en-US/docs/Web/HTML/Element/bdo
-- Bidirectional Text Override
diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs
index 7a406ec4b..2dc289f18 100644
--- a/src/Text/Pandoc/Readers/MediaWiki.hs
+++ b/src/Text/Pandoc/Readers/MediaWiki.hs
@@ -37,8 +37,7 @@ import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (nested, tableCaption)
import Text.Pandoc.Readers.HTML (htmlTag, isBlockTag, isCommentTag)
import Text.Pandoc.Shared (safeRead, stringify, stripTrailingNewlines,
- trim, splitTextBy, tshow)
-import Text.Pandoc.Walk (walk)
+ trim, splitTextBy, tshow, formatCode)
import Text.Pandoc.XML (fromEntities)
-- | Read mediawiki from an input string and return a Pandoc document.
@@ -392,14 +391,7 @@ preformatted = try $ do
else return $ B.para $ encode contents
encode :: Inlines -> Inlines
-encode = B.fromList . normalizeCode . B.toList . walk strToCode
- where strToCode (Str s) = Code ("",[],[]) s
- strToCode Space = Code ("",[],[]) " "
- strToCode x = x
- normalizeCode [] = []
- normalizeCode (Code a1 x : Code a2 y : zs) | a1 == a2 =
- normalizeCode $ Code a1 (x <> y) : zs
- normalizeCode (x:xs) = x : normalizeCode xs
+encode = formatCode nullAttr
header :: PandocMonad m => MWParser m Blocks
header = try $ do