aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2011-01-04 19:12:33 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2011-01-04 19:12:33 -0800
commitfcbe1e95ebe170aadc6eadd6797ddf7fbb286ef2 (patch)
tree22436bbf6a9e000d7b1fa0b9327c30a35d0c0e57 /src
parent3e61333af0f5ac1cdb045bdab0293f03e2e1e39e (diff)
downloadpandoc-fcbe1e95ebe170aadc6eadd6797ddf7fbb286ef2.tar.gz
Moved 'macro' and 'applyMacros'' from markdown reader to Parsing.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Parsing.hs29
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs24
2 files changed, 27 insertions, 26 deletions
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 3035a2319..bcdb053c4 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -68,7 +68,9 @@ module Text.Pandoc.Parsing ( (>>~),
toKey,
fromKey,
lookupKeySrc,
- smartPunctuation )
+ smartPunctuation,
+ macro,
+ applyMacros' )
where
import Text.Pandoc.Definition
@@ -82,7 +84,7 @@ import Network.URI ( parseURI, URI (..), isAllowedInURI )
import Control.Monad ( join, liftM, guard )
import Text.Pandoc.Shared
import qualified Data.Map as M
-import Text.TeXMath.Macros (Macro)
+import Text.TeXMath.Macros (applyMacros, Macro, pMacroDefinition)
-- | Like >>, but returns the operation on the left.
-- (Suggested by Tillmann Rendel on Haskell-cafe list.)
@@ -781,3 +783,26 @@ emDash = do
try (charOrRef "—") <|> (oneOfStrings ["---", "--"] >> return '—')
return EmDash
+--
+-- Macros
+--
+
+-- | Parse a \newcommand or \renewcommand macro definition.
+macro :: GenParser Char ParserState Block
+macro = getState >>= guard . stateApplyMacros >>
+ pMacroDefinition >>= addMacro >> blanklines >> 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
+
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index feeb1a69c..2c8bef063 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -44,7 +44,6 @@ import Text.Pandoc.Readers.HTML ( htmlTag, htmlInBalanced, isInlineTag, isBlockT
import Text.Pandoc.CharacterReferences ( decodeCharacterReferences )
import Text.ParserCombinators.Parsec
import Control.Monad (when, liftM, guard)
-import Text.TeXMath.Macros (applyMacros, Macro, pMacroDefinition)
import Text.HTML.TagSoup
import Text.HTML.TagSoup.Match (tagOpen)
@@ -871,29 +870,6 @@ 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 >> blanklines >> 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
--