Move formatting from inside inline code elements to the outside in order to retain formatting.
This commit is contained in:
parent
befa9d1301
commit
7fdc01ac0d
5 changed files with 42 additions and 19 deletions
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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" ] ] ]
|
||||
```
|
||||
|
|
|
@ -1505,7 +1505,12 @@
|
|||
, Space
|
||||
, Str "the"
|
||||
, Space
|
||||
, Code ( "" , [] , [] ) "epub:switch"
|
||||
, Link
|
||||
( "" , [] , [] )
|
||||
[ Code ( "" , [] , [] ) "epub:switch" ]
|
||||
( "http://idpf.org/epub/30/spec/epub30-contentdocs.html#sec-xhtml-content-switch"
|
||||
, ""
|
||||
)
|
||||
, Space
|
||||
, Str "element"
|
||||
, Space
|
||||
|
@ -1615,7 +1620,12 @@
|
|||
, Space
|
||||
, Str "an"
|
||||
, Space
|
||||
, Code ( "" , [] , [] ) "epub:case"
|
||||
, Link
|
||||
( "" , [] , [] )
|
||||
[ Code ( "" , [] , [] ) "epub:case" ]
|
||||
( "http://idpf.org/epub/30/spec/epub30-contentdocs.html#sec-xhtml-epub-case"
|
||||
, ""
|
||||
)
|
||||
, Space
|
||||
, Str "element."
|
||||
]
|
||||
|
|
|
@ -605,7 +605,12 @@
|
|||
, Space
|
||||
, Str "the"
|
||||
, 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
|
||||
, Str "properties"
|
||||
, Space
|
||||
|
|
Loading…
Reference in a new issue