Factor out "returnState" into Parsing module
This commit is contained in:
parent
febe5112af
commit
9cd0bdb41a
3 changed files with 7 additions and 15 deletions
|
@ -66,6 +66,7 @@ module Text.Pandoc.Parsing ( anyLine,
|
|||
gridTableWith,
|
||||
readWith,
|
||||
returnWarnings,
|
||||
returnState,
|
||||
readWithM,
|
||||
testStringWith,
|
||||
guardEnabled,
|
||||
|
@ -873,6 +874,10 @@ returnWarnings p = do
|
|||
warnings <- stateWarnings <$> getState
|
||||
return (doc, warnings)
|
||||
|
||||
-- | Return the final internal state with the result of a parser
|
||||
returnState :: (Stream s m c) => ParsecT s st m a -> ParsecT s st m (a, st)
|
||||
returnState p = (,) <$> p <*> getState
|
||||
|
||||
-- | Parse a string with @parser@ (for testing).
|
||||
testStringWith :: (Show a, Stream [Char] Identity Char)
|
||||
=> ParserT [Char] ParserState Identity a
|
||||
|
|
|
@ -81,17 +81,10 @@ readMarkdownWithWarnings :: ReaderOptions -- ^ Reader options
|
|||
-> (Pandoc, [String])
|
||||
readMarkdownWithWarnings opts s = runMarkdown opts s (returnWarnings parseMarkdown)
|
||||
|
||||
|
||||
retState :: MarkdownParser a -> MarkdownParser (a, ParserState)
|
||||
retState p = do
|
||||
r <- p
|
||||
s <- getState
|
||||
return (r, s)
|
||||
|
||||
runMarkdown :: ReaderOptions -> String -> MarkdownParser a -> a
|
||||
runMarkdown opts inp p = fst res
|
||||
where
|
||||
imd = readWithM (retState p) def{ stateOptions = opts } (inp ++ "\n\n")
|
||||
imd = readWithM (returnState p) def{ stateOptions = opts } (inp ++ "\n\n")
|
||||
res = runReader imd s
|
||||
s :: ParserState
|
||||
s = snd $ runReader imd s
|
||||
|
|
|
@ -67,17 +67,11 @@ readOrg opts s = runOrg opts s parseOrg
|
|||
runOrg :: ReaderOptions -> String -> OrgParser a -> a
|
||||
runOrg opts inp p = fst res
|
||||
where
|
||||
imd = readWithM (retState p) def{ orgStateOptions = opts } (inp ++ "\n\n")
|
||||
imd = readWithM (returnState p) def{ orgStateOptions = opts } (inp ++ "\n\n")
|
||||
res = runReader imd s
|
||||
s :: OrgParserState
|
||||
s = snd $ runReader imd s
|
||||
|
||||
retState :: OrgParser a -> OrgParser (a, OrgParserState)
|
||||
retState p = do
|
||||
r <- p
|
||||
s <- getState
|
||||
return (r, s)
|
||||
|
||||
type OrgParser a = ParserT [Char] OrgParserState (Reader OrgParserState) a
|
||||
|
||||
parseOrg :: OrgParser Pandoc
|
||||
|
|
Loading…
Add table
Reference in a new issue