various minor changes, renamed functions

Among other changes two functions have been renamed:

* ‘parseMaybe’ → ‘parse'’ (also added to change log)
* ‘putState’ → ‘setState’ (for consistency)
This commit is contained in:
mrkkrp 2015-08-20 14:05:41 +06:00
parent 3661da90e5
commit f9cfe390af
4 changed files with 60 additions and 42 deletions

View File

@ -92,6 +92,13 @@
* Added new primitive combinator `hidden p` which hides “expected” tokens in * Added new primitive combinator `hidden p` which hides “expected” tokens in
error message when parser `p` fails. error message when parser `p` fails.
* Added new function `parse'` for lightweight parsing where error messages
(and thus file name) are not important and entire input should be
parsed. For example it can be used when parsing of single number according
to specification of its format is desired.
* Renamed `putState``setState` for consistency.
* Added comprehensive QuickCheck test suite. * Added comprehensive QuickCheck test suite.
* Added benchmarks. * Added benchmarks.

View File

@ -40,18 +40,17 @@
-- imported explicitly along with two modules mentioned above. -- imported explicitly along with two modules mentioned above.
module Text.Megaparsec module Text.Megaparsec
( -- * Parsers ( -- * Running parser
ParsecT Parsec
, Parsec , ParsecT
, runParser , runParser
, runParserT , runParserT
, parse , parse
, parseMaybe , parse'
, parseTest , parseTest
, getPosition -- * Backtracking user state
, getInput
, getState , getState
, putState , setState
, modifyState , modifyState
-- * Combinators -- * Combinators
, (A.<|>) , (A.<|>)
@ -141,11 +140,13 @@ module Text.Megaparsec
, Consumed (..) , Consumed (..)
, Reply (..) , Reply (..)
, State (..) , State (..)
, getPosition
, setPosition
, getInput
, setInput
, getParserState , getParserState
, setParserState , setParserState
, updateParserState , updateParserState )
, setPosition
, setInput )
where where
import qualified Control.Applicative as A import qualified Control.Applicative as A

View File

@ -146,10 +146,10 @@ setErrorPos pos (ParseError _ ms) = ParseError pos ms
-- messages and preferring shortest match. -- messages and preferring shortest match.
mergeError :: ParseError -> ParseError -> ParseError mergeError :: ParseError -> ParseError -> ParseError
mergeError e1@(ParseError pos1 ms1) e2@(ParseError pos2 ms2) = mergeError e1@(ParseError pos1 _) e2@(ParseError pos2 ms2) =
case pos1 `compare` pos2 of case pos1 `compare` pos2 of
LT -> e1 LT -> e1
EQ -> foldr addErrorMessage (ParseError pos1 ms1) ms2 EQ -> foldr addErrorMessage e1 ms2
GT -> e2 GT -> e2
-- | @showMessages ms@ transforms list of error messages @ms@ into -- | @showMessages ms@ transforms list of error messages @ms@ into

View File

@ -19,13 +19,13 @@ module Text.Megaparsec.Prim
, Stream (..) , Stream (..)
, Consumed (..) , Consumed (..)
, Reply (..) , Reply (..)
, ParsecT
, Parsec , Parsec
, ParsecT
-- * Running parser -- * Running parser
, runParser , runParser
, runParserT , runParserT
, parse , parse
, parseMaybe , parse'
, parseTest , parseTest
-- * Primitive combinators -- * Primitive combinators
, unexpected , unexpected
@ -40,15 +40,15 @@ module Text.Megaparsec.Prim
, tokens , tokens
-- * Parser state combinators -- * Parser state combinators
, getPosition , getPosition
, getInput
, setPosition , setPosition
, getInput
, setInput , setInput
, getParserState , getParserState
, setParserState , setParserState
, updateParserState , updateParserState
-- * User state combinators -- * User state combinators
, getState , getState
, putState , setState
, modifyState ) , modifyState )
where where
@ -81,6 +81,7 @@ data State s u = State
{ stateInput :: s { stateInput :: s
, statePos :: !SourcePos , statePos :: !SourcePos
, stateUser :: !u } , stateUser :: !u }
deriving (Show, Eq)
-- | An instance of @Stream s m t@ has stream type @s@, underlying monad @m@ -- | An instance of @Stream s m t@ has stream type @s@, underlying monad @m@
-- and token type @t@ determined by the stream. -- and token type @t@ determined by the stream.
@ -123,7 +124,9 @@ instance Monad m => Stream TL.Text m Char where
-- --
-- See also: 'Reply'. -- See also: 'Reply'.
data Consumed a = Consumed a | Empty !a data Consumed a
= Consumed a
| Empty !a
-- | This data structure represents an aspect of result of parser's -- | This data structure represents an aspect of result of parser's
-- work. The two constructors have the following meaning: -- work. The two constructors have the following meaning:
@ -133,7 +136,9 @@ data Consumed a = Consumed a | Empty !a
-- --
-- See also 'Consumed'. -- See also 'Consumed'.
data Reply s u a = Ok a !(State s u) | Error ParseError data Reply s u a
= Ok a !(State s u)
| Error ParseError
-- | 'Hints' represent collection of strings to be included into 'ParserError' -- | 'Hints' represent collection of strings to be included into 'ParserError'
-- as “expected” messages when a parser fails without consuming input right -- as “expected” messages when a parser fails without consuming input right
@ -179,6 +184,7 @@ accHints hs1 c x s hs2 = c x s (hs1 <> hs2)
refreshLastHint :: Hints -> String -> Hints refreshLastHint :: Hints -> String -> Hints
refreshLastHint (Hints []) _ = Hints [] refreshLastHint (Hints []) _ = Hints []
refreshLastHint (Hints (_:xs)) "" = Hints xs
refreshLastHint (Hints (_:xs)) l = Hints ([l]:xs) refreshLastHint (Hints (_:xs)) l = Hints ([l]:xs)
-- If you're reading this, you may be interested in how Megaparsec works on -- If you're reading this, you may be interested in how Megaparsec works on
@ -247,10 +253,10 @@ instance A.Applicative (ParsecT s u m) where
instance A.Alternative (ParsecT s u m) where instance A.Alternative (ParsecT s u m) where
empty = mzero empty = mzero
(<|>) = mplus (<|>) = mplus
many p = reverse <$> manyAccum p many p = reverse <$> manyAcc p
manyAccum :: ParsecT s u m a -> ParsecT s u m [a] manyAcc :: ParsecT s u m a -> ParsecT s u m [a]
manyAccum p = ParsecT $ \s cok cerr eok _ -> manyAcc p = ParsecT $ \s cok cerr eok _ ->
let errToHints c err = c (toHints err) let errToHints c err = c (toHints err)
walk xs x s' _ = walk xs x s' _ =
unParser p s' unParser p s'
@ -412,12 +418,17 @@ parse :: Stream s Identity t =>
Parsec s () a -> SourceName -> s -> Either ParseError a Parsec s () a -> SourceName -> s -> Either ParseError a
parse p = runParser p () parse p = runParser p ()
-- | @parseMaybe p input@ runs parser @p@ on @input@ and returns result -- | @parse' p input@ runs parser @p@ on @input@ and returns result
-- inside 'Just' on success and 'Nothing' on failure. This function also -- inside 'Just' on success and 'Nothing' on failure. This function also
-- parses 'eof', so all input should be consumed by the parser. -- parses 'eof', so all input should be consumed by the parser @p@.
--
-- The function is supposed to be useful for lightweight parsing, where
-- error messages (and thus file name) are not important and entire input
-- should be parsed. For example it can be used when parsing of single
-- number according to specification of its format is desired.
parseMaybe :: Stream s Identity t => Parsec s () a -> s -> Maybe a parse' :: Stream s Identity t => Parsec s () a -> s -> Maybe a
parseMaybe p s = parse' p s =
case parse (p <* eof) "" s of case parse (p <* eof) "" s of
Left _ -> Nothing Left _ -> Nothing
Right x -> Just x Right x -> Just x
@ -638,37 +649,36 @@ eoi = "end of input"
getPosition :: Monad m => ParsecT s u m SourcePos getPosition :: Monad m => ParsecT s u m SourcePos
getPosition = statePos <$> getParserState getPosition = statePos <$> getParserState
-- | @setPosition pos@ sets the current source position to @pos@.
setPosition :: Monad m => SourcePos -> ParsecT s u m ()
setPosition pos = updateParserState (\(State s _ u) -> State s pos u)
-- | Returns the current input. -- | Returns the current input.
getInput :: Monad m => ParsecT s u m s getInput :: Monad m => ParsecT s u m s
getInput = stateInput <$> getParserState getInput = stateInput <$> getParserState
-- | @setPosition pos@ sets the current source position to @pos@.
setPosition :: Monad m => SourcePos -> ParsecT s u m ()
setPosition pos = void $ updateParserState (\(State s _ u) -> State s pos u)
-- | @setInput input@ continues parsing with @input@. The 'getInput' and -- | @setInput input@ continues parsing with @input@. The 'getInput' and
-- @setInput@ functions can for example be used to deal with #include files. -- @setInput@ functions can for example be used to deal with #include files.
setInput :: Monad m => s -> ParsecT s u m () setInput :: Monad m => s -> ParsecT s u m ()
setInput s = void $ updateParserState (\(State _ pos u) -> State s pos u) setInput s = updateParserState (\(State _ pos u) -> State s pos u)
-- | Returns the full parser state as a 'State' record. -- | Returns the full parser state as a 'State' record.
getParserState :: Monad m => ParsecT s u m (State s u) getParserState :: Monad m => ParsecT s u m (State s u)
getParserState = updateParserState id getParserState = ParsecT $ \s _ _ eok _ -> eok s s mempty
-- | @setParserState st@ set the full parser state to @st@. -- | @setParserState st@ set the full parser state to @st@.
setParserState :: Monad m => State s u -> ParsecT s u m (State s u) setParserState :: Monad m => State s u -> ParsecT s u m ()
setParserState st = updateParserState (const st) setParserState st = updateParserState (const st)
-- | @updateParserState f@ applies function @f@ to the parser state. -- | @updateParserState f@ applies function @f@ to the parser state.
updateParserState :: (State s u -> State s u) -> ParsecT s u m (State s u) updateParserState :: (State s u -> State s u) -> ParsecT s u m ()
updateParserState f = ParsecT $ \s _ _ eok _ -> updateParserState f = ParsecT $ \s _ _ eok _ -> eok () (f s) mempty
let s' = f s in eok s' s' mempty
-- User state combinators -- User state combinators
@ -677,10 +687,10 @@ updateParserState f = ParsecT $ \s _ _ eok _ ->
getState :: Monad m => ParsecT s u m u getState :: Monad m => ParsecT s u m u
getState = stateUser <$> getParserState getState = stateUser <$> getParserState
-- | @putState st@ set the user state to @st@. -- | @setState st@ set the user state to @st@.
putState :: Monad m => u -> ParsecT s u m () setState :: Monad m => u -> ParsecT s u m ()
putState u = void $ updateParserState (\s -> s { stateUser = u }) setState u = updateParserState (\s -> s { stateUser = u })
-- | @modifyState f@ applies function @f@ to the user state. Suppose -- | @modifyState f@ applies function @f@ to the user state. Suppose
-- that we want to count identifiers in a source, we could use the user -- that we want to count identifiers in a source, we could use the user
@ -689,4 +699,4 @@ putState u = void $ updateParserState (\s -> s { stateUser = u })
-- > expr = Id <$> identifier <* modifyState (+1) -- > expr = Id <$> identifier <* modifyState (+1)
modifyState :: Monad m => (u -> u) -> ParsecT s u m () modifyState :: Monad m => (u -> u) -> ParsecT s u m ()
modifyState f = void $ updateParserState (\s -> s { stateUser = f (stateUser s)}) modifyState f = updateParserState (\s -> s { stateUser = f (stateUser s)})