Merge pull request #1706 from tarleb/org-symbol-entities

Org reader: parse LaTeX-style MathML entities
This commit is contained in:
John MacFarlane 2014-10-21 10:11:19 -07:00
commit 78bdc08de7
2 changed files with 20 additions and 1 deletions

View file

@ -42,6 +42,7 @@ import Text.Pandoc.Parsing hiding ( F, unF, askF, asksF, runF
import Text.Pandoc.Readers.LaTeX (inlineCommand, rawLaTeXInline) import Text.Pandoc.Readers.LaTeX (inlineCommand, rawLaTeXInline)
import Text.Pandoc.Shared (compactify', compactify'DL) import Text.Pandoc.Shared (compactify', compactify'DL)
import Text.TeXMath (readTeX, writePandoc, DisplayType(..)) import Text.TeXMath (readTeX, writePandoc, DisplayType(..))
import qualified Text.TeXMath.Readers.MathML.EntityMap as MathMLEntityMap
import Control.Applicative ( Applicative, pure import Control.Applicative ( Applicative, pure
, (<$>), (<$), (<*>), (<*), (*>) ) , (<$>), (<$), (<*>), (<*), (*>) )
@ -1431,7 +1432,8 @@ simpleSubOrSuperString = try $
inlineLaTeX :: OrgParser (F Inlines) inlineLaTeX :: OrgParser (F Inlines)
inlineLaTeX = try $ do inlineLaTeX = try $ do
cmd <- inlineLaTeXCommand cmd <- inlineLaTeXCommand
maybe mzero returnF $ parseAsMath cmd `mplus` parseAsInlineLaTeX cmd maybe mzero returnF $
parseAsMath cmd `mplus` parseAsMathMLSym cmd `mplus` parseAsInlineLaTeX cmd
where where
parseAsMath :: String -> Maybe Inlines parseAsMath :: String -> Maybe Inlines
parseAsMath cs = B.fromList <$> texMathToPandoc cs parseAsMath cs = B.fromList <$> texMathToPandoc cs
@ -1439,6 +1441,11 @@ inlineLaTeX = try $ do
parseAsInlineLaTeX :: String -> Maybe Inlines parseAsInlineLaTeX :: String -> Maybe Inlines
parseAsInlineLaTeX cs = maybeRight $ runParser inlineCommand state "" cs parseAsInlineLaTeX cs = maybeRight $ runParser inlineCommand state "" cs
parseAsMathMLSym :: String -> Maybe Inlines
parseAsMathMLSym cs = B.str <$> MathMLEntityMap.getUnicode (clean cs)
-- dropWhileEnd would be nice here, but it's not available before base 4.5
where clean = reverse . dropWhile (`elem` "{}") . reverse . drop 1
state :: ParserState state :: ParserState
state = def{ stateOptions = def{ readerParseRaw = True }} state = def{ stateOptions = def{ readerParseRaw = True }}

View file

@ -276,6 +276,18 @@ tests =
"\\notacommand{foo}" =?> "\\notacommand{foo}" =?>
para (rawInline "latex" "\\notacommand{foo}") para (rawInline "latex" "\\notacommand{foo}")
, "MathML symbol in LaTeX-style" =:
"There is a hackerspace in Lübeck, Germany, called nbsp (unicode symbol: '\\nbsp')." =?>
para ("There is a hackerspace in Lübeck, Germany, called nbsp (unicode symbol: ' ').")
, "MathML symbol in LaTeX-style, including braces" =:
"\\Aacute{}stor" =?>
para "Ástor"
, "MathML copy sign" =:
"\\copy" =?>
para "©"
, "LaTeX citation" =: , "LaTeX citation" =:
"\\cite{Coffee}" =?> "\\cite{Coffee}" =?>
let citation = Citation let citation = Citation