aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2018-10-14 22:29:49 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2018-10-15 00:37:17 -0700
commite752a027f13a0e6c669fa3211824f82daff23058 (patch)
tree18ba77c2a4af4f93e31a0613b3052607f65d1ca2 /src/Text/Pandoc/Readers
parent1435d0b07995329821363d12da89c85206d8afa9 (diff)
downloadpandoc-e752a027f13a0e6c669fa3211824f82daff23058.tar.gz
T.P.R.LaTeX.Parsing: moved some functions up a level.
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Parsing.hs41
1 files changed, 21 insertions, 20 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
index 9256217fe..556d0ca97 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
@@ -403,30 +403,30 @@ doMacros n = do
Tok spos (CtrlSeq (name <> w)) (x1 <> w <> x2) : ts
where (x1, x2) = T.break isSpaceOrTab x
combineTok t ts = t:ts
+ matchTok (Tok _ toktype txt) =
+ satisfyTok (\(Tok _ toktype' txt') ->
+ toktype == toktype' &&
+ txt == txt')
+ matchPattern toks = try $ mapM_ matchTok toks
+ getargs argmap [] = return argmap
+ getargs argmap (Pattern toks : rest) = try $ do
+ matchPattern toks
+ getargs argmap rest
+ getargs argmap (ArgNum i : Pattern toks : rest) =
+ try $ do
+ x <- mconcat <$> manyTill
+ (braced <|> ((:[]) <$> anyTok))
+ (matchPattern toks)
+ getargs (M.insert i x argmap) rest
+ getargs argmap (ArgNum i : rest) = do
+ x <- try $ spaces >> bracedOrToken
+ getargs (M.insert i x argmap) rest
handleMacros spos name ts = do
macros <- sMacros <$> getState
case M.lookup name macros of
Nothing -> return ()
Just (Macro expansionPoint argspecs optarg newtoks) -> do
setInput ts
- let matchTok (Tok _ toktype txt) =
- satisfyTok (\(Tok _ toktype' txt') ->
- toktype == toktype' &&
- txt == txt')
- let matchPattern toks = try $ mapM_ matchTok toks
- let getargs argmap [] = return argmap
- getargs argmap (Pattern toks : rest) = try $ do
- matchPattern toks
- getargs argmap rest
- getargs argmap (ArgNum i : Pattern toks : rest) =
- try $ do
- x <- mconcat <$> manyTill
- (braced <|> ((:[]) <$> anyTok))
- (matchPattern toks)
- getargs (M.insert i x argmap) rest
- getargs argmap (ArgNum i : rest) = do
- x <- try $ spaces >> bracedOrToken
- getargs (M.insert i x argmap) rest
args <- case optarg of
Nothing -> getargs M.empty argspecs
Just o -> do
@@ -442,12 +442,13 @@ doMacros n = do
-- see #4007
addTok _ (Tok _ (CtrlSeq x) txt)
acc@(Tok _ Word _ : _)
- | not (T.null txt) &&
- isLetter (T.last txt) =
+ | not (T.null txt)
+ , isLetter (T.last txt) =
Tok spos (CtrlSeq x) (txt <> " ") : acc
addTok _ t acc = setpos spos t : acc
ts' <- getInput
setInput $ foldr (addTok False) ts' newtoks
+
case expansionPoint of
ExpandWhenUsed ->
if n > 20 -- detect macro expansion loops