[Haskell Cafe] Troubles with StateT and Parsec

Hi haskellers, I have a few problems using monad transformers. I have such two functions: parseSyslog :: StateT Integer Parser TimeStamp parseString :: StateT Integer Parser LogString and the following code: parseString = do -- string parse here, all in the form of lift $ <parser> stamp <- lift $ lexeme parseTimestamp -- <?> "timestamp" message <- lift $ manyTill anyToken eof -- <?> "message" return (LogString <...parsed values here...> (check stamp console message) <...more parsed values here...>) where check :: (Maybe TimeStamp) -> Console -> String -> Maybe TimeStamp check Nothing Syslog message = case (lift parse $ parseSyslog "" message) of Left err -> Nothing Right res -> Just res <...other clauses here...> this code seems quite intuitive to me, however it doesn't compile with a king error: Couldn't match kind `(* -> *) -> * -> *' against `?? -> ? -> *' When matching the kinds of `t :: (* -> *) -> * -> *' and `(->) :: ?? -> ? -> *' Probable cause: `lift' is applied to too many arguments In the first argument of `($)', namely `lift parse' I'm not so familiar with monad transformers whatsoever, so I'll be very happy if someone can show me the right way. The code compile nicely if I use "parse" line in a such way: check Nothing Syslog message = case (parse (evalStateT parseSyslog 0) "" message) of but this is not what I really want. To be accurate, here is the sequence which I do want to have in the code: some user state is initialized; parseString gets called many times and changes the state via call to the parseSyslog (that is the only function that really uses/affects user state, everything else is pure Parsec code with it's own internal state). Two main problems that I have now is: 1) impossibility to use parse/parseTest functions with the (StateT <state type> Parser <parse type>) argument. I want it to be lifted somehow, but cannot see how 2) too many lifts in the code. I have only one function that really affects state, but code is filled with lifts from StateT to underlying Parser Sorry if the questions are silly; any help is appreciated -- Regards, Paul Sujkov

Hi Paul, the expression (lift parse $ parseSyslog "" message) has the same meaning as (lift parse (parseSyslog "" message)), so you are indeed applying lift to two arguments, while it expects one. Probably you forgot the $ after lift? Best regards, Daniel Paul Sujkov schrieb:
Hi haskellers,
I have a few problems using monad transformers. I have such two functions:
parseSyslog :: StateT Integer Parser TimeStamp parseString :: StateT Integer Parser LogString
and the following code: parseString = do -- string parse here, all in the form of lift $ <parser> stamp <- lift $ lexeme parseTimestamp -- <?> "timestamp" message <- lift $ manyTill anyToken eof -- <?> "message" return (LogString <...parsed values here...> (check stamp console message) <...more parsed values here...>) where check :: (Maybe TimeStamp) -> Console -> String -> Maybe TimeStamp check Nothing Syslog message = case (lift parse $ parseSyslog "" message) of Left err -> Nothing Right res -> Just res <...other clauses here...>
this code seems quite intuitive to me, however it doesn't compile with a king error:
Couldn't match kind `(* -> *) -> * -> *' against `?? -> ? -> *' When matching the kinds of `t :: (* -> *) -> * -> *' and `(->) :: ?? -> ? -> *' Probable cause: `lift' is applied to too many arguments In the first argument of `($)', namely `lift parse'
I'm not so familiar with monad transformers whatsoever, so I'll be very happy if someone can show me the right way. The code compile nicely if I use "parse" line in a such way:
check Nothing Syslog message = case (parse (evalStateT parseSyslog 0) "" message) of
but this is not what I really want. To be accurate, here is the sequence which I do want to have in the code:
some user state is initialized; parseString gets called many times and changes the state via call to the parseSyslog (that is the only function that really uses/affects user state, everything else is pure Parsec code with it's own internal state). Two main problems that I have now is:
1) impossibility to use parse/parseTest functions with the (StateT <state type> Parser <parse type>) argument. I want it to be lifted somehow, but cannot see how 2) too many lifts in the code. I have only one function that really affects state, but code is filled with lifts from StateT to underlying Parser
Sorry if the questions are silly; any help is appreciated
-- Regards, Paul Sujkov ------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Aug 3, 2009 at 10:46 AM, Paul Sujkov
parseSyslog :: StateT Integer Parser TimeStamp parseString :: StateT Integer Parser LogString
and the following code: parseString = do [...]
Without real code to look at, it's impossible to properly debug the errors in your pseudocode above. For instance, your type signatures aren't real, and you don't mention which version of Parsec you're using. Regardless, you shouldn't need to use monad transformers with Parsec, as it has its own support for managing state that gives you exactly the same features as StateT. See the getState, setState, and updateState functions. I notice that you try to explain why you are using StateT later in your message, but I don't understand your description.

Hi Bryan,
GHC 6.10.1, Parsec 3.0.0 and type signatures are right from the code: they
are actually real (except the ones with the <shortcuts>). I see now that it
is really a better idea to use internal Parser state to collect the data I
need to carry through, so in any case thank you
I've sent two letters on topic not to the mail-list, so I'll quote them
here:
"to make the problem clear: I've changed parseSyslog function from Parser
type to StateT Parser type (a parser with some additional user state); the
question is: how should I use "parse" function, which expects Parser type
signature for it's first argument? Am I right that I should lift parse
function to the StateT transformer to achieve this?"
"the Parser datatype from the Parsec library is itself a State monad;
however, it's internal state is used for parsing purposes. What is a good
practice to implement stateful parsers with Parsec? Using StateT transformer
on top of the Parser type, or using it's own internal state? Or maybe there
is some better way, that I am anaware of?"
that's the state of things right now actually, but I think the solution is
already clear. Thanks to everyone in the conversation :)
2009/8/3 Bryan O'Sullivan
On Mon, Aug 3, 2009 at 10:46 AM, Paul Sujkov
wrote: parseSyslog :: StateT Integer Parser TimeStamp parseString :: StateT Integer Parser LogString
and the following code: parseString = do [...]
Without real code to look at, it's impossible to properly debug the errors in your pseudocode above. For instance, your type signatures aren't real, and you don't mention which version of Parsec you're using.
Regardless, you shouldn't need to use monad transformers with Parsec, as it has its own support for managing state that gives you exactly the same features as StateT. See the getState, setState, and updateState functions. I notice that you try to explain why you are using StateT later in your message, but I don't understand your description.
-- Regards, Paul Sujkov

On Mon, Aug 3, 2009 at 11:46 AM, Paul Sujkov
2) too many lifts in the code. I have only one function that really affects state, but code is filled with lifts from StateT to underlying Parser
You do know you can do this, right? do x <- get put (x + 1) lift $ do etc etc etc If you only have one use of the state, you should be able to write the rest of the parser as a regular Parsec without the StateT (including type signatures), and lift it all at once. Luke
participants (4)
-
Bryan O'Sullivan
-
Daniel van den Eijkel
-
Luke Palmer
-
Paul Sujkov