aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJoe Hermaszewski <github@sub.monoid.al>2018-04-27 03:12:28 +0800
committerJohn MacFarlane <jgm@berkeley.edu>2018-04-26 12:12:28 -0700
commitcfa4eee28bc3d6521f806bc37c937e9615d15588 (patch)
treedc366824308eea59298a83abf5cb71b9ff974dda
parent00e3c5c8c1af3cb288ea9b6a4129a6ac029df3cb (diff)
downloadpandoc-cfa4eee28bc3d6521f806bc37c937e9615d15588.tar.gz
DocBook Reader: Read Latex math as output by asciidoctor (#4569)
-rw-r--r--src/Text/Pandoc/Readers/DocBook.hs59
1 files changed, 48 insertions, 11 deletions
diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs
index 809018697..3d48c7ee8 100644
--- a/src/Text/Pandoc/Readers/DocBook.hs
+++ b/src/Text/Pandoc/Readers/DocBook.hs
@@ -265,7 +265,7 @@ List of all DocBook tags, with [x] indicating implemented,
[ ] manvolnum - A reference volume number
[x] markup - A string of formatting markup in text that is to be
represented literally
-[ ] mathphrase - A mathematical phrase, an expression that can be represented
+[x] mathphrase - A mathematical phrase, an expression that can be represented
with ordinary text and a small amount of markup
[ ] medialabel - A name that identifies the physical medium on which some
information resides
@@ -727,6 +727,8 @@ parseBlock (Elem e) =
"bibliodiv" -> sect 1
"biblioentry" -> parseMixed para (elContent e)
"bibliomixed" -> parseMixed para (elContent e)
+ "equation" -> para <$> equation e displayMath
+ "informalequation" -> para <$> equation e displayMath
"glosssee" -> para . (\ils -> text "See " <> ils <> str ".")
<$> getInlines e
"glossseealso" -> para . (\ils -> text "See also " <> ils <> str ".")
@@ -953,9 +955,9 @@ parseInline (CRef ref) =
return $ maybe (text $ map toUpper ref) text $ lookupEntity ref
parseInline (Elem e) =
case qName (elName e) of
- "equation" -> equation displayMath
- "informalequation" -> equation displayMath
- "inlineequation" -> equation math
+ "equation" -> equation e displayMath
+ "informalequation" -> equation e displayMath
+ "inlineequation" -> equation e math
"subscript" -> subscript <$> innerInlines
"superscript" -> superscript <$> innerInlines
"inlinemediaobject" -> getMediaobject e
@@ -1034,13 +1036,6 @@ parseInline (Elem e) =
_ -> innerInlines
where innerInlines = (trimInlines . mconcat) <$>
mapM parseInline (elContent e)
- equation constructor = return $ mconcat $
- map (constructor . writeTeX)
- $ rights
- $ map (readMathML . showElement . everywhere (mkT removePrefix))
- $ filterChildren (\x -> qName (elName x) == "math" &&
- qPrefix (elName x) == Just "mml") e
- removePrefix elname = elname { qPrefix = Nothing }
codeWithLang = do
let classes' = case attrValue "language" e of
"" -> []
@@ -1091,3 +1086,45 @@ parseInline (Elem e) =
xrefLabel = attrValue "xreflabel" el
descendantContent name = maybe "???" strContent
. filterElementName (\n -> qName n == name)
+
+-- | Extract a math equation from an element
+--
+-- asciidoc can generate Latex math in CDATA sections.
+--
+-- Note that if some MathML can't be parsed it is silently ignored!
+equation
+ :: Monad m
+ => Element
+ -- ^ The element from which to extract a mathematical equation
+ -> (String -> Inlines)
+ -- ^ A constructor for some Inlines, taking the TeX code as input
+ -> m Inlines
+equation e constructor =
+ return $ mconcat $ map constructor $ mathMLEquations ++ latexEquations
+ where
+ mathMLEquations :: [String]
+ mathMLEquations = map writeTeX $ rights $ readMath
+ (\x -> qName (elName x) == "math" && qPrefix (elName x) == Just "mml")
+ (readMathML . showElement)
+
+ latexEquations :: [String]
+ latexEquations = readMath (\x -> qName (elName x) == "mathphrase")
+ (concat . fmap showVerbatimCData . elContent)
+
+ readMath :: (Element -> Bool) -> (Element -> b) -> [b]
+ readMath childPredicate fromElement =
+ ( map (fromElement . everywhere (mkT removePrefix))
+ $ filterChildren childPredicate e
+ )
+
+-- | Get the actual text stored in a verbatim CData block. 'showContent'
+-- returns the text still surrounded by the [[CDATA]] tags.
+--
+-- Returns 'showContent' if this is not a verbatim CData
+showVerbatimCData :: Content -> String
+showVerbatimCData (Text (CData CDataVerbatim d _)) = d
+showVerbatimCData c = showContent c
+
+-- | Set the prefix of a name to 'Nothing'
+removePrefix :: QName -> QName
+removePrefix elname = elname { qPrefix = Nothing }