LaTeX reader: parse macro defs as raw latex...

when `latex_macros` is disabled.  (When `latex_macros` is enabled,
we omit them, since pandoc is applying the macros itself.)

Previously, it was documented that the macro definitions got
passed through as raw latex regardless of whether `latex_macros`
was set -- but in fact they never got passed through.
This commit is contained in:
John MacFarlane 2019-11-02 10:36:31 -07:00
parent 724fd655e7
commit db972b8ea0
2 changed files with 15 additions and 10 deletions

View file

@ -4337,8 +4337,8 @@ When `latex_macros` is disabled, the raw LaTeX and math will
not have macros applied. This is usually a better approach when not have macros applied. This is usually a better approach when
you are targeting LaTeX or PDF. you are targeting LaTeX or PDF.
Whether or not `latex_macros` is enabled, the macro definitions The macro definitions will be passed through as raw LaTeX
will still be passed through as raw LaTeX. only if `latex_macros` is not enabled.
## Links ## Links

View file

@ -128,7 +128,7 @@ rawLaTeXBlock = do
lookAhead (try (char '\\' >> letter)) lookAhead (try (char '\\' >> letter))
inp <- getInput inp <- getInput
let toks = tokenize "source" $ T.pack inp let toks = tokenize "source" $ T.pack inp
snd <$> (rawLaTeXParser toks False macroDef blocks snd <$> (rawLaTeXParser toks False (macroDef (const mempty)) blocks
<|> (rawLaTeXParser toks True <|> (rawLaTeXParser toks True
(do choice (map controlSeq (do choice (map controlSeq
["include", "input", "subfile", "usepackage"]) ["include", "input", "subfile", "usepackage"])
@ -1418,7 +1418,7 @@ inline = (mempty <$ comment)
<|> (space <$ whitespace) <|> (space <$ whitespace)
<|> (softbreak <$ endline) <|> (softbreak <$ endline)
<|> word <|> word
<|> macroDef <|> macroDef (rawInline "latex")
<|> inlineCommand' <|> inlineCommand'
<|> inlineEnvironment <|> inlineEnvironment
<|> inlineGroup <|> inlineGroup
@ -1464,9 +1464,11 @@ end_ t = try (do
preamble :: PandocMonad m => LP m Blocks preamble :: PandocMonad m => LP m Blocks
preamble = mempty <$ many preambleBlock preamble = mempty <$ many preambleBlock
where preambleBlock = spaces1 where preambleBlock = spaces1
<|> void (macroDef <|> blockCommand) <|> macroDef (const ())
<|> void blockCommand
<|> void braced <|> void braced
<|> (notFollowedBy (begin_ "document") >> void anyTok) <|> (do notFollowedBy (begin_ "document")
void anyTok)
paragraph :: PandocMonad m => LP m Blocks paragraph :: PandocMonad m => LP m Blocks
paragraph = do paragraph = do
@ -1532,9 +1534,12 @@ authors = try $ do
egroup egroup
addMeta "author" (map trimInlines auths) addMeta "author" (map trimInlines auths)
macroDef :: (Monoid a, PandocMonad m) => LP m a macroDef :: (PandocMonad m, Monoid a) => (String -> a) -> LP m a
macroDef = macroDef constructor = do
mempty <$ (commandDef <|> environmentDef) (_, s) <- withRaw (commandDef <|> environmentDef)
(constructor (T.unpack $ untokenize s) <$
guardDisabled Ext_latex_macros)
<|> return mempty
where commandDef = do where commandDef = do
(name, macro') <- newcommand <|> letmacro <|> defmacro (name, macro') <- newcommand <|> letmacro <|> defmacro
guardDisabled Ext_latex_macros <|> guardDisabled Ext_latex_macros <|>
@ -2368,7 +2373,7 @@ block :: PandocMonad m => LP m Blocks
block = do block = do
res <- (mempty <$ spaces1) res <- (mempty <$ spaces1)
<|> environment <|> environment
<|> macroDef <|> macroDef (rawBlock "latex")
<|> blockCommand <|> blockCommand
<|> paragraph <|> paragraph
<|> grouped block <|> grouped block