Factor out T.P.Readers.LaTeX.Macro.
This commit is contained in:
parent
e1454fe0d0
commit
382f0e23d2
3 changed files with 156 additions and 139 deletions
|
@ -634,6 +634,7 @@ library
|
||||||
Text.Pandoc.Readers.LaTeX.Citation,
|
Text.Pandoc.Readers.LaTeX.Citation,
|
||||||
Text.Pandoc.Readers.LaTeX.Math,
|
Text.Pandoc.Readers.LaTeX.Math,
|
||||||
Text.Pandoc.Readers.LaTeX.Table,
|
Text.Pandoc.Readers.LaTeX.Table,
|
||||||
|
Text.Pandoc.Readers.LaTeX.Macro,
|
||||||
Text.Pandoc.Readers.Odt.Base,
|
Text.Pandoc.Readers.Odt.Base,
|
||||||
Text.Pandoc.Readers.Odt.Namespaces,
|
Text.Pandoc.Readers.Odt.Namespaces,
|
||||||
Text.Pandoc.Readers.Odt.StyleReader,
|
Text.Pandoc.Readers.Odt.StyleReader,
|
||||||
|
|
|
@ -47,8 +47,7 @@ import Text.Pandoc.Logging
|
||||||
import Text.Pandoc.Options
|
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 (Tok (..), TokType (..))
|
||||||
ArgSpec (..), Tok (..), TokType (..))
|
|
||||||
import Text.Pandoc.Readers.LaTeX.Parsing
|
import Text.Pandoc.Readers.LaTeX.Parsing
|
||||||
import Text.Pandoc.Readers.LaTeX.Accent (accentCommands)
|
import Text.Pandoc.Readers.LaTeX.Accent (accentCommands)
|
||||||
import Text.Pandoc.Readers.LaTeX.Citation (citationCommands, cites)
|
import Text.Pandoc.Readers.LaTeX.Citation (citationCommands, cites)
|
||||||
|
@ -58,6 +57,7 @@ import Text.Pandoc.Readers.LaTeX.Math (dollarsMath, inlineEnvironments,
|
||||||
newtheorem, theoremstyle, proof,
|
newtheorem, theoremstyle, proof,
|
||||||
theoremEnvironment)
|
theoremEnvironment)
|
||||||
import Text.Pandoc.Readers.LaTeX.Table (tableEnvironments)
|
import Text.Pandoc.Readers.LaTeX.Table (tableEnvironments)
|
||||||
|
import Text.Pandoc.Readers.LaTeX.Macro (macroDef)
|
||||||
import Text.Pandoc.Readers.LaTeX.Lang (polyglossiaLangToBCP47,
|
import Text.Pandoc.Readers.LaTeX.Lang (polyglossiaLangToBCP47,
|
||||||
babelLangToBCP47, setDefaultLanguage)
|
babelLangToBCP47, setDefaultLanguage)
|
||||||
import Text.Pandoc.Readers.LaTeX.SIunitx (siunitxCommands)
|
import Text.Pandoc.Readers.LaTeX.SIunitx (siunitxCommands)
|
||||||
|
@ -1027,143 +1027,6 @@ authors = try $ do
|
||||||
egroup
|
egroup
|
||||||
addMeta "author" (map trimInlines auths)
|
addMeta "author" (map trimInlines auths)
|
||||||
|
|
||||||
macroDef :: (PandocMonad m, Monoid a) => (Text -> a) -> LP m a
|
|
||||||
macroDef constructor = do
|
|
||||||
(_, s) <- withRaw (commandDef <|> environmentDef)
|
|
||||||
(constructor (untokenize s) <$
|
|
||||||
guardDisabled Ext_latex_macros)
|
|
||||||
<|> return mempty
|
|
||||||
where commandDef = do
|
|
||||||
(name, macro') <- newcommand <|> letmacro <|> defmacro
|
|
||||||
guardDisabled Ext_latex_macros <|>
|
|
||||||
updateState (\s -> s{ sMacros = M.insert name macro' (sMacros s) })
|
|
||||||
environmentDef = do
|
|
||||||
mbenv <- newenvironment
|
|
||||||
case mbenv of
|
|
||||||
Nothing -> return ()
|
|
||||||
Just (name, macro1, macro2) ->
|
|
||||||
guardDisabled Ext_latex_macros <|>
|
|
||||||
do updateState $ \s -> s{ sMacros =
|
|
||||||
M.insert name macro1 (sMacros s) }
|
|
||||||
updateState $ \s -> s{ sMacros =
|
|
||||||
M.insert ("end" <> name) macro2 (sMacros s) }
|
|
||||||
-- @\newenvironment{envname}[n-args][default]{begin}{end}@
|
|
||||||
-- is equivalent to
|
|
||||||
-- @\newcommand{\envname}[n-args][default]{begin}@
|
|
||||||
-- @\newcommand{\endenvname}@
|
|
||||||
|
|
||||||
letmacro :: PandocMonad m => LP m (Text, Macro)
|
|
||||||
letmacro = do
|
|
||||||
controlSeq "let"
|
|
||||||
(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 $
|
|
||||||
-- we use withVerbatimMode, because macros are to be expanded
|
|
||||||
-- at point of use, not point of definition
|
|
||||||
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
|
|
||||||
Tok _ (Arg i) _ <- satisfyTok isArgTok
|
|
||||||
return $ ArgNum i
|
|
||||||
|
|
||||||
argspecPattern :: PandocMonad m => LP m ArgSpec
|
|
||||||
argspecPattern =
|
|
||||||
Pattern <$> many1 (satisfyTok (\(Tok _ toktype' txt) ->
|
|
||||||
(toktype' == Symbol || toktype' == Word) &&
|
|
||||||
(txt /= "{" && txt /= "\\" && txt /= "}")))
|
|
||||||
|
|
||||||
newcommand :: PandocMonad m => LP m (Text, Macro)
|
|
||||||
newcommand = do
|
|
||||||
pos <- getPosition
|
|
||||||
Tok _ (CtrlSeq mtype) _ <- controlSeq "newcommand" <|>
|
|
||||||
controlSeq "renewcommand" <|>
|
|
||||||
controlSeq "providecommand" <|>
|
|
||||||
controlSeq "DeclareMathOperator" <|>
|
|
||||||
controlSeq "DeclareRobustCommand"
|
|
||||||
withVerbatimMode $ do
|
|
||||||
Tok _ (CtrlSeq name) txt <- do
|
|
||||||
optional (symbol '*')
|
|
||||||
anyControlSeq <|>
|
|
||||||
(symbol '{' *> spaces *> anyControlSeq <* spaces <* symbol '}')
|
|
||||||
spaces
|
|
||||||
numargs <- option 0 $ try bracketedNum
|
|
||||||
let argspecs = map ArgNum [1..numargs]
|
|
||||||
spaces
|
|
||||||
optarg <- option Nothing $ Just <$> try bracketedToks
|
|
||||||
spaces
|
|
||||||
contents' <- bracedOrToken
|
|
||||||
let contents =
|
|
||||||
case mtype of
|
|
||||||
"DeclareMathOperator" ->
|
|
||||||
Tok pos (CtrlSeq "mathop") "\\mathop"
|
|
||||||
: Tok pos Symbol "{"
|
|
||||||
: Tok pos (CtrlSeq "mathrm") "\\mathrm"
|
|
||||||
: Tok pos Symbol "{"
|
|
||||||
: (contents' ++
|
|
||||||
[ Tok pos Symbol "}", Tok pos Symbol "}" ])
|
|
||||||
_ -> contents'
|
|
||||||
macros <- sMacros <$> getState
|
|
||||||
case M.lookup name macros of
|
|
||||||
Just macro
|
|
||||||
| mtype == "newcommand" -> do
|
|
||||||
report $ MacroAlreadyDefined txt pos
|
|
||||||
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
|
|
||||||
pos <- getPosition
|
|
||||||
Tok _ (CtrlSeq mtype) _ <- controlSeq "newenvironment" <|>
|
|
||||||
controlSeq "renewenvironment" <|>
|
|
||||||
controlSeq "provideenvironment"
|
|
||||||
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
|
|
||||||
macros <- sMacros <$> getState
|
|
||||||
case M.lookup name macros of
|
|
||||||
Just _
|
|
||||||
| mtype == "newenvironment" -> do
|
|
||||||
report $ MacroAlreadyDefined name pos
|
|
||||||
return Nothing
|
|
||||||
| mtype == "provideenvironment" ->
|
|
||||||
return Nothing
|
|
||||||
_ -> return $ Just (name,
|
|
||||||
Macro ExpandWhenUsed argspecs optarg startcontents,
|
|
||||||
Macro ExpandWhenUsed [] Nothing endcontents)
|
|
||||||
|
|
||||||
bracketedNum :: PandocMonad m => LP m Int
|
|
||||||
bracketedNum = do
|
|
||||||
ds <- untokenize <$> bracketedToks
|
|
||||||
case safeRead ds of
|
|
||||||
Just i -> return i
|
|
||||||
_ -> return 0
|
|
||||||
|
|
||||||
looseItem :: PandocMonad m => LP m Blocks
|
looseItem :: PandocMonad m => LP m Blocks
|
||||||
looseItem = do
|
looseItem = do
|
||||||
inListItem <- sInListItem <$> getState
|
inListItem <- sInListItem <$> getState
|
||||||
|
|
153
src/Text/Pandoc/Readers/LaTeX/Macro.hs
Normal file
153
src/Text/Pandoc/Readers/LaTeX/Macro.hs
Normal file
|
@ -0,0 +1,153 @@
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
module Text.Pandoc.Readers.LaTeX.Macro
|
||||||
|
( macroDef
|
||||||
|
)
|
||||||
|
where
|
||||||
|
import Text.Pandoc.Extensions (Extension(..))
|
||||||
|
import Text.Pandoc.Logging (LogMessage(MacroAlreadyDefined))
|
||||||
|
import Text.Pandoc.Readers.LaTeX.Parsing
|
||||||
|
import Text.Pandoc.Readers.LaTeX.Types
|
||||||
|
import Text.Pandoc.Class
|
||||||
|
import Text.Pandoc.Shared (safeRead)
|
||||||
|
import Text.Pandoc.Parsing hiding (blankline, mathDisplay, mathInline,
|
||||||
|
optional, space, spaces, withRaw, (<|>))
|
||||||
|
import Control.Applicative ((<|>), optional)
|
||||||
|
import qualified Data.Map as M
|
||||||
|
import Data.Text (Text)
|
||||||
|
|
||||||
|
macroDef :: (PandocMonad m, Monoid a) => (Text -> a) -> LP m a
|
||||||
|
macroDef constructor = do
|
||||||
|
(_, s) <- withRaw (commandDef <|> environmentDef)
|
||||||
|
(constructor (untokenize s) <$
|
||||||
|
guardDisabled Ext_latex_macros)
|
||||||
|
<|> return mempty
|
||||||
|
where commandDef = do
|
||||||
|
(name, macro') <- newcommand <|> letmacro <|> defmacro
|
||||||
|
guardDisabled Ext_latex_macros <|>
|
||||||
|
updateState (\s -> s{ sMacros = M.insert name macro' (sMacros s) })
|
||||||
|
environmentDef = do
|
||||||
|
mbenv <- newenvironment
|
||||||
|
case mbenv of
|
||||||
|
Nothing -> return ()
|
||||||
|
Just (name, macro1, macro2) ->
|
||||||
|
guardDisabled Ext_latex_macros <|>
|
||||||
|
do updateState $ \s -> s{ sMacros =
|
||||||
|
M.insert name macro1 (sMacros s) }
|
||||||
|
updateState $ \s -> s{ sMacros =
|
||||||
|
M.insert ("end" <> name) macro2 (sMacros s) }
|
||||||
|
-- @\newenvironment{envname}[n-args][default]{begin}{end}@
|
||||||
|
-- is equivalent to
|
||||||
|
-- @\newcommand{\envname}[n-args][default]{begin}@
|
||||||
|
-- @\newcommand{\endenvname}@
|
||||||
|
|
||||||
|
letmacro :: PandocMonad m => LP m (Text, Macro)
|
||||||
|
letmacro = do
|
||||||
|
controlSeq "let"
|
||||||
|
(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 $
|
||||||
|
-- we use withVerbatimMode, because macros are to be expanded
|
||||||
|
-- at point of use, not point of definition
|
||||||
|
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
|
||||||
|
Tok _ (Arg i) _ <- satisfyTok isArgTok
|
||||||
|
return $ ArgNum i
|
||||||
|
|
||||||
|
argspecPattern :: PandocMonad m => LP m ArgSpec
|
||||||
|
argspecPattern =
|
||||||
|
Pattern <$> many1 (satisfyTok (\(Tok _ toktype' txt) ->
|
||||||
|
(toktype' == Symbol || toktype' == Word) &&
|
||||||
|
(txt /= "{" && txt /= "\\" && txt /= "}")))
|
||||||
|
|
||||||
|
newcommand :: PandocMonad m => LP m (Text, Macro)
|
||||||
|
newcommand = do
|
||||||
|
pos <- getPosition
|
||||||
|
Tok _ (CtrlSeq mtype) _ <- controlSeq "newcommand" <|>
|
||||||
|
controlSeq "renewcommand" <|>
|
||||||
|
controlSeq "providecommand" <|>
|
||||||
|
controlSeq "DeclareMathOperator" <|>
|
||||||
|
controlSeq "DeclareRobustCommand"
|
||||||
|
withVerbatimMode $ do
|
||||||
|
Tok _ (CtrlSeq name) txt <- do
|
||||||
|
optional (symbol '*')
|
||||||
|
anyControlSeq <|>
|
||||||
|
(symbol '{' *> spaces *> anyControlSeq <* spaces <* symbol '}')
|
||||||
|
spaces
|
||||||
|
numargs <- option 0 $ try bracketedNum
|
||||||
|
let argspecs = map ArgNum [1..numargs]
|
||||||
|
spaces
|
||||||
|
optarg <- option Nothing $ Just <$> try bracketedToks
|
||||||
|
spaces
|
||||||
|
contents' <- bracedOrToken
|
||||||
|
let contents =
|
||||||
|
case mtype of
|
||||||
|
"DeclareMathOperator" ->
|
||||||
|
Tok pos (CtrlSeq "mathop") "\\mathop"
|
||||||
|
: Tok pos Symbol "{"
|
||||||
|
: Tok pos (CtrlSeq "mathrm") "\\mathrm"
|
||||||
|
: Tok pos Symbol "{"
|
||||||
|
: (contents' ++
|
||||||
|
[ Tok pos Symbol "}", Tok pos Symbol "}" ])
|
||||||
|
_ -> contents'
|
||||||
|
macros <- sMacros <$> getState
|
||||||
|
case M.lookup name macros of
|
||||||
|
Just macro
|
||||||
|
| mtype == "newcommand" -> do
|
||||||
|
report $ MacroAlreadyDefined txt pos
|
||||||
|
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
|
||||||
|
pos <- getPosition
|
||||||
|
Tok _ (CtrlSeq mtype) _ <- controlSeq "newenvironment" <|>
|
||||||
|
controlSeq "renewenvironment" <|>
|
||||||
|
controlSeq "provideenvironment"
|
||||||
|
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
|
||||||
|
macros <- sMacros <$> getState
|
||||||
|
case M.lookup name macros of
|
||||||
|
Just _
|
||||||
|
| mtype == "newenvironment" -> do
|
||||||
|
report $ MacroAlreadyDefined name pos
|
||||||
|
return Nothing
|
||||||
|
| mtype == "provideenvironment" ->
|
||||||
|
return Nothing
|
||||||
|
_ -> return $ Just (name,
|
||||||
|
Macro ExpandWhenUsed argspecs optarg startcontents,
|
||||||
|
Macro ExpandWhenUsed [] Nothing endcontents)
|
||||||
|
|
||||||
|
bracketedNum :: PandocMonad m => LP m Int
|
||||||
|
bracketedNum = do
|
||||||
|
ds <- untokenize <$> bracketedToks
|
||||||
|
case safeRead ds of
|
||||||
|
Just i -> return i
|
||||||
|
_ -> return 0
|
Loading…
Reference in a new issue