aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2021-05-26 22:50:35 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2021-05-27 09:15:04 -0700
commit81eadfd99ad3e905b806cc6c80ab0fea0185286f (patch)
tree20aca56660789331dc9cd034c7e1f1f4116d8e95 /src/Text/Pandoc/Readers/LaTeX/Parsing.hs
parente0a1f7d2cfa1b18210ea13e0aa03747e6c76e5c5 (diff)
downloadpandoc-81eadfd99ad3e905b806cc6c80ab0fea0185286f.tar.gz
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.
Diffstat (limited to 'src/Text/Pandoc/Readers/LaTeX/Parsing.hs')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Parsing.hs19
1 files changed, 18 insertions, 1 deletions
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