Text.Pandoc.Parsing: Added getOption.

This commit is contained in:
John MacFarlane 2012-07-25 11:27:25 -07:00
parent dfa19061ab
commit 8b380a464e

View file

@ -61,6 +61,7 @@ module Text.Pandoc.Parsing ( (>>~),
readWith, readWith,
testStringWith, testStringWith,
ParserState (..), ParserState (..),
getOption,
defaultParserState, defaultParserState,
HeaderType (..), HeaderType (..),
ParserContext (..), ParserContext (..),
@ -390,9 +391,7 @@ nullBlock = anyChar >> return Null
-- | Fail if reader is in strict markdown syntax mode. -- | Fail if reader is in strict markdown syntax mode.
failIfStrict :: Parsec [a] ParserState () failIfStrict :: Parsec [a] ParserState ()
failIfStrict = do failIfStrict = getOption readerStrict >>= guard . not
state <- getState
if readerStrict (stateOptions state) then fail "strict mode" else return ()
-- | Fail unless we're in literate haskell mode. -- | Fail unless we're in literate haskell mode.
failUnlessLHS :: Parsec [tok] ParserState () failUnlessLHS :: Parsec [tok] ParserState ()
@ -750,6 +749,9 @@ defaultParserState =
stateMacros = [], stateMacros = [],
stateRstDefaultRole = "title-reference"} stateRstDefaultRole = "title-reference"}
getOption :: (ReaderOptions -> a) -> Parser [t] ParserState a
getOption f = (f . stateOptions) `fmap` getState
data HeaderType data HeaderType
= SingleHeader Char -- ^ Single line of characters underneath = SingleHeader Char -- ^ Single line of characters underneath
| DoubleHeader Char -- ^ Lines of characters above and below | DoubleHeader Char -- ^ Lines of characters above and below
@ -795,7 +797,7 @@ lookupKeySrc table key = case M.lookup key table of
-- | Fail unless we're in "smart typography" mode. -- | Fail unless we're in "smart typography" mode.
failUnlessSmart :: Parsec [tok] ParserState () failUnlessSmart :: Parsec [tok] ParserState ()
failUnlessSmart = getState >>= guard . readerSmart . stateOptions failUnlessSmart = getOption readerSmart >>= guard
smartPunctuation :: Parsec [Char] ParserState Inline smartPunctuation :: Parsec [Char] ParserState Inline
-> Parsec [Char] ParserState Inline -> Parsec [Char] ParserState Inline