DocBook reader: don't squelch space at end of emphasis element.

Instead, include it after the emphasis.  Closes #6719.

Same fix was made for other inline elements, e.g. strikethrough.
This commit is contained in:
John MacFarlane 2020-10-08 21:27:17 -07:00
parent dd3c4000ff
commit f19286cf12
2 changed files with 24 additions and 16 deletions

View file

@ -26,7 +26,7 @@ import Text.Pandoc.Builder
import Text.Pandoc.Class.PandocMonad (PandocMonad, report) import Text.Pandoc.Class.PandocMonad (PandocMonad, report)
import Text.Pandoc.Options import Text.Pandoc.Options
import Text.Pandoc.Logging (LogMessage(..)) import Text.Pandoc.Logging (LogMessage(..))
import Text.Pandoc.Shared (crFilter, safeRead) import Text.Pandoc.Shared (crFilter, safeRead, extractSpaces)
import Text.TeXMath (readMathML, writeTeX) import Text.TeXMath (readMathML, writeTeX)
import Text.XML.Light import Text.XML.Light
@ -1065,19 +1065,19 @@ parseInline (Elem e) =
let ident = attrValue "id" e let ident = attrValue "id" e
let classes = T.words $ attrValue "class" e let classes = T.words $ attrValue "class" e
if ident /= "" || classes /= [] if ident /= "" || classes /= []
then spanWith (ident,classes,[]) <$> innerInlines then innerInlines (spanWith (ident,classes,[]))
else innerInlines else innerInlines id
"equation" -> equation e displayMath "equation" -> equation e displayMath
"informalequation" -> equation e displayMath "informalequation" -> equation e displayMath
"inlineequation" -> equation e math "inlineequation" -> equation e math
"subscript" -> subscript <$> innerInlines "subscript" -> innerInlines subscript
"superscript" -> superscript <$> innerInlines "superscript" -> innerInlines superscript
"inlinemediaobject" -> getMediaobject e "inlinemediaobject" -> getMediaobject e
"quote" -> do "quote" -> do
qt <- gets dbQuoteType qt <- gets dbQuoteType
let qt' = if qt == SingleQuote then DoubleQuote else SingleQuote let qt' = if qt == SingleQuote then DoubleQuote else SingleQuote
modify $ \st -> st{ dbQuoteType = qt' } modify $ \st -> st{ dbQuoteType = qt' }
contents <- innerInlines contents <- innerInlines id
modify $ \st -> st{ dbQuoteType = qt } modify $ \st -> st{ dbQuoteType = qt }
return $ if qt == SingleQuote return $ if qt == SingleQuote
then singleQuoted contents then singleQuoted contents
@ -1098,7 +1098,7 @@ parseInline (Elem e) =
"replaceable" -> do x <- getInlines e "replaceable" -> do x <- getInlines e
return $ str "<" <> x <> str ">" return $ str "<" <> x <> str ">"
"markup" -> codeWithLang "markup" -> codeWithLang
"wordasword" -> emph <$> innerInlines "wordasword" -> innerInlines emph
"command" -> codeWithLang "command" -> codeWithLang
"varname" -> codeWithLang "varname" -> codeWithLang
"function" -> codeWithLang "function" -> codeWithLang
@ -1126,21 +1126,21 @@ parseInline (Elem e) =
"email" -> return $ link ("mailto:" <> T.pack (strContent e)) "" "email" -> return $ link ("mailto:" <> T.pack (strContent e)) ""
$ str $ T.pack $ strContent e $ str $ T.pack $ strContent e
"uri" -> return $ link (T.pack $ strContent e) "" $ str $ T.pack $ strContent e "uri" -> return $ link (T.pack $ strContent e) "" $ str $ T.pack $ strContent e
"ulink" -> link (attrValue "url" e) "" <$> innerInlines "ulink" -> innerInlines (link (attrValue "url" e) "")
"link" -> do "link" -> do
ils <- innerInlines ils <- innerInlines id
let href = case findAttr (QName "href" (Just "http://www.w3.org/1999/xlink") Nothing) e of let href = case findAttr (QName "href" (Just "http://www.w3.org/1999/xlink") Nothing) e of
Just h -> T.pack h Just h -> T.pack h
_ -> "#" <> attrValue "linkend" e _ -> "#" <> attrValue "linkend" e
let ils' = if ils == mempty then str href else ils let ils' = if ils == mempty then str href else ils
let attr = (attrValue "id" e, T.words $ attrValue "role" e, []) let attr = (attrValue "id" e, T.words $ attrValue "role" e, [])
return $ linkWith attr href "" ils' return $ linkWith attr href "" ils'
"foreignphrase" -> emph <$> innerInlines "foreignphrase" -> innerInlines emph
"emphasis" -> case attrValue "role" e of "emphasis" -> case attrValue "role" e of
"bold" -> strong <$> innerInlines "bold" -> innerInlines strong
"strong" -> strong <$> innerInlines "strong" -> innerInlines strong
"strikethrough" -> strikeout <$> innerInlines "strikethrough" -> innerInlines strikeout
_ -> emph <$> innerInlines _ -> innerInlines emph
"footnote" -> note . mconcat <$> "footnote" -> note . mconcat <$>
mapM parseBlock (elContent e) mapM parseBlock (elContent e)
"title" -> return mempty "title" -> return mempty
@ -1149,12 +1149,12 @@ parseInline (Elem e) =
-- <?asciidor-br?> to in handleInstructions, above. A kludge to -- <?asciidor-br?> to in handleInstructions, above. A kludge to
-- work around xml-light's inability to parse an instruction. -- work around xml-light's inability to parse an instruction.
"br" -> return linebreak "br" -> return linebreak
_ -> skip >> innerInlines _ -> skip >> innerInlines id
where skip = do where skip = do
lift $ report $ IgnoredElement $ T.pack $ qName (elName e) lift $ report $ IgnoredElement $ T.pack $ qName (elName e)
return mempty return mempty
innerInlines = trimInlines . mconcat <$> innerInlines f = extractSpaces f . mconcat <$>
mapM parseInline (elContent e) mapM parseInline (elContent e)
codeWithLang = do codeWithLang = do
let classes' = case attrValue "language" e of let classes' = case attrValue "language" e of

8
test/command/6719.md Normal file
View file

@ -0,0 +1,8 @@
```
% pandoc -f docbook -t native
<para>
<emphasis>emphasized </emphasis>text
</para>
^D
[Para [Emph [Str "emphasized"],Space,Str "text"]]
```