Process LaTeX macros in markdown, and apply to TeX math.
Example: \newcommand{\plus}[2]{#1 + #2} $\plus{3}{4}$ yields: 3+4
This commit is contained in:
parent
3b1d68b2bc
commit
6b722d1b45
4 changed files with 39 additions and 8 deletions
|
@ -157,7 +157,7 @@ Library
|
||||||
process >= 1, directory >= 1,
|
process >= 1, directory >= 1,
|
||||||
bytestring >= 0.9, zip-archive >= 0.1.1.4,
|
bytestring >= 0.9, zip-archive >= 0.1.1.4,
|
||||||
utf8-string >= 0.3, old-time >= 1,
|
utf8-string >= 0.3, old-time >= 1,
|
||||||
HTTP >= 4000.0.5, texmath >= 0.3, xml >= 1.3.5 && < 1.4,
|
HTTP >= 4000.0.5, texmath >= 0.4, xml >= 1.3.5 && < 1.4,
|
||||||
random, extensible-exceptions
|
random, extensible-exceptions
|
||||||
if impl(ghc >= 6.10)
|
if impl(ghc >= 6.10)
|
||||||
Build-depends: base >= 4 && < 5, syb
|
Build-depends: base >= 4 && < 5, syb
|
||||||
|
|
|
@ -79,6 +79,7 @@ import Network.URI ( parseURI, URI (..), isAllowedInURI )
|
||||||
import Control.Monad ( join, liftM )
|
import Control.Monad ( join, liftM )
|
||||||
import Text.Pandoc.Shared
|
import Text.Pandoc.Shared
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
import Text.TeXMath.Macros (Macro)
|
||||||
|
|
||||||
-- | Like >>, but returns the operation on the left.
|
-- | Like >>, but returns the operation on the left.
|
||||||
-- (Suggested by Tillmann Rendel on Haskell-cafe list.)
|
-- (Suggested by Tillmann Rendel on Haskell-cafe list.)
|
||||||
|
@ -602,7 +603,9 @@ data ParserState = ParserState
|
||||||
stateIndentedCodeClasses :: [String], -- ^ Classes to use for indented code blocks
|
stateIndentedCodeClasses :: [String], -- ^ Classes to use for indented code blocks
|
||||||
stateNextExample :: Int, -- ^ Number of next example
|
stateNextExample :: Int, -- ^ Number of next example
|
||||||
stateExamples :: M.Map String Int, -- ^ Map from example labels to numbers
|
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
|
deriving Show
|
||||||
|
|
||||||
|
@ -630,7 +633,9 @@ defaultParserState =
|
||||||
stateIndentedCodeClasses = [],
|
stateIndentedCodeClasses = [],
|
||||||
stateNextExample = 1,
|
stateNextExample = 1,
|
||||||
stateExamples = M.empty,
|
stateExamples = M.empty,
|
||||||
stateHasChapters = False }
|
stateHasChapters = False,
|
||||||
|
stateApplyMacros = True,
|
||||||
|
stateMacros = []}
|
||||||
|
|
||||||
data HeaderType
|
data HeaderType
|
||||||
= SingleHeader Char -- ^ Single line of characters underneath
|
= SingleHeader Char -- ^ Single line of characters underneath
|
||||||
|
|
|
@ -46,7 +46,8 @@ import Text.Pandoc.Readers.HTML ( rawHtmlBlock, anyHtmlBlockTag,
|
||||||
htmlBlockElement, htmlComment, unsanitaryURI )
|
htmlBlockElement, htmlComment, unsanitaryURI )
|
||||||
import Text.Pandoc.CharacterReferences ( decodeCharacterReferences )
|
import Text.Pandoc.CharacterReferences ( decodeCharacterReferences )
|
||||||
import Text.ParserCombinators.Parsec
|
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.
|
-- | Read markdown from an input string and return a Pandoc document.
|
||||||
readMarkdown :: ParserState -- ^ Parser state, including options for parser
|
readMarkdown :: ParserState -- ^ Parser state, including options for parser
|
||||||
|
@ -284,6 +285,7 @@ block = do
|
||||||
, plain
|
, plain
|
||||||
, nullBlock ]
|
, nullBlock ]
|
||||||
else [ codeBlockDelimited
|
else [ codeBlockDelimited
|
||||||
|
, macro
|
||||||
, header
|
, header
|
||||||
, table
|
, table
|
||||||
, codeBlockIndented
|
, codeBlockIndented
|
||||||
|
@ -867,6 +869,29 @@ table = multilineTable False <|> simpleTable True <|>
|
||||||
simpleTable False <|> multilineTable True <|>
|
simpleTable False <|> multilineTable True <|>
|
||||||
gridTable False <|> gridTable True <?> "table"
|
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
|
-- inline
|
||||||
--
|
--
|
||||||
|
@ -969,8 +994,8 @@ mathChunk = do char '\\'
|
||||||
<|> many1 (noneOf " \t\n\\$")
|
<|> many1 (noneOf " \t\n\\$")
|
||||||
|
|
||||||
math :: GenParser Char ParserState Inline
|
math :: GenParser Char ParserState Inline
|
||||||
math = (mathDisplay >>= return . Math DisplayMath)
|
math = (mathDisplay >>= applyMacros' >>= return . Math DisplayMath)
|
||||||
<|> (mathInline >>= return . Math InlineMath)
|
<|> (mathInline >>= applyMacros' >>= return . Math InlineMath)
|
||||||
|
|
||||||
mathDisplay :: GenParser Char ParserState String
|
mathDisplay :: GenParser Char ParserState String
|
||||||
mathDisplay = try $ do
|
mathDisplay = try $ do
|
||||||
|
|
|
@ -786,10 +786,11 @@ main = do
|
||||||
stateCitations = map citeKey refs,
|
stateCitations = map citeKey refs,
|
||||||
#endif
|
#endif
|
||||||
stateSmart = smart || writerName' `elem`
|
stateSmart = smart || writerName' `elem`
|
||||||
["latex", "context", "man"],
|
["latex", "context", "latex+lhs", "man"],
|
||||||
stateColumns = columns,
|
stateColumns = columns,
|
||||||
stateStrict = strict,
|
stateStrict = strict,
|
||||||
stateIndentedCodeClasses = codeBlockClasses }
|
stateIndentedCodeClasses = codeBlockClasses,
|
||||||
|
stateApplyMacros = writerName' `notElem` ["latex", "latex+lhs"] }
|
||||||
|
|
||||||
let writerOptions = WriterOptions { writerStandalone = standalone',
|
let writerOptions = WriterOptions { writerStandalone = standalone',
|
||||||
writerTemplate = if null template
|
writerTemplate = if null template
|
||||||
|
|
Loading…
Reference in a new issue