Use formatCode from #7525 in HTML and MediaWiki (#8162)

Move formatting from inside inline code elements to the outside in order
to retain formatting.
This commit is contained in:
Elliot Bobrow 2022-07-06 13:10:24 -07:00 committed by GitHub
parent befa9d1301
commit 7fdc01ac0d
No known key found for this signature in database
GPG key ID: 4AEE18F83AFDEB23
5 changed files with 42 additions and 19 deletions

View file

@ -63,7 +63,7 @@ import Text.Pandoc.Options (
import Text.Pandoc.Parsing hiding ((<|>)) import Text.Pandoc.Parsing hiding ((<|>))
import Text.Pandoc.Shared ( import Text.Pandoc.Shared (
addMetaField, blocksToInlines', escapeURI, extractSpaces, addMetaField, blocksToInlines', escapeURI, extractSpaces,
htmlSpanLikeElements, renderTags', safeRead, tshow) htmlSpanLikeElements, renderTags', safeRead, tshow, formatCode)
import Text.Pandoc.Walk import Text.Pandoc.Walk
import Text.Parsec.Error import Text.Parsec.Error
import Text.TeXMath (readMathML, writeTeX) import Text.TeXMath (readMathML, writeTeX)
@ -786,18 +786,20 @@ pSvg = do
pCodeWithClass :: PandocMonad m => Text -> Text -> TagParser m Inlines pCodeWithClass :: PandocMonad m => Text -> Text -> TagParser m Inlines
pCodeWithClass name class' = try $ do pCodeWithClass name class' = try $ do
TagOpen open attr' <- pSatisfy $ tagOpen (== name) (const True) TagOpen open attr' <- pSatisfy $ tagOpen (== name) (const True)
result <- manyTill pAny (pCloses open)
let (ids,cs,kvs) = toAttr attr' let (ids,cs,kvs) = toAttr attr'
cs' = class' : cs cs' = class' : cs
return . B.codeWith (ids,cs',kvs) . code open (ids,cs',kvs)
T.unwords . T.lines . innerText $ result
pCode :: PandocMonad m => TagParser m Inlines pCode :: PandocMonad m => TagParser m Inlines
pCode = try $ do pCode = try $ do
(TagOpen open attr') <- pSatisfy $ tagOpen (`elem` ["code","tt"]) (const True) (TagOpen open attr') <- pSatisfy $ tagOpen (`elem` ["code","tt"]) (const True)
let attr = toAttr attr' let attr = toAttr attr'
result <- manyTill pAny (pCloses open) code open attr
return $ B.codeWith attr $ T.unwords $ T.lines $ innerText result
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 -- https://developer.mozilla.org/en-US/docs/Web/HTML/Element/bdo
-- Bidirectional Text Override -- Bidirectional Text Override

View file

@ -37,8 +37,7 @@ import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (nested, tableCaption) import Text.Pandoc.Parsing hiding (nested, tableCaption)
import Text.Pandoc.Readers.HTML (htmlTag, isBlockTag, isCommentTag) import Text.Pandoc.Readers.HTML (htmlTag, isBlockTag, isCommentTag)
import Text.Pandoc.Shared (safeRead, stringify, stripTrailingNewlines, import Text.Pandoc.Shared (safeRead, stringify, stripTrailingNewlines,
trim, splitTextBy, tshow) trim, splitTextBy, tshow, formatCode)
import Text.Pandoc.Walk (walk)
import Text.Pandoc.XML (fromEntities) import Text.Pandoc.XML (fromEntities)
-- | Read mediawiki from an input string and return a Pandoc document. -- | Read mediawiki from an input string and return a Pandoc document.
@ -392,14 +391,7 @@ preformatted = try $ do
else return $ B.para $ encode contents else return $ B.para $ encode contents
encode :: Inlines -> Inlines encode :: Inlines -> Inlines
encode = B.fromList . normalizeCode . B.toList . walk strToCode encode = formatCode nullAttr
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
header :: PandocMonad m => MWParser m Blocks header :: PandocMonad m => MWParser m Blocks
header = try $ do header = try $ do

View file

@ -17,3 +17,17 @@
] ]
] ]
``` ```
```
% pandoc -f html -t native
<code><b>hi</b></code>
^D
[ Plain [ Strong [ Code ( "" , [] , [] ) "hi" ] ] ]
```
```
% pandoc -f mediawiki -t native
<code>''hey''</code>
^D
[ Para [ Emph [ Code ( "" , [] , [] ) "hey" ] ] ]
```

View file

@ -1505,7 +1505,12 @@
, Space , Space
, Str "the" , Str "the"
, Space , Space
, Code ( "" , [] , [] ) "epub:switch" , Link
( "" , [] , [] )
[ Code ( "" , [] , [] ) "epub:switch" ]
( "http://idpf.org/epub/30/spec/epub30-contentdocs.html#sec-xhtml-content-switch"
, ""
)
, Space , Space
, Str "element" , Str "element"
, Space , Space
@ -1615,7 +1620,12 @@
, Space , Space
, Str "an" , Str "an"
, Space , Space
, Code ( "" , [] , [] ) "epub:case" , Link
( "" , [] , [] )
[ Code ( "" , [] , [] ) "epub:case" ]
( "http://idpf.org/epub/30/spec/epub30-contentdocs.html#sec-xhtml-epub-case"
, ""
)
, Space , Space
, Str "element." , Str "element."
] ]

View file

@ -605,7 +605,12 @@
, Space , Space
, Str "the" , Str "the"
, Space , Space
, Code ( "" , [] , [] ) "CSS Multi-Column Layout" , Link
( "" , [] , [] )
[ Code ( "" , [] , [] ) "CSS Multi-Column Layout" ]
( "http://idpf.org/epub/30/spec/epub30-contentdocs.html#sec-css-multi-column"
, ""
)
, Space , Space
, Str "properties" , Str "properties"
, Space , Space