aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/Readers/Org/BlockStarts.hs14
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs4
-rw-r--r--src/Text/Pandoc/Readers/Org/Inlines.hs14
-rw-r--r--test/Tests/Readers/Org/Block.hs32
-rw-r--r--test/Tests/Readers/Org/Directive.hs22
-rw-r--r--test/Tests/Readers/Org/Inline.hs2
-rw-r--r--test/Tests/Readers/Org/Inline/Citation.hs2
-rw-r--r--test/command/10836.md12
8 files changed, 61 insertions, 41 deletions
diff --git a/src/Text/Pandoc/Readers/Org/BlockStarts.hs b/src/Text/Pandoc/Readers/Org/BlockStarts.hs
index c91c7ad46..52fbec889 100644
--- a/src/Text/Pandoc/Readers/Org/BlockStarts.hs
+++ b/src/Text/Pandoc/Readers/Org/BlockStarts.hs
@@ -23,13 +23,14 @@ module Text.Pandoc.Readers.Org.BlockStarts
, endOfBlock
) where
-import Control.Monad (void)
+import Control.Monad (void, guard)
import Data.Text (Text)
import Text.Pandoc.Readers.Org.Parsing
import Text.Pandoc.Definition as Pandoc
import Text.Pandoc.Shared (safeRead)
import Text.Pandoc.Parsing (lowerAlpha, upperAlpha)
import Text.Pandoc.Extensions
+import Text.Pandoc.Readers.LaTeX.Math (inlineEnvironmentNames)
import Data.Functor (($>))
-- | Horizontal Line (five -- dashes or more)
@@ -55,10 +56,13 @@ gridTableStart = try $ skipSpaces <* char '+' <* char '-'
latexEnvStart :: Monad m => OrgParser m Text
-latexEnvStart = try $
- skipSpaces *> string "\\begin{"
- *> latexEnvName
- <* string "}"
+latexEnvStart = try $ do
+ skipSpaces
+ string "\\begin{"
+ name <- latexEnvName
+ char '}'
+ guard $ name `notElem` inlineEnvironmentNames
+ pure name
where
latexEnvName :: Monad m => OrgParser m Text
latexEnvName = try $ mappend <$> many1Char alphaNum <*> option "" (textStr "*")
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index 82cc6d49a..8c2b406b9 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
@@ -25,7 +26,7 @@ import Text.Pandoc.Readers.Org.ParserState
import Text.Pandoc.Readers.Org.Parsing
import Text.Pandoc.Readers.Org.Shared (cleanLinkText, isImageFilename,
originalLang, translateLang, exportsCode)
-
+import Text.Pandoc.Readers.LaTeX.Math (inlineEnvironmentNames)
import Text.Pandoc.Builder (Blocks, Inlines, Many(..))
import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Definition
@@ -796,6 +797,7 @@ rowToContent tbl row =
latexFragment :: PandocMonad m => OrgParser m (F Blocks)
latexFragment = try $ do
envName <- latexEnvStart
+ guard $ envName `notElem` inlineEnvironmentNames
texOpt <- getExportSetting exportWithLatex
let envStart = "\\begin{" <> envName <> "}"
let envEnd = "\\end{" <> envName <> "}"
diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs
index b4d732a74..0f9a36d0c 100644
--- a/src/Text/Pandoc/Readers/Org/Inlines.hs
+++ b/src/Text/Pandoc/Readers/Org/Inlines.hs
@@ -808,16 +808,20 @@ inlineLaTeX = try $ do
allowEntities <- getExportSetting exportWithEntities
ils <- parseAsInlineLaTeX cmd texOpt
maybe mzero returnF $
- parseAsMathMLSym allowEntities cmd `mplus`
- parseAsMath cmd texOpt `mplus`
- ils
+ if "\\begin{" `T.isPrefixOf` cmd
+ then ils
+ else parseAsMathMLSym allowEntities cmd `mplus`
+ parseAsMath cmd texOpt `mplus`
+ ils
where
parseAsInlineLaTeX :: PandocMonad m
=> Text -> TeXExport -> OrgParser m (Maybe Inlines)
parseAsInlineLaTeX cs = \case
- TeXExport -> maybeRight <$> runParserT inlineCommand state "" (toSources cs)
+ TeXExport -> maybeRight <$> runParserT
+ (B.rawInline "latex" . snd <$> withRaw inlineCommand)
+ state "" (toSources cs)
TeXIgnore -> return (Just mempty)
- TeXVerbatim -> return (Just $ B.str cs)
+ TeXVerbatim -> return (Just $ B.text cs)
parseAsMathMLSym :: Bool -> Text -> Maybe Inlines
parseAsMathMLSym allowEntities cs = do
diff --git a/test/Tests/Readers/Org/Block.hs b/test/Tests/Readers/Org/Block.hs
index 0b47b90b3..2bb658213 100644
--- a/test/Tests/Readers/Org/Block.hs
+++ b/test/Tests/Readers/Org/Block.hs
@@ -169,26 +169,24 @@ tests =
rawBlock "html" "<samp>Hello, World!</samp>\n"
, "LaTeX fragment" =:
- T.unlines [ "\\begin{equation}"
- , "X_i = \\begin{cases}"
- , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\"
- , " C_{\\alpha(i)} & \\text{otherwise}"
- , " \\end{cases}"
- , "\\end{equation}"
- ] =?>
- rawBlock "latex"
- (T.unlines [ "\\begin{equation}"
- , "X_i = \\begin{cases}"
- , " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) =" <>
- " \\alpha(i)\\\\"
- , " C_{\\alpha(i)} & \\text{otherwise}"
- , " \\end{cases}"
- , "\\end{equation}"
- ])
+ "\\begin{equation}\n\
+ \X_i = \\begin{cases}\n\
+ \ G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\\n\
+ \ C_{\\alpha(i)} & \\text{otherwise}\n\
+ \ \\end{cases}\n\
+ \\\end{equation}"
+ =?>
+ para (rawInline "latex"
+ "\\begin{equation}\n\
+ \X_i = \\begin{cases}\n\
+ \ G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\\n\
+ \ C_{\\alpha(i)} & \\text{otherwise}\n\
+ \ \\end{cases}\n\
+ \\\end{equation}")
, "One-line LaTeX fragment" =:
"\\begin{equation} 2 + 3 \\end{equation}" =?>
- rawBlock "latex" "\\begin{equation} 2 + 3 \\end{equation}\n"
+ para (rawInline "latex" "\\begin{equation} 2 + 3 \\end{equation}")
, "LaTeX fragment with more arguments" =:
T.unlines [ "\\begin{tikzcd}[ampersand replacement=\\&]"
diff --git a/test/Tests/Readers/Org/Directive.hs b/test/Tests/Readers/Org/Directive.hs
index db997afa8..1f80e8607 100644
--- a/test/Tests/Readers/Org/Directive.hs
+++ b/test/Tests/Readers/Org/Directive.hs
@@ -188,7 +188,7 @@ tests =
T.unlines [ "#+OPTIONS: tex:t"
, "Hello \\emph{Name}"
] =?>
- para ("Hello" <> space <> emph "Name")
+ para ("Hello" <> space <> rawInline "latex" "\\emph{Name}")
, "Alpha" =:
T.unlines [ "#+OPTIONS: tex:t"
@@ -197,15 +197,15 @@ tests =
para "α"
, "equation environment" =:
- T.unlines [ "#+OPTIONS: tex:t"
- , "\\begin{equation}"
- , "f(x) = x^2"
- , "\\end{equation}"
- ] =?>
- rawBlock "latex" (T.unlines [ "\\begin{equation}"
- , "f(x) = x^2"
- , "\\end{equation}"
- ])
+ "#+OPTIONS: tex:t\n\
+ \\\begin{equation}\n\
+ \f(x) = x^2\n\
+ \\\end{equation}"
+ =?>
+ para (rawInline "latex"
+ "\\begin{equation}\n\
+ \f(x) = x^2\n\
+ \\\end{equation}")
]
, testGroup "Ignore LaTeX fragments"
@@ -227,7 +227,7 @@ tests =
, "f(x) = x^2"
, "\\end{equation}"
] =?>
- (mempty :: Blocks)
+ (para mempty)
]
, testGroup "Verbatim LaTeX"
diff --git a/test/Tests/Readers/Org/Inline.hs b/test/Tests/Readers/Org/Inline.hs
index 21f42858c..00956e1ce 100644
--- a/test/Tests/Readers/Org/Inline.hs
+++ b/test/Tests/Readers/Org/Inline.hs
@@ -342,7 +342,7 @@ tests =
, "Inline LaTeX command with spaces" =:
"\\emph{Emphasis mine}" =?>
- para (emph "Emphasis mine")
+ para (rawInline "latex" "\\emph{Emphasis mine}")
, "Inline math symbols" =:
"\\tau \\oplus \\alpha" =?>
diff --git a/test/Tests/Readers/Org/Inline/Citation.hs b/test/Tests/Readers/Org/Inline/Citation.hs
index ed60a16e9..3849ae3e7 100644
--- a/test/Tests/Readers/Org/Inline/Citation.hs
+++ b/test/Tests/Readers/Org/Inline/Citation.hs
@@ -208,6 +208,6 @@ tests =
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0}
- in (para . cite [citation] $ rawInline "latex" "\\cite{Coffee}")
+ in (para $ rawInline "latex" "\\cite{Coffee}")
]
diff --git a/test/command/10836.md b/test/command/10836.md
new file mode 100644
index 000000000..864361b5c
--- /dev/null
+++ b/test/command/10836.md
@@ -0,0 +1,12 @@
+```
+% pandoc -f org -t latex
+Some equation here
+\begin{equation}
+x = y
+\end{equation}
+where $x$ is something important.
+^D
+Some equation here \begin{equation}
+x = y
+\end{equation} where \(x\) is something important.
+```