aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2025-11-03 20:51:20 +0100
committerJohn MacFarlane <[email protected]>2025-11-03 23:16:48 +0100
commit74f583847fb108593101a34ed88a13005a2252fb (patch)
tree55ea08f3aa4d3eb5bea50dc8142da9db63124810
parent594f1099561790453f4fb4bd8558621f4eec724b (diff)
LaTeX reader: fix bugs in raw LaTeX parsing.
Fix `rawTeXParser`. Make macro expansion in raw LaTeX depend on the setting of the `latex_macros` extension. Previously macros were always expanded, even in raw TeX in markdown. In addition, there was previously a bug that caused content to be garbled in certain cases. Closes #11253. Handle `ifstrequal` at a lower level, like the other `if` commands. See #11253.
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs17
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Parsing.hs40
-rw-r--r--test/command/11253.md27
3 files changed, 55 insertions, 29 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 68714954c..c9d2d62d3 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -177,8 +177,7 @@ rawLaTeXInline = do
( rawLaTeXParser toks
(mempty <$ (controlSeq "input" >> skipMany rawopt >> braced))
inlines
- <|> rawLaTeXParser toks (inlineEnvironment <|> inlineCommand')
- inlines
+ <|> rawLaTeXParser toks inline inlines
)
finalbraces <- mconcat <$> many (try (string "{}")) -- see #5439
return $ raw <> T.pack finalbraces
@@ -426,7 +425,6 @@ inlineCommands = M.unions
, ("textcolor", coloredInline "color")
, ("colorbox", coloredInline "background-color")
-- etoolbox
- , ("ifstrequal", ifstrequal)
, ("newtoggle", braced >>= newToggle)
, ("toggletrue", braced >>= setToggle True)
, ("togglefalse", braced >>= setToggle False)
@@ -566,18 +564,6 @@ ifToggle = do
report $ UndefinedToggle name' pos
return ()
-ifstrequal :: (PandocMonad m, Monoid a) => LP m a
-ifstrequal = do
- str1 <- tok
- str2 <- tok
- ifequal <- withVerbatimMode braced
- ifnotequal <- withVerbatimMode braced
- TokStream _ ts <- getInput
- if str1 == str2
- then setInput $ TokStream False (ifequal ++ ts)
- else setInput $ TokStream False (ifnotequal ++ ts)
- return mempty
-
coloredInline :: PandocMonad m => Text -> LP m Inlines
coloredInline stylename = do
skipopts
@@ -1026,7 +1012,6 @@ blockCommands = M.fromList
-- alignment
, ("raggedright", pure mempty)
-- etoolbox
- , ("ifstrequal", ifstrequal)
, ("newtoggle", braced >>= newToggle)
, ("toggletrue", braced >>= setToggle True)
, ("togglefalse", braced >>= setToggle False)
diff --git a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
index f4d363380..bb76f6e18 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
@@ -301,14 +301,14 @@ rawLaTeXParser toks parser valParser = do
Left _ -> mzero
Right ((val, raw), st) -> do
updateState (updateMacros ((NonEmpty.head (sMacros st)) <>))
- let skipTilPos stopPos = do
- anyChar
+ let rawChar = do
pos <- getPosition
- if pos >= stopPos
- then return ()
- else skipTilPos stopPos
- skipTilPos endpos
- let result = untokenize raw
+ if pos >= endpos
+ then mzero
+ else anyChar
+ result <- (guardEnabled Ext_latex_macros
+ >> (untokenize raw <$ skipMany rawChar))
+ <|> T.pack <$> many rawChar
-- ensure we end with space if input did, see #4442
let result' =
case reverse toks' of
@@ -650,16 +650,30 @@ trySpecialMacro "xspace" ts = do
Tok pos Word t : _
| startsWithAlphaNum t -> return $ Tok pos Spaces " " : ts'
_ -> return ts'
-trySpecialMacro "iftrue" ts = handleIf True ts
-trySpecialMacro "iffalse" ts = handleIf False ts
+trySpecialMacro "iftrue" ts = handleIf (ifParser True) ts
+trySpecialMacro "iffalse" ts = handleIf (ifParser False) ts
trySpecialMacro "ifmmode" ts = do
mathMode <- sMathMode <$> getState
- handleIf mathMode ts
+ handleIf (ifParser mathMode) ts
+trySpecialMacro "ifstrequal" ts = do
+ handleIf ifStrequalParser ts
trySpecialMacro _ _ = mzero
-handleIf :: PandocMonad m => Bool -> [Tok] -> LP m [Tok]
-handleIf b ts = do
- res' <- lift $ runParserT (ifParser b) defaultLaTeXState "tokens"
+ifStrequalParser :: PandocMonad m => LP m [Tok]
+ifStrequalParser = do
+ str1 <- braced <|> count 1 anyTok
+ str2 <- braced <|> count 1 anyTok
+ ifequal <- withVerbatimMode (braced <|> count 1 anyTok)
+ ifnotequal <- withVerbatimMode (braced <|> count 1 anyTok)
+ TokStream _ ts <- getInput
+ return $
+ if untokenize str1 == untokenize str2
+ then ifequal ++ ts
+ else ifnotequal ++ ts
+
+handleIf :: PandocMonad m => LP m [Tok] -> [Tok] -> LP m [Tok]
+handleIf parser ts = do
+ res' <- lift $ runParserT parser defaultLaTeXState "tokens"
$ TokStream False ts
case res' of
Left _ -> Prelude.fail "Could not parse conditional"
diff --git a/test/command/11253.md b/test/command/11253.md
new file mode 100644
index 000000000..cc10d8bc0
--- /dev/null
+++ b/test/command/11253.md
@@ -0,0 +1,27 @@
+```
+% pandoc -f markdown -t native
+\ifstrequal{hello}{hello}{TRUE}{FALSE}
+\ifstrequal{hello}{world}{TRUE}{FALSE}
+^D
+[ Para
+ [ RawInline (Format "tex") "TRUE"
+ , SoftBreak
+ , RawInline (Format "tex") "FALSE"
+ ]
+]
+```
+
+```
+% pandoc -f markdown-latex_macros -t native
+\ifstrequal{hello}{hello}{TRUE}{FALSE}
+\ifstrequal{hello}{world}{TRUE}{FALSE}
+^D
+[ Para
+ [ RawInline
+ (Format "tex") "\\ifstrequal{hello}{hello}{TRUE}{FALSE}"
+ , SoftBreak
+ , RawInline
+ (Format "tex") "\\ifstrequal{hello}{world}{TRUE}{FALSE}"
+ ]
+]
+```