LaTeX reader: handle parameter patterns for \def
.
For example: `\def\foo#1[#2]{#1 and #2}`. Closes #4768. Also fixes #4771. API change: in Text.Pandoc.Readers.LaTeX.Types, new type ArgSpec added. Second parameter of Macro constructor is now `[ArgSpec]` instead of `Int`.
This commit is contained in:
parent
919c50162c
commit
c27ce1e70e
3 changed files with 57 additions and 23 deletions
|
@ -71,7 +71,7 @@ import Text.Pandoc.Options
|
||||||
import Text.Pandoc.Parsing hiding (blankline, many, mathDisplay, mathInline,
|
import Text.Pandoc.Parsing hiding (blankline, many, mathDisplay, mathInline,
|
||||||
optional, space, spaces, withRaw, (<|>))
|
optional, space, spaces, withRaw, (<|>))
|
||||||
import Text.Pandoc.Readers.LaTeX.Types (ExpansionPoint (..), Macro (..),
|
import Text.Pandoc.Readers.LaTeX.Types (ExpansionPoint (..), Macro (..),
|
||||||
Tok (..), TokType (..))
|
ArgSpec (..), Tok (..), TokType (..))
|
||||||
import Text.Pandoc.Shared
|
import Text.Pandoc.Shared
|
||||||
import qualified Text.Pandoc.Translations as Translations
|
import qualified Text.Pandoc.Translations as Translations
|
||||||
import Text.Pandoc.Walk
|
import Text.Pandoc.Walk
|
||||||
|
@ -473,21 +473,38 @@ doMacros n = do
|
||||||
macros <- sMacros <$> getState
|
macros <- sMacros <$> getState
|
||||||
case M.lookup name macros of
|
case M.lookup name macros of
|
||||||
Nothing -> return ()
|
Nothing -> return ()
|
||||||
Just (Macro expansionPoint numargs optarg newtoks) -> do
|
Just (Macro expansionPoint argspecs optarg newtoks) -> do
|
||||||
setInput ts
|
setInput ts
|
||||||
let getarg = try $ spaces >> bracedOrToken
|
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
|
args <- case optarg of
|
||||||
Nothing -> count numargs getarg
|
Nothing -> getargs M.empty argspecs
|
||||||
Just o ->
|
Just o -> do
|
||||||
(:) <$> option o bracketedToks
|
x <- option o bracketedToks
|
||||||
<*> count (numargs - 1) getarg
|
getargs (M.singleton 1 x) argspecs
|
||||||
-- first boolean param is true if we're tokenizing
|
-- first boolean param is true if we're tokenizing
|
||||||
-- an argument (in which case we don't want to
|
-- an argument (in which case we don't want to
|
||||||
-- expand #1 etc.)
|
-- expand #1 etc.)
|
||||||
let addTok False (Tok _ (Arg i) _) acc | i > 0
|
let addTok False (Tok _ (Arg i) _) acc =
|
||||||
, i <= numargs =
|
case M.lookup i args of
|
||||||
foldr (addTok True) acc (args !! (i - 1))
|
Nothing -> mzero
|
||||||
-- add space if needed after control sequence
|
Just xs -> foldr (addTok True) acc xs
|
||||||
-- see #4007
|
-- see #4007
|
||||||
addTok _ (Tok _ (CtrlSeq x) txt)
|
addTok _ (Tok _ (CtrlSeq x) txt)
|
||||||
acc@(Tok _ Word _ : _)
|
acc@(Tok _ Word _ : _)
|
||||||
|
@ -2148,24 +2165,28 @@ letmacro = do
|
||||||
optional $ symbol '='
|
optional $ symbol '='
|
||||||
spaces
|
spaces
|
||||||
contents <- bracedOrToken
|
contents <- bracedOrToken
|
||||||
return (name, Macro ExpandWhenDefined 0 Nothing contents)
|
return (name, Macro ExpandWhenDefined [] Nothing contents)
|
||||||
|
|
||||||
defmacro :: PandocMonad m => LP m (Text, Macro)
|
defmacro :: PandocMonad m => LP m (Text, Macro)
|
||||||
defmacro = try $ do
|
defmacro = try $ do
|
||||||
controlSeq "def"
|
controlSeq "def"
|
||||||
Tok _ (CtrlSeq name) _ <- anyControlSeq
|
Tok _ (CtrlSeq name) _ <- anyControlSeq
|
||||||
numargs <- option 0 $ argSeq 1
|
argspecs <- many (argspecArg <|> argspecPattern)
|
||||||
-- we use withVerbatimMode, because macros are to be expanded
|
-- we use withVerbatimMode, because macros are to be expanded
|
||||||
-- at point of use, not point of definition
|
-- at point of use, not point of definition
|
||||||
contents <- withVerbatimMode bracedOrToken
|
contents <- withVerbatimMode bracedOrToken
|
||||||
return (name, Macro ExpandWhenUsed numargs Nothing contents)
|
return (name, Macro ExpandWhenUsed argspecs Nothing contents)
|
||||||
|
|
||||||
-- Note: we don't yet support fancy things like #1.#2
|
argspecArg :: PandocMonad m => LP m ArgSpec
|
||||||
argSeq :: PandocMonad m => Int -> LP m Int
|
argspecArg = do
|
||||||
argSeq n = do
|
|
||||||
Tok _ (Arg i) _ <- satisfyTok isArgTok
|
Tok _ (Arg i) _ <- satisfyTok isArgTok
|
||||||
guard $ i == n
|
return $ ArgNum i
|
||||||
argSeq (n+1) <|> return n
|
|
||||||
|
argspecPattern :: PandocMonad m => LP m ArgSpec
|
||||||
|
argspecPattern =
|
||||||
|
Pattern <$> many1 (satisfyTok (\(Tok _ toktype' txt) ->
|
||||||
|
(toktype' == Symbol || toktype' == Word) &&
|
||||||
|
(txt /= "{" && txt /= "\\" && txt /= "}")))
|
||||||
|
|
||||||
isArgTok :: Tok -> Bool
|
isArgTok :: Tok -> Bool
|
||||||
isArgTok (Tok _ (Arg _) _) = True
|
isArgTok (Tok _ (Arg _) _) = True
|
||||||
|
@ -2186,6 +2207,7 @@ newcommand = do
|
||||||
(symbol '{' *> spaces *> anyControlSeq <* spaces <* symbol '}')
|
(symbol '{' *> spaces *> anyControlSeq <* spaces <* symbol '}')
|
||||||
spaces
|
spaces
|
||||||
numargs <- option 0 $ try bracketedNum
|
numargs <- option 0 $ try bracketedNum
|
||||||
|
let argspecs = map (\i -> ArgNum i) [1..numargs]
|
||||||
spaces
|
spaces
|
||||||
optarg <- option Nothing $ Just <$> try bracketedToks
|
optarg <- option Nothing $ Just <$> try bracketedToks
|
||||||
spaces
|
spaces
|
||||||
|
@ -2195,7 +2217,7 @@ newcommand = do
|
||||||
case M.lookup name macros of
|
case M.lookup name macros of
|
||||||
Just _ -> report $ MacroAlreadyDefined (T.unpack txt) pos
|
Just _ -> report $ MacroAlreadyDefined (T.unpack txt) pos
|
||||||
Nothing -> return ()
|
Nothing -> return ()
|
||||||
return (name, Macro ExpandWhenUsed numargs optarg contents)
|
return (name, Macro ExpandWhenUsed argspecs optarg contents)
|
||||||
|
|
||||||
newenvironment :: PandocMonad m => LP m (Text, Macro, Macro)
|
newenvironment :: PandocMonad m => LP m (Text, Macro, Macro)
|
||||||
newenvironment = do
|
newenvironment = do
|
||||||
|
@ -2208,6 +2230,7 @@ newenvironment = do
|
||||||
name <- untokenize <$> braced
|
name <- untokenize <$> braced
|
||||||
spaces
|
spaces
|
||||||
numargs <- option 0 $ try bracketedNum
|
numargs <- option 0 $ try bracketedNum
|
||||||
|
let argspecs = map (\i -> ArgNum i) [1..numargs]
|
||||||
spaces
|
spaces
|
||||||
optarg <- option Nothing $ Just <$> try bracketedToks
|
optarg <- option Nothing $ Just <$> try bracketedToks
|
||||||
spaces
|
spaces
|
||||||
|
@ -2219,8 +2242,8 @@ newenvironment = do
|
||||||
case M.lookup name macros of
|
case M.lookup name macros of
|
||||||
Just _ -> report $ MacroAlreadyDefined (T.unpack name) pos
|
Just _ -> report $ MacroAlreadyDefined (T.unpack name) pos
|
||||||
Nothing -> return ()
|
Nothing -> return ()
|
||||||
return (name, Macro ExpandWhenUsed numargs optarg startcontents,
|
return (name, Macro ExpandWhenUsed argspecs optarg startcontents,
|
||||||
Macro ExpandWhenUsed 0 Nothing endcontents)
|
Macro ExpandWhenUsed [] Nothing endcontents)
|
||||||
|
|
||||||
bracketedToks :: PandocMonad m => LP m [Tok]
|
bracketedToks :: PandocMonad m => LP m [Tok]
|
||||||
bracketedToks = do
|
bracketedToks = do
|
||||||
|
|
|
@ -31,6 +31,7 @@ Types for LaTeX tokens and macros.
|
||||||
module Text.Pandoc.Readers.LaTeX.Types ( Tok(..)
|
module Text.Pandoc.Readers.LaTeX.Types ( Tok(..)
|
||||||
, TokType(..)
|
, TokType(..)
|
||||||
, Macro(..)
|
, Macro(..)
|
||||||
|
, ArgSpec(..)
|
||||||
, ExpansionPoint(..)
|
, ExpansionPoint(..)
|
||||||
, SourcePos
|
, SourcePos
|
||||||
)
|
)
|
||||||
|
@ -49,5 +50,8 @@ data Tok = Tok SourcePos TokType Text
|
||||||
data ExpansionPoint = ExpandWhenDefined | ExpandWhenUsed
|
data ExpansionPoint = ExpandWhenDefined | ExpandWhenUsed
|
||||||
deriving (Eq, Ord, Show)
|
deriving (Eq, Ord, Show)
|
||||||
|
|
||||||
data Macro = Macro ExpansionPoint Int (Maybe [Tok]) [Tok]
|
data Macro = Macro ExpansionPoint [ArgSpec] (Maybe [Tok]) [Tok]
|
||||||
|
deriving Show
|
||||||
|
|
||||||
|
data ArgSpec = ArgNum Int | Pattern [Tok]
|
||||||
deriving Show
|
deriving Show
|
||||||
|
|
7
test/command/4768.md
Normal file
7
test/command/4768.md
Normal file
|
@ -0,0 +1,7 @@
|
||||||
|
```
|
||||||
|
% pandoc -f latex -t plain
|
||||||
|
\def\foo#1!#2!#3{#1 or #2 and #3}
|
||||||
|
\foo aa!bbb bbb!{ccc}
|
||||||
|
^D
|
||||||
|
aa or bbb bbb and ccc
|
||||||
|
```
|
Loading…
Add table
Reference in a new issue