diff options
Diffstat (limited to 'src/Text/Pandoc/Readers/LaTeX.hs')
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 129 |
1 files changed, 69 insertions, 60 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 7c5619165..26ac781db 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -1308,13 +1308,7 @@ isBlockCommand s = treatAsBlock :: Set.Set Text treatAsBlock = Set.fromList - [ "let", "def", "DeclareRobustCommand" - , "newcommand", "renewcommand" - , "newenvironment", "renewenvironment" - , "providecommand", "provideenvironment" - -- newcommand, etc. should be parsed by macroDef, but we need this - -- here so these aren't parsed as inline commands to ignore - , "special", "pdfannot", "pdfstringdef" + [ "special", "pdfannot", "pdfstringdef" , "bibliographystyle" , "maketitle", "makeindex", "makeglossary" , "addcontentsline", "addtocontents", "addtocounter" @@ -1375,6 +1369,7 @@ inline = (mempty <$ comment) <|> (space <$ whitespace) <|> (softbreak <$ endline) <|> word + <|> macroDef <|> inlineCommand' <|> inlineEnvironment <|> inlineGroup @@ -1420,8 +1415,7 @@ end_ t = try (do preamble :: PandocMonad m => LP m Blocks preamble = mempty <$ many preambleBlock where preambleBlock = spaces1 - <|> void macroDef - <|> void blockCommand + <|> void (macroDef <|> blockCommand) <|> void braced <|> (notFollowedBy (begin_ "document") >> void anyTok) @@ -1484,9 +1478,9 @@ authors = try $ do egroup addMeta "author" (map trimInlines auths) -macroDef :: PandocMonad m => LP m Blocks +macroDef :: (Monoid a, PandocMonad m) => LP m a macroDef = - mempty <$ ((commandDef <|> environmentDef) <* doMacros 0) + mempty <$ (commandDef <|> environmentDef) where commandDef = do (name, macro') <- newcommand <|> letmacro <|> defmacro guardDisabled Ext_latex_macros <|> @@ -1506,21 +1500,28 @@ macroDef = letmacro :: PandocMonad m => LP m (Text, Macro) letmacro = do controlSeq "let" - Tok _ (CtrlSeq name) _ <- anyControlSeq - optional $ symbol '=' - spaces - contents <- bracedOrToken - return (name, Macro ExpandWhenDefined [] Nothing contents) + (name, contents) <- withVerbatimMode $ do + Tok _ (CtrlSeq name) _ <- anyControlSeq + optional $ symbol '=' + spaces + -- we first parse in verbatim mode, and then expand macros, + -- because we don't want \let\foo\bar to turn into + -- \let\foo hello if we have previously \def\bar{hello} + contents <- bracedOrToken + return (name, contents) + contents' <- doMacros' 0 contents + return (name, Macro ExpandWhenDefined [] Nothing contents') defmacro :: PandocMonad m => LP m (Text, Macro) -defmacro = try $ do - controlSeq "def" - Tok _ (CtrlSeq name) _ <- anyControlSeq - argspecs <- many (argspecArg <|> argspecPattern) +defmacro = try $ -- we use withVerbatimMode, because macros are to be expanded -- at point of use, not point of definition - contents <- withVerbatimMode bracedOrToken - return (name, Macro ExpandWhenUsed argspecs Nothing contents) + withVerbatimMode $ do + controlSeq "def" + Tok _ (CtrlSeq name) _ <- anyControlSeq + argspecs <- many (argspecArg <|> argspecPattern) + contents <- bracedOrToken + return (name, Macro ExpandWhenUsed argspecs Nothing contents) argspecArg :: PandocMonad m => LP m ArgSpec argspecArg = do @@ -1530,8 +1531,8 @@ argspecArg = do argspecPattern :: PandocMonad m => LP m ArgSpec argspecPattern = Pattern <$> many1 (satisfyTok (\(Tok _ toktype' txt) -> - (toktype' == Symbol || toktype' == Word) && - (txt /= "{" && txt /= "\\" && txt /= "}"))) + (toktype' == Symbol || toktype' == Word) && + (txt /= "{" && txt /= "\\" && txt /= "}"))) newcommand :: PandocMonad m => LP m (Text, Macro) newcommand = do @@ -1540,22 +1541,24 @@ newcommand = do controlSeq "renewcommand" <|> controlSeq "providecommand" <|> controlSeq "DeclareRobustCommand" - optional $ symbol '*' - Tok _ (CtrlSeq name) txt <- withVerbatimMode $ anyControlSeq <|> - (symbol '{' *> spaces *> anyControlSeq <* spaces <* symbol '}') - spaces - numargs <- option 0 $ try bracketedNum - let argspecs = map (\i -> ArgNum i) [1..numargs] - spaces - optarg <- option Nothing $ Just <$> try bracketedToks - spaces - contents <- withVerbatimMode bracedOrToken - when (mtype == "newcommand") $ do - macros <- sMacros <$> getState - case M.lookup name macros of - Just _ -> report $ MacroAlreadyDefined (T.unpack txt) pos - Nothing -> return () - return (name, Macro ExpandWhenUsed argspecs optarg contents) + withVerbatimMode $ do + Tok _ (CtrlSeq name) txt <- do + optional (symbol '*') + anyControlSeq <|> + (symbol '{' *> spaces *> anyControlSeq <* spaces <* symbol '}') + spaces + numargs <- option 0 $ try bracketedNum + let argspecs = map (\i -> ArgNum i) [1..numargs] + spaces + optarg <- option Nothing $ Just <$> try bracketedToks + spaces + contents <- bracedOrToken + when (mtype == "newcommand") $ do + macros <- sMacros <$> getState + case M.lookup name macros of + Just _ -> report $ MacroAlreadyDefined (T.unpack txt) pos + Nothing -> return () + return (name, Macro ExpandWhenUsed argspecs optarg contents) newenvironment :: PandocMonad m => LP m (Text, Macro, Macro) newenvironment = do @@ -1563,24 +1566,23 @@ newenvironment = do Tok _ (CtrlSeq mtype) _ <- controlSeq "newenvironment" <|> controlSeq "renewenvironment" <|> controlSeq "provideenvironment" - optional $ symbol '*' - spaces - name <- untokenize <$> braced - spaces - numargs <- option 0 $ try bracketedNum - let argspecs = map (\i -> ArgNum i) [1..numargs] - spaces - optarg <- option Nothing $ Just <$> try bracketedToks - spaces - startcontents <- withVerbatimMode bracedOrToken - spaces - endcontents <- withVerbatimMode bracedOrToken - when (mtype == "newenvironment") $ do - macros <- sMacros <$> getState - case M.lookup name macros of - Just _ -> report $ MacroAlreadyDefined (T.unpack name) pos - Nothing -> return () - return (name, Macro ExpandWhenUsed argspecs optarg startcontents, + withVerbatimMode $ do + optional $ symbol '*' + spaces + name <- untokenize <$> braced + spaces + numargs <- option 0 $ try bracketedNum + spaces + optarg <- option Nothing $ Just <$> try bracketedToks + let argspecs = map (\i -> ArgNum i) [1..numargs] + startcontents <- spaces >> bracedOrToken + endcontents <- spaces >> bracedOrToken + when (mtype == "newenvironment") $ do + macros <- sMacros <$> getState + case M.lookup name macros of + Just _ -> report $ MacroAlreadyDefined (T.unpack name) pos + Nothing -> return () + return (name, Macro ExpandWhenUsed argspecs optarg startcontents, Macro ExpandWhenUsed [] Nothing endcontents) bracketedNum :: PandocMonad m => LP m Int @@ -1644,7 +1646,9 @@ blockCommand = try $ do let names = ordNub [name', name] let rawDefiniteBlock = do guard $ isBlockCommand name - rawBlock "latex" <$> getRawCommand name (txt <> star) + rawcontents <- getRawCommand name (txt <> star) + (guardEnabled Ext_raw_tex >> return (rawBlock "latex" rawcontents)) + <|> ignore rawcontents -- heuristic: if it could be either block or inline, we -- treat it if block if we have a sequence of block -- commands followed by a newline. But we stop if we @@ -1656,7 +1660,10 @@ blockCommand = try $ do guard $ "start" `T.isPrefixOf` n let rawMaybeBlock = try $ do guard $ not $ isInlineCommand name - curr <- rawBlock "latex" <$> getRawCommand name (txt <> star) + rawcontents <- getRawCommand name (txt <> star) + curr <- (guardEnabled Ext_raw_tex >> + return (rawBlock "latex" rawcontents)) + <|> ignore rawcontents rest <- many $ notFollowedBy startCommand *> blockCommand lookAhead $ blankline <|> startCommand return $ curr <> mconcat rest @@ -1757,6 +1764,8 @@ blockCommands = M.fromList , ("input", include "input") , ("subfile", include "subfile") , ("usepackage", include "usepackage") + -- preamble + , ("PackageError", mempty <$ (braced >> braced >> braced)) ] |