Moved ParseRaw from ParserState to ReaderOptions.

This commit is contained in:
John MacFarlane 2012-07-25 11:43:56 -07:00
parent 8b380a464e
commit ef0619cc6d
7 changed files with 28 additions and 24 deletions

View file

@ -51,9 +51,10 @@ data Extension = Footnotes
deriving (Show, Read, Enum, Eq, Ord, Bounded)
data ReaderOptions = ReaderOptions{
readerExtensions :: Set Extension
, readerSmart :: Bool
, readerStrict :: Bool -- FOR TRANSITION ONLY
readerExtensions :: Set Extension -- ^ Syntax extensions
, readerSmart :: Bool -- ^ Smart punctuation
, readerStrict :: Bool -- ^ FOR TRANSITION ONLY
, readerParseRaw :: Bool -- ^ Parse raw HTML, LaTeX
} deriving (Show, Read)
instance Default ReaderOptions
@ -61,4 +62,5 @@ instance Default ReaderOptions
readerExtensions = Set.fromList [minBound..maxBound]
, readerSmart = False
, readerStrict = False
, readerParseRaw = False
}

View file

@ -689,7 +689,6 @@ testStringWith parser str = UTF8.putStrLn $ show $
-- | Parsing options.
data ParserState = ParserState
{ stateOptions :: ReaderOptions, -- ^ User options
stateParseRaw :: Bool, -- ^ Parse raw HTML and LaTeX?
stateParserContext :: ParserContext, -- ^ Inside list?
stateQuoteContext :: QuoteContext, -- ^ Inside quoted environment?
stateMaxNestingLevel :: Int, -- ^ Max # of nested Strong/Emph
@ -724,7 +723,6 @@ instance Default ParserState where
defaultParserState :: ParserState
defaultParserState =
ParserState { stateOptions = def,
stateParseRaw = False,
stateParserContext = NullState,
stateQuoteContext = NoQuote,
stateMaxNestingLevel = 6,

View file

@ -195,8 +195,8 @@ pRawTag = do
pRawHtmlBlock :: TagParser [Block]
pRawHtmlBlock = do
raw <- pHtmlBlock "script" <|> pHtmlBlock "style" <|> pRawTag
state <- getState
if stateParseRaw state && not (null raw)
parseRaw <- getOption readerParseRaw
if parseRaw && not (null raw)
then return [RawBlock "html" raw]
else return []
@ -380,8 +380,8 @@ pCode = try $ do
pRawHtmlInline :: TagParser [Inline]
pRawHtmlInline = do
result <- pSatisfy (tagComment (const True)) <|> pSatisfy isInlineTag
state <- getState
if stateParseRaw state
parseRaw <- getOption readerParseRaw
if parseRaw
then return [RawInline "html" $ renderTags' [result]]
else return []

View file

@ -35,6 +35,7 @@ module Text.Pandoc.Readers.LaTeX ( readLaTeX,
import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding ((<|>), many, optional, space)
import qualified Text.Pandoc.UTF8 as UTF8
import Data.Char ( chr, ord )
@ -230,14 +231,14 @@ ignoreInlines name = (name, doraw <|> (mempty <$ optargs))
where optargs = skipopts *> skipMany (try $ optional sp *> braced)
contseq = '\\':name
doraw = (rawInline "latex" . (contseq ++) . snd) <$>
(getState >>= guard . stateParseRaw >> (withRaw optargs))
(getOption readerParseRaw >>= guard >> (withRaw optargs))
ignoreBlocks :: String -> (String, LP Blocks)
ignoreBlocks name = (name, doraw <|> (mempty <$ optargs))
where optargs = skipopts *> skipMany (try $ optional sp *> braced)
contseq = '\\':name
doraw = (rawBlock "latex" . (contseq ++) . snd) <$>
(getState >>= guard . stateParseRaw >> (withRaw optargs))
(getOption readerParseRaw >>= guard >> (withRaw optargs))
blockCommands :: M.Map String (LP Blocks)
blockCommands = M.fromList $
@ -321,7 +322,7 @@ inlineCommand :: LP Inlines
inlineCommand = try $ do
name <- anyControlSeq
guard $ not $ isBlockCommand name
parseRaw <- stateParseRaw `fmap` getState
parseRaw <- getOption readerParseRaw
star <- option "" (string "*")
let name' = name ++ star
let rawargs = withRaw (skipopts *> option "" dimenarg
@ -336,7 +337,7 @@ inlineCommand = try $ do
Nothing -> raw
unlessParseRaw :: LP ()
unlessParseRaw = getState >>= guard . not . stateParseRaw
unlessParseRaw = getOption readerParseRaw >>= guard . not
isBlockCommand :: String -> Bool
isBlockCommand s = maybe False (const True) $ M.lookup s blockCommands
@ -660,7 +661,7 @@ environment = do
rawEnv :: String -> LP Blocks
rawEnv name = do
let addBegin x = "\\begin{" ++ name ++ "}" ++ x
parseRaw <- stateParseRaw `fmap` getState
parseRaw <- getOption readerParseRaw
if parseRaw
then (rawBlock "latex" . addBegin) <$>
(withRaw (env name blocks) >>= applyMacros' . snd)

View file

@ -176,7 +176,9 @@ titleBlock = try $ do
parseMarkdown :: Parser [Char] ParserState Pandoc
parseMarkdown = do
-- markdown allows raw HTML
updateState (\state -> state { stateParseRaw = True })
updateState $ \state -> state { stateOptions =
let oldOpts = stateOptions state in
oldOpts{ readerParseRaw = True } }
startPos <- getPosition
-- go through once just to get list of reference keys and notes
-- docMinusKeys is the raw document with blanks where the keys/notes were...

View file

@ -79,9 +79,9 @@ parseTextile :: Parser [Char] ParserState Pandoc
parseTextile = do
-- textile allows raw HTML and does smart punctuation by default
oldOpts <- stateOptions `fmap` getState
updateState $ \state -> state { stateParseRaw = True
, stateOptions = oldOpts{ readerSmart = True }
}
updateState $ \state -> state{ stateOptions = oldOpts{ readerSmart = True
, readerParseRaw = True
} }
many blankline
startPos <- getPosition
-- go through once just to get list of reference keys and notes

View file

@ -936,18 +936,19 @@ main = do
then "."
else takeDirectory (head sources)
let startParserState = def{ stateParseRaw = parseRaw,
stateTabStop = tabStop,
let startParserState = def{ stateTabStop = tabStop,
stateLiterateHaskell = "+lhs" `isSuffixOf` readerName' ||
lhsExtension sources,
stateStandalone = standalone',
stateCitations = map CSL.refId refs,
stateOldDashes = oldDashes,
stateColumns = columns,
stateOptions = def{ readerStrict = strict
, readerSmart = smart ||
(texLigatures &&
(laTeXOutput || writerName' == "context")) },
stateOptions = def{
readerStrict = strict
, readerSmart = smart || (texLigatures &&
(laTeXOutput || writerName' == "context"))
, readerParseRaw = parseRaw
},
stateIndentedCodeClasses = codeBlockClasses,
stateApplyMacros = not laTeXOutput
}