[Haskell-cafe] [Haskell Cafe] Troubles with StateT and Parsec

Paul Sujkov psujkov at gmail.com
Mon Aug 3 13:46:30 EDT 2009


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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090803/6f44599b/attachment.html


More information about the Haskell-Cafe mailing list