aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Readers/Org.hs12
-rw-r--r--tests/Tests/Readers/Org.hs4
2 files changed, 11 insertions, 5 deletions
diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs
index 5e98be31d..a7987475a 100644
--- a/src/Text/Pandoc/Readers/Org.hs
+++ b/src/Text/Pandoc/Readers/Org.hs
@@ -49,7 +49,7 @@ import qualified Text.TeXMath.Readers.MathML.EntityMap as MathMLEntityMap
import Control.Arrow (first)
import Control.Monad (foldM, guard, liftM, liftM2, mplus, mzero, when)
import Control.Monad.Reader (Reader, runReader, ask, asks, local)
-import Data.Char (isAlphaNum, toLower)
+import Data.Char (isAlphaNum, isSpace, toLower)
import Data.Default
import Data.List (intersperse, isPrefixOf, isSuffixOf)
import qualified Data.Map as M
@@ -1587,8 +1587,8 @@ inlineLaTeX = try $ do
state :: ParserState
state = def{ stateOptions = def{ readerParseRaw = True }}
- texMathToPandoc inp = (maybeRight $ readTeX inp) >>=
- writePandoc DisplayInline
+ texMathToPandoc :: String -> Maybe [Inline]
+ texMathToPandoc cs = (maybeRight $ readTeX cs) >>= writePandoc DisplayInline
maybeRight :: Either a b -> Maybe b
maybeRight = either (const Nothing) Just
@@ -1598,9 +1598,11 @@ inlineLaTeXCommand = try $ do
rest <- getInput
case runParser rawLaTeXInline def "source" rest of
Right (RawInline _ cs) -> do
- let len = length cs
+ -- drop any trailing whitespace, those should not be part of the command
+ let cmdNoSpc = takeWhile (not . isSpace) $ cs
+ let len = length cmdNoSpc
count len anyChar
- return cs
+ return cmdNoSpc
_ -> mzero
smart :: OrgParser (F Inlines)
diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs
index bb9b37d13..6112055ba 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -328,6 +328,10 @@ tests =
"\\copy" =?>
para "©"
+ , "MathML symbols, space separated" =:
+ "\\ForAll \\Auml" =?>
+ para "∀ Ä"
+
, "LaTeX citation" =:
"\\cite{Coffee}" =?>
let citation = Citation