From 3238a2f9191b83864abd682261634a603ec89056 Mon Sep 17 00:00:00 2001
From: Albert Krewinkel <tarleb@moltkeplatz.de>
Date: Tue, 20 May 2014 22:29:21 +0200
Subject: [PATCH] Org reader: support for inline LaTeX

Inline LaTeX is now accepted and parsed by the org-mode reader.  Both,
math symbols (like \tau) and LaTeX commands (like \cite{Coffee}), can be
used without any further escaping.
---
 src/Text/Pandoc/Readers/LaTeX.hs |  1 +
 src/Text/Pandoc/Readers/Org.hs   | 32 +++++++++++++++++++++++++++++++-
 tests/Tests/Readers/Org.hs       | 27 +++++++++++++++++++++++++++
 3 files changed, 59 insertions(+), 1 deletion(-)

diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 6f870318f..7fc587882 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -31,6 +31,7 @@ Conversion of LaTeX to 'Pandoc' document.
 module Text.Pandoc.Readers.LaTeX ( readLaTeX,
                                    rawLaTeXInline,
                                    rawLaTeXBlock,
+                                   inlineCommand,
                                    handleIncludes
                                  ) where
 
diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs
index 86dda2732..c3ea8d7c2 100644
--- a/src/Text/Pandoc/Readers/Org.hs
+++ b/src/Text/Pandoc/Readers/Org.hs
@@ -39,12 +39,15 @@ import           Text.Pandoc.Parsing hiding ( F, unF, askF, asksF, runF
                                             , newline, orderedListMarker
                                             , parseFromString
                                             , updateLastStrPos )
+import           Text.Pandoc.Readers.LaTeX (inlineCommand, rawLaTeXInline)
 import           Text.Pandoc.Shared (compactify', compactify'DL)
+import           Text.Parsec.Pos (updatePosString)
+import           Text.TeXMath (texMathToPandoc, DisplayType(..))
 
 import           Control.Applicative ( Applicative, pure
                                      , (<$>), (<$), (<*>), (<*), (*>), (<**>) )
 import           Control.Arrow (first)
-import           Control.Monad (foldM, guard, liftM, liftM2, mzero, when)
+import           Control.Monad (foldM, guard, liftM, liftM2, mplus, mzero, when)
 import           Control.Monad.Reader (Reader, runReader, ask, asks)
 import           Data.Char (isAlphaNum, toLower)
 import           Data.Default
@@ -886,6 +889,7 @@ inline =
          , verbatim
          , subscript
          , superscript
+         , inlineLaTeX
          , symbol
          ] <* (guard =<< newlinesCountWithinLimits)
   <?> "inline"
@@ -1351,3 +1355,29 @@ simpleSubOrSuperString = try $
          , mappend <$> option [] ((:[]) <$> oneOf "+-")
                    <*> many1 alphaNum
          ]
+
+inlineLaTeX :: OrgParser (F Inlines)
+inlineLaTeX = try $ do
+  cmd <- inlineLaTeXCommand
+  maybe mzero returnF $ parseAsMath cmd `mplus` parseAsInlineLaTeX cmd
+ where
+   parseAsMath :: String -> Maybe Inlines
+   parseAsMath cs = maybeRight $ B.fromList <$> texMathToPandoc DisplayInline cs
+
+   parseAsInlineLaTeX :: String -> Maybe Inlines
+   parseAsInlineLaTeX cs = maybeRight $ runParser inlineCommand state "" cs
+
+   state :: ParserState
+   state = def{ stateOptions = def{ readerParseRaw = True }}
+
+maybeRight :: Either a b -> Maybe b
+maybeRight = either (const Nothing) Just
+
+inlineLaTeXCommand :: OrgParser String
+inlineLaTeXCommand = try $ do
+  rest <- getInput
+  pos <- getPosition
+  case runParser rawLaTeXInline def "source" rest of
+    Right (RawInline _ cs) -> cs <$ (setInput $ drop (length cs) rest)
+                                 <* (setPosition $ updatePosString pos cs)
+    _ -> mzero
diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs
index ca97ba348..4ed77887f 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -247,6 +247,33 @@ tests =
                          , citationNoteNum = 0
                          , citationHash = 0}
           in (para $ cite [citation] "[see @item1 p. 34-35]")
+
+      , "Inline LaTeX symbol" =:
+          "\\dots" =?>
+          para "…"
+
+      , "Inline LaTeX command" =:
+          "\\textit{Emphasised}" =?>
+          para (emph "Emphasised")
+
+      , "Inline LaTeX math symbol" =:
+          "\\tau" =?>
+          para (emph "τ")
+
+      , "Unknown inline LaTeX command" =:
+          "\\notacommand{foo}" =?>
+          para (rawInline "latex" "\\notacommand{foo}")
+
+      , "LaTeX citation" =:
+          "\\cite{Coffee}" =?>
+          let citation = Citation
+                         { citationId = "Coffee"
+                         , citationPrefix = []
+                         , citationSuffix = []
+                         , citationMode = AuthorInText
+                         , citationNoteNum = 0
+                         , citationHash = 0}
+          in (para . cite [citation] $ rawInline "latex" "\\cite{Coffee}")
       ]
 
   , testGroup "Meta Information" $