Parsec State Monad Question
Christian Maeder
maeder at tzi.de
Fri Mar 5 12:43:10 EST 2004
In a local copy of Parsec.Prim I've added:
mapState :: (st1 -> st2) -> State tok st1 -> State tok st2
mapState f (State i p u) = State i p $ f u
mapOkReply :: (st1 -> st2) -> Reply tok st1 a -> Reply tok st2 a
mapOkReply _ (Error a) = Error a
mapOkReply f (Ok a s e) = Ok a (mapState f s) e
mapConsumed :: (a -> b) -> Consumed a -> Consumed b
mapConsumed f (Consumed a) = Consumed $ f a
mapConsumed f (Empty a) = Empty $ f a
mapParse :: (st2 -> st1) -> (st1 -> st2)
-> GenParser tok st1 a -> GenParser tok st2 a
mapParse f g (Parser p) =
Parser (mapConsumed (mapOkReply g) . p . mapState f)
parseWithState :: GenParser tok inter a -> inter -> GenParser tok st a
parseWithState p inter =
do st <- getState
mapParse (const inter) (const st) p
I've only exported mapParse and parseWithState.
HTH Christian
John Knottenbelt wrote:
> Hi
>
> I was wondering if it was possible to write a function that allows changing
> the state type of the Parser monad from Parsec.
>
> The full parser type is: GenParser p s a, where p is the token type, s is the
> state type and a is the return type of the monad. However, I mostly use
> CharParser s a which is a synonym for GenParser Char s a.
>
> What I would like is a function that allows me to combine CharParsers with
> differing state types. Something like:
>
> runParser' :: CharParser t a -> t -> CharParser s (t,a)
>
> So that I can use parsers written to work with different state types together
> on the same input stream.
>
> Does anybody know if this is possible, or how one might do it with Parsec?
>
> Thanks
>
> John
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
More information about the Glasgow-haskell-users
mailing list