Skip to content

Commit 60c147d

Browse files
committed
Org reader: change handling of inline TeX.
Previously inline TeX was handled in a way that was different from org's own export, and that could lead to information loss. This was particularly noticeable for inline math environments such as `equation`. Previously, an `equation` environment starting at the beginning of a line would create a raw block, splitting up the paragraph containing it (see #10836). On the other hand, an `equation` environment not at the beginning of a line would be turned into regular inline elements representing the math. (This would cause the equation number to go missing and in some cases degrade the math formatting.) Now, we parse all of these as raw "latex" inlines, which will be omitted when converting to formats other than LaTeX (and other formats like pandoc's Markdown that allow raw LaTex). Closes #10836.
1 parent 1ce62c9 commit 60c147d

File tree

7 files changed

+53
-36
lines changed

7 files changed

+53
-36
lines changed

src/Text/Pandoc/Readers/Org/Blocks.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE ScopedTypeVariables #-}
12
{-# LANGUAGE FlexibleContexts #-}
23
{-# LANGUAGE LambdaCase #-}
34
{-# LANGUAGE OverloadedStrings #-}
@@ -25,7 +26,7 @@ import Text.Pandoc.Readers.Org.ParserState
2526
import Text.Pandoc.Readers.Org.Parsing
2627
import Text.Pandoc.Readers.Org.Shared (cleanLinkText, isImageFilename,
2728
originalLang, translateLang, exportsCode)
28-
29+
import Text.Pandoc.Readers.LaTeX.Math (inlineEnvironmentNames)
2930
import Text.Pandoc.Builder (Blocks, Inlines, Many(..))
3031
import Text.Pandoc.Class.PandocMonad (PandocMonad)
3132
import Text.Pandoc.Definition
@@ -796,6 +797,7 @@ rowToContent tbl row =
796797
latexFragment :: PandocMonad m => OrgParser m (F Blocks)
797798
latexFragment = try $ do
798799
envName <- latexEnvStart
800+
guard $ envName `notElem` inlineEnvironmentNames
799801
texOpt <- getExportSetting exportWithLatex
800802
let envStart = "\\begin{" <> envName <> "}"
801803
let envEnd = "\\end{" <> envName <> "}"

src/Text/Pandoc/Readers/Org/Inlines.hs

Lines changed: 9 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -808,16 +808,20 @@ inlineLaTeX = try $ do
808808
allowEntities <- getExportSetting exportWithEntities
809809
ils <- parseAsInlineLaTeX cmd texOpt
810810
maybe mzero returnF $
811-
parseAsMathMLSym allowEntities cmd `mplus`
812-
parseAsMath cmd texOpt `mplus`
813-
ils
811+
if "\\begin{" `T.isPrefixOf` cmd
812+
then ils
813+
else parseAsMathMLSym allowEntities cmd `mplus`
814+
parseAsMath cmd texOpt `mplus`
815+
ils
814816
where
815817
parseAsInlineLaTeX :: PandocMonad m
816818
=> Text -> TeXExport -> OrgParser m (Maybe Inlines)
817819
parseAsInlineLaTeX cs = \case
818-
TeXExport -> maybeRight <$> runParserT inlineCommand state "" (toSources cs)
820+
TeXExport -> maybeRight <$> runParserT
821+
(B.rawInline "latex" . snd <$> withRaw inlineCommand)
822+
state "" (toSources cs)
819823
TeXIgnore -> return (Just mempty)
820-
TeXVerbatim -> return (Just $ B.str cs)
824+
TeXVerbatim -> return (Just $ B.text cs)
821825

822826
parseAsMathMLSym :: Bool -> Text -> Maybe Inlines
823827
parseAsMathMLSym allowEntities cs = do

test/Tests/Readers/Org/Block.hs

Lines changed: 15 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -169,26 +169,24 @@ tests =
169169
rawBlock "html" "<samp>Hello, World!</samp>\n"
170170

171171
, "LaTeX fragment" =:
172-
T.unlines [ "\\begin{equation}"
173-
, "X_i = \\begin{cases}"
174-
, " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\"
175-
, " C_{\\alpha(i)} & \\text{otherwise}"
176-
, " \\end{cases}"
177-
, "\\end{equation}"
178-
] =?>
179-
rawBlock "latex"
180-
(T.unlines [ "\\begin{equation}"
181-
, "X_i = \\begin{cases}"
182-
, " G_{\\alpha(i)} & \\text{if }\\alpha(i-1) =" <>
183-
" \\alpha(i)\\\\"
184-
, " C_{\\alpha(i)} & \\text{otherwise}"
185-
, " \\end{cases}"
186-
, "\\end{equation}"
187-
])
172+
"\\begin{equation}\n\
173+
\X_i = \\begin{cases}\n\
174+
\ G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\\n\
175+
\ C_{\\alpha(i)} & \\text{otherwise}\n\
176+
\ \\end{cases}\n\
177+
\\\end{equation}"
178+
=?>
179+
para (rawInline "latex"
180+
"\\begin{equation}\n\
181+
\X_i = \\begin{cases}\n\
182+
\ G_{\\alpha(i)} & \\text{if }\\alpha(i-1) = \\alpha(i)\\\\\n\
183+
\ C_{\\alpha(i)} & \\text{otherwise}\n\
184+
\ \\end{cases}\n\
185+
\\\end{equation}")
188186

189187
, "One-line LaTeX fragment" =:
190188
"\\begin{equation} 2 + 3 \\end{equation}" =?>
191-
rawBlock "latex" "\\begin{equation} 2 + 3 \\end{equation}\n"
189+
para (rawInline "latex" "\\begin{equation} 2 + 3 \\end{equation}")
192190

193191
, "LaTeX fragment with more arguments" =:
194192
T.unlines [ "\\begin{tikzcd}[ampersand replacement=\\&]"

test/Tests/Readers/Org/Directive.hs

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -188,7 +188,7 @@ tests =
188188
T.unlines [ "#+OPTIONS: tex:t"
189189
, "Hello \\emph{Name}"
190190
] =?>
191-
para ("Hello" <> space <> emph "Name")
191+
para ("Hello" <> space <> rawInline "latex" "\\emph{Name}")
192192

193193
, "Alpha" =:
194194
T.unlines [ "#+OPTIONS: tex:t"
@@ -197,15 +197,15 @@ tests =
197197
para "α"
198198

199199
, "equation environment" =:
200-
T.unlines [ "#+OPTIONS: tex:t"
201-
, "\\begin{equation}"
202-
, "f(x) = x^2"
203-
, "\\end{equation}"
204-
] =?>
205-
rawBlock "latex" (T.unlines [ "\\begin{equation}"
206-
, "f(x) = x^2"
207-
, "\\end{equation}"
208-
])
200+
"#+OPTIONS: tex:t\n\
201+
\\\begin{equation}\n\
202+
\f(x) = x^2\n\
203+
\\\end{equation}"
204+
=?>
205+
para (rawInline "latex"
206+
"\\begin{equation}\n\
207+
\f(x) = x^2\n\
208+
\\\end{equation}")
209209
]
210210

211211
, testGroup "Ignore LaTeX fragments"
@@ -227,7 +227,7 @@ tests =
227227
, "f(x) = x^2"
228228
, "\\end{equation}"
229229
] =?>
230-
(mempty :: Blocks)
230+
(para mempty)
231231
]
232232

233233
, testGroup "Verbatim LaTeX"

test/Tests/Readers/Org/Inline.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -342,7 +342,7 @@ tests =
342342

343343
, "Inline LaTeX command with spaces" =:
344344
"\\emph{Emphasis mine}" =?>
345-
para (emph "Emphasis mine")
345+
para (rawInline "latex" "\\emph{Emphasis mine}")
346346

347347
, "Inline math symbols" =:
348348
"\\tau \\oplus \\alpha" =?>

test/Tests/Readers/Org/Inline/Citation.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -208,6 +208,6 @@ tests =
208208
, citationMode = NormalCitation
209209
, citationNoteNum = 0
210210
, citationHash = 0}
211-
in (para . cite [citation] $ rawInline "latex" "\\cite{Coffee}")
211+
in (para $ rawInline "latex" "\\cite{Coffee}")
212212

213213
]

test/command/10836.md

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,13 @@
1+
```
2+
% pandoc -f org -t latex
3+
Some equation here
4+
\begin{equation}
5+
x = y
6+
\end{equation}
7+
where $x$ is something important.
8+
^D
9+
Some equation here
10+
\begin{equation}
11+
x = y
12+
\end{equation} where \(x\) is something important.
13+
```

0 commit comments

Comments
 (0)