From 2654da38237a981777ed57e4af64781e3773bf01 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 25 Jul 2012 20:42:15 -0700 Subject: Moved stateApplyMacros, stateIndentedCodeClasses to ReaderOptions. --- src/Text/Pandoc/Options.hs | 23 ++++++++++++++--------- src/Text/Pandoc/Parsing.hs | 8 ++------ src/Text/Pandoc/Readers/Markdown.hs | 4 ++-- src/pandoc.hs | 6 +++--- 4 files changed, 21 insertions(+), 20 deletions(-) (limited to 'src') diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 64c3709e1..aef18e7eb 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -62,17 +62,22 @@ data ReaderOptions = ReaderOptions{ -- - before numerial is en-dash , readerLiterateHaskell :: Bool -- ^ Interpret as literate Haskell , readerCitations :: [String] -- ^ List of available citations + , readerApplyMacros :: Bool -- ^ Apply macros to TeX math + , readerIndentedCodeClasses :: [String] -- ^ Default classes for + -- indented code blocks } deriving (Show, Read) instance Default ReaderOptions where def = ReaderOptions{ - readerExtensions = Set.fromList [minBound..maxBound] - , readerSmart = False - , readerStrict = False - , readerParseRaw = False - , readerColumns = 80 - , readerTabStop = 4 - , readerOldDashes = False - , readerLiterateHaskell = False - , readerCitations = [] + readerExtensions = Set.fromList [minBound..maxBound] + , readerSmart = False + , readerStrict = False + , readerParseRaw = False + , readerColumns = 80 + , readerTabStop = 4 + , readerOldDashes = False + , readerLiterateHaskell = False + , readerCitations = [] + , readerApplyMacros = True + , readerIndentedCodeClasses = [] } diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index 997316180..2ac902211 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -698,11 +698,9 @@ data ParserState = ParserState stateAuthors :: [[Inline]], -- ^ Authors of document stateDate :: [Inline], -- ^ Date of document stateHeaderTable :: [HeaderType], -- ^ Ordered list of header types used - 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 - stateApplyMacros :: Bool, -- ^ Apply LaTeX macros? stateMacros :: [Macro], -- ^ List of macros defined so far stateRstDefaultRole :: String -- ^ Current rST default interpreted text role } @@ -724,11 +722,9 @@ defaultParserState = stateAuthors = [], stateDate = [], stateHeaderTable = [], - stateIndentedCodeClasses = [], stateNextExample = 1, stateExamples = M.empty, stateHasChapters = False, - stateApplyMacros = True, stateMacros = [], stateRstDefaultRole = "title-reference"} @@ -916,7 +912,7 @@ emDashOld = do -- | Parse a \newcommand or \renewcommand macro definition. macro :: Parsec [Char] ParserState Block macro = do - apply <- stateApplyMacros `fmap` getState + apply <- getOption readerApplyMacros inp <- getInput case parseMacroDefinitions inp of ([], _) -> mzero @@ -931,7 +927,7 @@ macro = do -- | Apply current macros to string. applyMacros' :: String -> Parsec [Char] ParserState String applyMacros' target = do - apply <- liftM stateApplyMacros getState + apply <- getOption readerApplyMacros if apply then do macros <- liftM stateMacros getState return $ applyMacros macros target diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index f6f23faed..91f8e7c63 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -444,8 +444,8 @@ codeBlockIndented = do l <- indentedLine return $ b ++ l)) optional blanklines - st <- getState - return $ CodeBlock ("", stateIndentedCodeClasses st, []) $ + classes <- getOption readerIndentedCodeClasses + return $ CodeBlock ("", classes, []) $ stripTrailingNewlines $ concat contents lhsCodeBlock :: Parser [Char] ParserState Block diff --git a/src/pandoc.hs b/src/pandoc.hs index a0404d9e6..725f13e09 100644 --- a/src/pandoc.hs +++ b/src/pandoc.hs @@ -948,9 +948,9 @@ main = do "+lhs" `isSuffixOf` readerName' || lhsExtension sources , readerCitations = map CSL.refId refs - }, - stateIndentedCodeClasses = codeBlockClasses, - stateApplyMacros = not laTeXOutput + , readerIndentedCodeClasses = codeBlockClasses + , readerApplyMacros = not laTeXOutput + } } let writerOptions = def { writerStandalone = standalone', -- cgit v1.2.3