Remove retokenizing in rawLaTeXParser.

This was causing serious problems with `newif` commands.
See #6096.  And it didn't seem to make any difference for
the tests; I assume that, unless there's some untested
behavior, this is something that has now become unnecessary.
This commit is contained in:
John MacFarlane 2022-01-21 10:17:58 -08:00
parent 52b78b10c8
commit 672b6dc7e6
2 changed files with 11 additions and 15 deletions

View file

@ -138,14 +138,15 @@ rawLaTeXBlock :: (PandocMonad m, HasMacros s, HasReaderOptions s)
rawLaTeXBlock = do rawLaTeXBlock = do
lookAhead (try (char '\\' >> letter)) lookAhead (try (char '\\' >> letter))
toks <- getInputTokens toks <- getInputTokens
snd <$> (rawLaTeXParser toks False (macroDef (const mempty)) blocks snd <$> (
<|> rawLaTeXParser toks True rawLaTeXParser toks
(do choice (map controlSeq (macroDef (const mempty) <|>
do choice (map controlSeq
["include", "input", "subfile", "usepackage"]) ["include", "input", "subfile", "usepackage"])
skipMany opt skipMany opt
braced braced
return mempty) blocks return mempty) blocks
<|> rawLaTeXParser toks True <|> rawLaTeXParser toks
(environment <|> blockCommand) (environment <|> blockCommand)
(mconcat <$> many (block <|> beginOrEndCommand))) (mconcat <$> many (block <|> beginOrEndCommand)))
@ -169,10 +170,10 @@ rawLaTeXInline = do
lookAhead (try (char '\\' >> letter)) lookAhead (try (char '\\' >> letter))
toks <- getInputTokens toks <- getInputTokens
raw <- snd <$> raw <- snd <$>
( rawLaTeXParser toks True ( rawLaTeXParser toks
(mempty <$ (controlSeq "input" >> skipMany rawopt >> braced)) (mempty <$ (controlSeq "input" >> skipMany rawopt >> braced))
inlines inlines
<|> rawLaTeXParser toks True (inlineEnvironment <|> inlineCommand') <|> rawLaTeXParser toks (inlineEnvironment <|> inlineCommand')
inlines inlines
) )
finalbraces <- mconcat <$> many (try (string "{}")) -- see #5439 finalbraces <- mconcat <$> many (try (string "{}")) -- see #5439
@ -182,7 +183,7 @@ inlineCommand :: PandocMonad m => ParserT Sources ParserState m Inlines
inlineCommand = do inlineCommand = do
lookAhead (try (char '\\' >> letter)) lookAhead (try (char '\\' >> letter))
toks <- getInputTokens toks <- getInputTokens
fst <$> rawLaTeXParser toks True (inlineEnvironment <|> inlineCommand') fst <$> rawLaTeXParser toks (inlineEnvironment <|> inlineCommand')
inlines inlines
-- inline elements: -- inline elements:

View file

@ -255,9 +255,9 @@ withVerbatimMode parser = do
return result return result
rawLaTeXParser :: (PandocMonad m, HasMacros s, HasReaderOptions s, Show a) rawLaTeXParser :: (PandocMonad m, HasMacros s, HasReaderOptions s, Show a)
=> [Tok] -> Bool -> LP m a -> LP m a => [Tok] -> LP m a -> LP m a
-> ParserT Sources s m (a, Text) -> ParserT Sources s m (a, Text)
rawLaTeXParser toks retokenize parser valParser = do rawLaTeXParser toks parser valParser = do
pstate <- getState pstate <- getState
let lstate = def{ sOptions = extractReaderOptions pstate } let lstate = def{ sOptions = extractReaderOptions pstate }
let lstate' = lstate { sMacros = extractMacros pstate :| [] } let lstate' = lstate { sMacros = extractMacros pstate :| [] }
@ -271,12 +271,7 @@ rawLaTeXParser toks retokenize parser valParser = do
case res' of case res' of
Left _ -> mzero Left _ -> mzero
Right (endpos, toks') -> do Right (endpos, toks') -> do
res <- lift $ runParserT (do when retokenize $ do res <- lift $ runParserT rawparser lstate' "chunk" toks'
-- retokenize, applying macros
ts <- many anyTok
setInput ts
rawparser)
lstate' "chunk" toks'
case res of case res of
Left _ -> mzero Left _ -> mzero
Right ((val, raw), st) -> do Right ((val, raw), st) -> do