Moved stateApplyMacros, stateIndentedCodeClasses to ReaderOptions.
This commit is contained in:
parent
070b968ae0
commit
2654da3823
4 changed files with 21 additions and 20 deletions
|
@ -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 = []
|
||||
}
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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',
|
||||
|
|
Loading…
Reference in a new issue