diff options
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r-- | src/Text/Pandoc/Parsing.hs | 9 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 31 |
2 files changed, 35 insertions, 5 deletions
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index 3678fc22a..dce99fd75 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -79,6 +79,7 @@ import Network.URI ( parseURI, URI (..), isAllowedInURI ) import Control.Monad ( join, liftM ) import Text.Pandoc.Shared import qualified Data.Map as M +import Text.TeXMath.Macros (Macro) -- | Like >>, but returns the operation on the left. -- (Suggested by Tillmann Rendel on Haskell-cafe list.) @@ -602,7 +603,9 @@ data ParserState = ParserState stateIndentedCodeClasses :: [String], -- ^ Classes to use for indented code blocks stateNextExample :: Int, -- ^ Number of next example stateExamples :: M.Map String Int, -- ^ Map from example labels to numbers - stateHasChapters :: Bool -- ^ True if \chapter encountered + stateHasChapters :: Bool, -- ^ True if \chapter encountered + stateApplyMacros :: Bool, -- ^ Apply LaTeX macros? + stateMacros :: [Macro] -- ^ List of macros defined so far } deriving Show @@ -630,7 +633,9 @@ defaultParserState = stateIndentedCodeClasses = [], stateNextExample = 1, stateExamples = M.empty, - stateHasChapters = False } + stateHasChapters = False, + stateApplyMacros = True, + stateMacros = []} data HeaderType = SingleHeader Char -- ^ Single line of characters underneath diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 33fb3d8e6..0f10d2b65 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -46,7 +46,8 @@ import Text.Pandoc.Readers.HTML ( rawHtmlBlock, anyHtmlBlockTag, htmlBlockElement, htmlComment, unsanitaryURI ) import Text.Pandoc.CharacterReferences ( decodeCharacterReferences ) import Text.ParserCombinators.Parsec -import Control.Monad (when, liftM, unless) +import Control.Monad (when, liftM, unless, guard) +import Text.TeXMath.Macros (applyMacros, Macro, pMacroDefinition) -- | Read markdown from an input string and return a Pandoc document. readMarkdown :: ParserState -- ^ Parser state, including options for parser @@ -284,6 +285,7 @@ block = do , plain , nullBlock ] else [ codeBlockDelimited + , macro , header , table , codeBlockIndented @@ -867,6 +869,29 @@ table = multilineTable False <|> simpleTable True <|> simpleTable False <|> multilineTable True <|> gridTable False <|> gridTable True <?> "table" +-- +-- Macros +-- + +-- | Parse a \newcommand or \renewcommand macro definition. +macro :: GenParser Char ParserState Block +macro = getState >>= guard . stateApplyMacros >> + pMacroDefinition >>= addMacro >> return Null + +-- | Add a macro to the list of macros in state. +addMacro :: Macro -> GenParser Char ParserState () +addMacro m = do + updateState $ \st -> st{ stateMacros = m : stateMacros st } + +-- | Apply current macros to string. +applyMacros' :: String -> GenParser Char ParserState String +applyMacros' target = do + apply <- liftM stateApplyMacros getState + if apply + then do macros <- liftM stateMacros getState + return $ applyMacros macros target + else return target + -- -- inline -- @@ -969,8 +994,8 @@ mathChunk = do char '\\' <|> many1 (noneOf " \t\n\\$") math :: GenParser Char ParserState Inline -math = (mathDisplay >>= return . Math DisplayMath) - <|> (mathInline >>= return . Math InlineMath) +math = (mathDisplay >>= applyMacros' >>= return . Math DisplayMath) + <|> (mathInline >>= applyMacros' >>= return . Math InlineMath) mathDisplay :: GenParser Char ParserState String mathDisplay = try $ do |