Options -> ReaderOptions.

Better to keep reader and writer options separate.
This commit is contained in:
John MacFarlane 2012-07-25 11:08:06 -07:00
parent da3702357d
commit dfa19061ab
7 changed files with 29 additions and 29 deletions

View file

@ -15,7 +15,7 @@ markdown = readMarkdown defaultParserState{ stateStandalone = True }
markdownSmart :: String -> Pandoc
markdownSmart = readMarkdown defaultParserState{ stateOptions =
let oldOpts = stateOptions defaultParserState in
oldOpts { optionSmart = True } }
oldOpts { readerSmart = True } }
infix 4 =:
(=:) :: ToString c

View file

@ -29,7 +29,7 @@ Data structures and functions for representing parser and writer
options.
-}
module Text.Pandoc.Options ( Extension(..)
, Options(..)
, ReaderOptions(..)
) where
import Data.Set (Set)
import qualified Data.Set as Set
@ -50,15 +50,15 @@ data Extension = Footnotes
| Significant_bullets
deriving (Show, Read, Enum, Eq, Ord, Bounded)
data Options = Options{
optionExtensions :: Set Extension
, optionSmart :: Bool
, optionStrict :: Bool -- FOR TRANSITION ONLY
data ReaderOptions = ReaderOptions{
readerExtensions :: Set Extension
, readerSmart :: Bool
, readerStrict :: Bool -- FOR TRANSITION ONLY
} deriving (Show, Read)
instance Default Options
where def = Options{
optionExtensions = Set.fromList [minBound..maxBound]
, optionSmart = False
, optionStrict = False
instance Default ReaderOptions
where def = ReaderOptions{
readerExtensions = Set.fromList [minBound..maxBound]
, readerSmart = False
, readerStrict = False
}

View file

@ -392,7 +392,7 @@ nullBlock = anyChar >> return Null
failIfStrict :: Parsec [a] ParserState ()
failIfStrict = do
state <- getState
if optionStrict (stateOptions state) then fail "strict mode" else return ()
if readerStrict (stateOptions state) then fail "strict mode" else return ()
-- | Fail unless we're in literate haskell mode.
failUnlessLHS :: Parsec [tok] ParserState ()
@ -689,7 +689,7 @@ testStringWith parser str = UTF8.putStrLn $ show $
-- | Parsing options.
data ParserState = ParserState
{ stateOptions :: Options, -- ^ User options
{ stateOptions :: ReaderOptions, -- ^ User options
stateParseRaw :: Bool, -- ^ Parse raw HTML and LaTeX?
stateParserContext :: ParserContext, -- ^ Inside list?
stateQuoteContext :: QuoteContext, -- ^ Inside quoted environment?
@ -795,7 +795,7 @@ lookupKeySrc table key = case M.lookup key table of
-- | Fail unless we're in "smart typography" mode.
failUnlessSmart :: Parsec [tok] ParserState ()
failUnlessSmart = getState >>= guard . optionSmart . stateOptions
failUnlessSmart = getState >>= guard . readerSmart . stateOptions
smartPunctuation :: Parsec [Char] ParserState Inline
-> Parsec [Char] ParserState Inline

View file

@ -126,7 +126,7 @@ pOrderedList :: TagParser [Block]
pOrderedList = try $ do
TagOpen _ attribs <- pSatisfy (~== TagOpen "ol" [])
st <- getState
let (start, style) = if optionStrict (stateOptions st)
let (start, style) = if readerStrict (stateOptions st)
then (1, DefaultStyle)
else (sta', sty')
where sta = fromMaybe "1" $
@ -281,7 +281,7 @@ pCodeBlock = try $ do
let attribsClasses = words $ fromMaybe "" $ lookup "class" attr
let attribsKV = filter (\(k,_) -> k /= "class" && k /= "id") attr
st <- getState
let attribs = if optionStrict (stateOptions st)
let attribs = if readerStrict (stateOptions st)
then ("",[],[])
else (attribsId, attribsClasses, attribsKV)
return [CodeBlock attribs result]

View file

@ -182,7 +182,7 @@ parseMarkdown = do
-- docMinusKeys is the raw document with blanks where the keys/notes were...
st <- getState
let firstPassParser = referenceKey
<|> (if optionStrict (stateOptions st) then mzero else noteBlock)
<|> (if readerStrict (stateOptions st) then mzero else noteBlock)
<|> liftM snd (withRaw codeBlockDelimited)
<|> lineClump
docMinusKeys <- liftM concat $ manyTill firstPassParser eof
@ -293,7 +293,7 @@ parseBlocks = manyTill block eof
block :: Parser [Char] ParserState Block
block = do
st <- getState
choice (if optionStrict (stateOptions st)
choice (if readerStrict (stateOptions st)
then [ header
, codeBlockIndented
, blockQuote
@ -534,7 +534,7 @@ anyOrderedListStart = try $ do
skipNonindentSpaces
notFollowedBy $ string "p." >> spaceChar >> digit -- page number
state <- getState
if optionStrict (stateOptions state)
if readerStrict (stateOptions state)
then do many1 digit
char '.'
spaceChar
@ -695,7 +695,7 @@ para = try $ do
option (Plain result) $ try $ do
newline
blanklines <|>
(getState >>= guard . optionStrict . stateOptions >>
(getState >>= guard . readerStrict . stateOptions >>
lookAhead (blockQuote <|> header) >> return "")
return $ Para result
@ -1009,7 +1009,7 @@ escapedChar' :: Parser [Char] ParserState Char
escapedChar' = try $ do
char '\\'
state <- getState
if optionStrict (stateOptions state)
if readerStrict (stateOptions state)
then oneOf "\\`*_{}[]()>#+-.!~"
else satisfy (not . isAlphaNum)
@ -1024,7 +1024,7 @@ escapedChar = do
ltSign :: Parser [Char] ParserState Inline
ltSign = do
st <- getState
if optionStrict (stateOptions st)
if readerStrict (stateOptions st)
then char '<'
else notFollowedBy' rawHtmlBlocks >> char '<' -- unless it starts html
return $ Str ['<']
@ -1160,7 +1160,7 @@ nonEndline = satisfy (/='\n')
str :: Parser [Char] ParserState Inline
str = do
smart <- (optionSmart . stateOptions) `fmap` getState
smart <- (readerSmart . stateOptions) `fmap` getState
a <- alphaNum
as <- many $ alphaNum
<|> (try $ char '_' >>~ lookAhead alphaNum)
@ -1201,7 +1201,7 @@ endline = try $ do
newline
notFollowedBy blankline
st <- getState
when (optionStrict (stateOptions st)) $ do
when (readerStrict (stateOptions st)) $ do
notFollowedBy emailBlockQuoteStart
notFollowedBy (char '#') -- atx header
-- parse potential list-starts differently if in a list:
@ -1283,7 +1283,7 @@ autoLink = try $ do
(orig, src) <- uri <|> emailAddress
char '>'
st <- getState
return $ if optionStrict (stateOptions st)
return $ if readerStrict (stateOptions st)
then Link [Str orig] (src, "")
else Link [Code ("",["url"],[]) orig] (src, "")
@ -1344,7 +1344,7 @@ inBrackets parser = do
rawHtmlInline :: Parser [Char] ParserState Inline
rawHtmlInline = do
st <- getState
(_,result) <- if optionStrict (stateOptions st)
(_,result) <- if readerStrict (stateOptions st)
then htmlTag (not . isTextTag)
else htmlTag isInlineTag
return $ RawInline "html" result

View file

@ -80,7 +80,7 @@ parseTextile = do
-- textile allows raw HTML and does smart punctuation by default
oldOpts <- stateOptions `fmap` getState
updateState $ \state -> state { stateParseRaw = True
, stateOptions = oldOpts{ optionSmart = True }
, stateOptions = oldOpts{ readerSmart = True }
}
many blankline
startPos <- getPosition

View file

@ -944,8 +944,8 @@ main = do
stateCitations = map CSL.refId refs,
stateOldDashes = oldDashes,
stateColumns = columns,
stateOptions = def{ optionStrict = strict
, optionSmart = smart ||
stateOptions = def{ readerStrict = strict
, readerSmart = smart ||
(texLigatures &&
(laTeXOutput || writerName' == "context")) },
stateIndentedCodeClasses = codeBlockClasses,