mirror of
https://github.com/mrkkrp/megaparsec.git
synced 2025-01-07 08:47:15 +03:00
cosmetic changes in ‘Text.Megaparsec.Prim’
Also eliminated dead segment of code in ‘token'’.
This commit is contained in:
parent
d0cdb85e89
commit
20984c20f2
@ -364,9 +364,7 @@ parserPlus m n = ParsecT $ \s cok cerr eok eerr ->
|
|||||||
in unParser m s cok cerr eok meerr
|
in unParser m s cok cerr eok meerr
|
||||||
|
|
||||||
instance MonadTrans (ParsecT s u) where
|
instance MonadTrans (ParsecT s u) where
|
||||||
lift amb = ParsecT $ \s _ _ eok _ -> do
|
lift amb = ParsecT $ \s _ _ eok _ -> amb >>= \a -> eok a s mempty
|
||||||
a <- amb
|
|
||||||
eok a s mempty
|
|
||||||
|
|
||||||
-- Running a parser
|
-- Running a parser
|
||||||
|
|
||||||
@ -572,37 +570,16 @@ token :: Stream s m t =>
|
|||||||
-> (t -> Maybe a) -- ^ Matching function for the token to parse.
|
-> (t -> Maybe a) -- ^ Matching function for the token to parse.
|
||||||
-> ParsecT s u m a
|
-> ParsecT s u m a
|
||||||
{-# INLINE token #-}
|
{-# INLINE token #-}
|
||||||
token nextpos = token' nextpos Nothing
|
token nextpos test = ParsecT $ \(State input pos u) cok _ _ eerr -> do
|
||||||
|
|
||||||
token' :: Stream s m t =>
|
|
||||||
(SourcePos -> t -> s -> SourcePos)
|
|
||||||
-> Maybe (SourcePos -> t -> s -> u -> u)
|
|
||||||
-> (t -> Maybe a)
|
|
||||||
-> ParsecT s u m a
|
|
||||||
{-# INLINE token' #-}
|
|
||||||
token' nextpos Nothing test
|
|
||||||
= ParsecT $ \(State input pos user) cok _ _ eerr -> do
|
|
||||||
r <- uncons input
|
r <- uncons input
|
||||||
case r of
|
case r of
|
||||||
Nothing -> eerr $ unexpectedErr eoi pos
|
Nothing -> eerr $ unexpectedErr eoi pos
|
||||||
Just (c,cs) ->
|
Just (c,cs) ->
|
||||||
case test c of
|
case test c of
|
||||||
Just x -> let newpos = nextpos pos c cs
|
Just x -> let newpos = nextpos pos c cs
|
||||||
newstate = State cs newpos user
|
newstate = State cs newpos u
|
||||||
in seq newpos $ seq newstate $ cok x newstate mempty
|
in seq newpos $ seq newstate $ cok x newstate mempty
|
||||||
Nothing -> eerr $ unexpectedErr (showToken c) pos
|
Nothing -> eerr $ unexpectedErr (showToken c) pos
|
||||||
token' nextpos (Just nextState) test
|
|
||||||
= ParsecT $ \(State input pos user) cok _ _ eerr -> do
|
|
||||||
r <- uncons input
|
|
||||||
case r of
|
|
||||||
Nothing -> eerr $ unexpectedErr eoi pos
|
|
||||||
Just (c,cs) ->
|
|
||||||
case test c of
|
|
||||||
Just x -> let newpos = nextpos pos c cs
|
|
||||||
newUser = nextState pos c cs user
|
|
||||||
newstate = State cs newpos newUser
|
|
||||||
in seq newpos $ seq newstate $ cok x newstate mempty
|
|
||||||
Nothing -> eerr $ unexpectedErr (showToken c) pos
|
|
||||||
|
|
||||||
-- | The parser @tokens posFromTok@ parses list of tokens and returns
|
-- | The parser @tokens posFromTok@ parses list of tokens and returns
|
||||||
-- it. The resulting parser will use 'showToken' to pretty-print the
|
-- it. The resulting parser will use 'showToken' to pretty-print the
|
||||||
|
Loading…
Reference in New Issue
Block a user