From 81eadfd99ad3e905b806cc6c80ab0fea0185286f Mon Sep 17 00:00:00 2001 From: John MacFarlane <jgm@berkeley.edu> Date: Wed, 26 May 2021 22:50:35 -0700 Subject: [PATCH] LaTeX reader: improve `\def` and implement `\newif`. - Improve parsing of `\def` macros. We previously set "verbatim mode" even for parsing the initial `\def`; this caused problems for things like ``` \def\foo{\def\bar{BAR}} \foo \bar ``` - Implement `\newif`. - Add tests. --- src/Text/Pandoc/Readers/LaTeX/Macro.hs | 59 ++++++++++++++++++------ src/Text/Pandoc/Readers/LaTeX/Parsing.hs | 19 +++++++- test/command/newif.md | 55 ++++++++++++++++++++++ 3 files changed, 118 insertions(+), 15 deletions(-) create mode 100644 test/command/newif.md diff --git a/src/Text/Pandoc/Readers/LaTeX/Macro.hs b/src/Text/Pandoc/Readers/LaTeX/Macro.hs index 607f5438c..5495a8e74 100644 --- a/src/Text/Pandoc/Readers/LaTeX/Macro.hs +++ b/src/Text/Pandoc/Readers/LaTeX/Macro.hs @@ -14,6 +14,7 @@ import Text.Pandoc.Parsing hiding (blankline, mathDisplay, mathInline, import Control.Applicative ((<|>), optional) import qualified Data.Map as M import Data.Text (Text) +import qualified Data.Text as T macroDef :: (PandocMonad m, Monoid a) => (Text -> a) -> LP m a macroDef constructor = do @@ -22,9 +23,11 @@ macroDef constructor = do guardDisabled Ext_latex_macros) <|> return mempty where commandDef = do - (name, macro') <- newcommand <|> letmacro <|> defmacro + nameMacroPairs <- newcommand <|> letmacro <|> defmacro <|> newif guardDisabled Ext_latex_macros <|> - updateState (\s -> s{ sMacros = M.insert name macro' (sMacros s) }) + mapM_ (\(name, macro') -> + updateState (\s -> s{ sMacros = M.insert name macro' + (sMacros s) })) nameMacroPairs environmentDef = do mbenv <- newenvironment case mbenv of @@ -40,7 +43,7 @@ macroDef constructor = do -- @\newcommand{\envname}[n-args][default]{begin}@ -- @\newcommand{\endenvname}@ -letmacro :: PandocMonad m => LP m (Text, Macro) +letmacro :: PandocMonad m => LP m [(Text, Macro)] letmacro = do controlSeq "let" (name, contents) <- withVerbatimMode $ do @@ -53,18 +56,47 @@ letmacro = do contents <- bracedOrToken return (name, contents) contents' <- doMacros' 0 contents - return (name, Macro ExpandWhenDefined [] Nothing contents') + return [(name, Macro ExpandWhenDefined [] Nothing contents')] -defmacro :: PandocMonad m => LP m (Text, Macro) -defmacro = try $ +defmacro :: PandocMonad m => LP m [(Text, Macro)] +defmacro = do -- we use withVerbatimMode, because macros are to be expanded -- at point of use, not point of definition + controlSeq "def" withVerbatimMode $ do - controlSeq "def" Tok _ (CtrlSeq name) _ <- anyControlSeq argspecs <- many (argspecArg <|> argspecPattern) contents <- bracedOrToken - return (name, Macro ExpandWhenUsed argspecs Nothing contents) + return [(name, Macro ExpandWhenUsed argspecs Nothing contents)] + +-- \newif\iffoo' defines: +-- \iffoo to be \iffalse +-- \footrue to be a command that defines \iffoo to be \iftrue +-- \foofalse to be a command that defines \iffoo to be \iffalse +newif :: PandocMonad m => LP m [(Text, Macro)] +newif = do + controlSeq "newif" + withVerbatimMode $ do + Tok pos (CtrlSeq name) _ <- anyControlSeq + -- \def\iffoo\iffalse + -- \def\footrue{\def\iffoo\iftrue} + -- \def\foofalse{\def\iffoo\iffalse} + let base = T.drop 2 name + return [ (name, Macro ExpandWhenUsed [] Nothing + [Tok pos (CtrlSeq "iffalse") "\\iffalse"]) + , (base <> "true", + Macro ExpandWhenUsed [] Nothing + [ Tok pos (CtrlSeq "def") "\\def" + , Tok pos (CtrlSeq name) ("\\" <> name) + , Tok pos (CtrlSeq "iftrue") "\\iftrue" + ]) + , (base <> "false", + Macro ExpandWhenUsed [] Nothing + [ Tok pos (CtrlSeq "def") "\\def" + , Tok pos (CtrlSeq name) ("\\" <> name) + , Tok pos (CtrlSeq "iffalse") "\\iffalse" + ]) + ] argspecArg :: PandocMonad m => LP m ArgSpec argspecArg = do @@ -77,10 +109,9 @@ argspecPattern = (toktype' == Symbol || toktype' == Word) && (txt /= "{" && txt /= "\\" && txt /= "}"))) -newcommand :: PandocMonad m => LP m (Text, Macro) +newcommand :: PandocMonad m => LP m [(Text, Macro)] newcommand = do - pos <- getPosition - Tok _ (CtrlSeq mtype) _ <- controlSeq "newcommand" <|> + Tok pos (CtrlSeq mtype) _ <- controlSeq "newcommand" <|> controlSeq "renewcommand" <|> controlSeq "providecommand" <|> controlSeq "DeclareMathOperator" <|> @@ -112,9 +143,9 @@ newcommand = do Just macro | mtype == "newcommand" -> do report $ MacroAlreadyDefined txt pos - return (name, macro) - | mtype == "providecommand" -> return (name, macro) - _ -> return (name, Macro ExpandWhenUsed argspecs optarg contents) + return [(name, macro)] + | mtype == "providecommand" -> return [(name, macro)] + _ -> return [(name, Macro ExpandWhenUsed argspecs optarg contents)] newenvironment :: PandocMonad m => LP m (Maybe (Text, Macro, Macro)) newenvironment = do diff --git a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs index 1c77eb299..a17b1f324 100644 --- a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs +++ b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs @@ -113,7 +113,6 @@ import Text.Pandoc.Readers.LaTeX.Types (ExpansionPoint (..), Macro (..), ArgSpec (..), Tok (..), TokType (..)) import Text.Pandoc.Shared import Text.Parsec.Pos --- import Debug.Trace newtype DottedNum = DottedNum [Int] deriving (Show, Eq) @@ -563,8 +562,26 @@ 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 _ _ = mzero +handleIf :: PandocMonad m => Bool -> [Tok] -> LP m [Tok] +handleIf b ts = do + res' <- lift $ runParserT (ifParser b) defaultLaTeXState "tokens" ts + case res' of + Left _ -> Prelude.fail "Could not parse conditional" + Right ts' -> return ts' + +ifParser :: PandocMonad m => Bool -> LP m [Tok] +ifParser b = do + ifToks <- many (notFollowedBy (controlSeq "else" <|> controlSeq "fi") + *> anyTok) + elseToks <- (controlSeq "else" >> manyTill anyTok (controlSeq "fi")) + <|> ([] <$ controlSeq "fi") + rest <- getInput + return $ (if b then ifToks else elseToks) ++ rest + startsWithAlphaNum :: Text -> Bool startsWithAlphaNum t = case T.uncons t of diff --git a/test/command/newif.md b/test/command/newif.md new file mode 100644 index 000000000..f444f14c9 --- /dev/null +++ b/test/command/newif.md @@ -0,0 +1,55 @@ +``` +% pandoc -f latex -t plain +\iftrue +should print +\iftrue +should print +\else +should not print +\fi +\else +should not print +\fi + +\iffalse +should not print +\else +\iftrue +should print +\else +should not print +\fi +\fi + +\newif\ifepub + +\ifepub +should not print +\fi + +\epubtrue + +\ifepub +should print +\else +should not print +\fi + +\epubfalse + +\ifepub +should not print +\else +should print +\fi +^D +should print + +should print + +should print + +should print + +should print +```