[Haskell-cafe] Parsec, state and/of my cluelessness

Niklas din.kompis at gmail.com
Mon Oct 17 14:18:30 EDT 2005


Hi everybody,

for my first real 'learn some haskell'-project I decided upon a parser. The
resulting application would be somewhat useful to me and armed with such a cool
library as Parsec, how could I fail? I was going to be a haskell hacker in
notime. Oh, the wine, the women and the fame.

Didn't work out though.

I'm going to parse a tree of controls. Each control can have values, (a tree of)
properties and more controls as children:

type Guid = String
type Value = (String, String)
data Property = MkProperty String (Maybe Guid) [Value] [Property]
data Control = MkControl String String [Value] [Property] [Control]

The top parser is along the lines of:

ctrlParser :: Parser Control
ctrlParser =
    do { reserved "Begin"
       ; ctrl <- identifier
       ; name <- identifier
       ; (vs, ps, cs) <- ctrlBodyParser
       ; reserved "End"
       ; return (MkControl ctrl name vs ps cs)
       }

Now comes the tricky part for me. Since the control can have three different
types of children I use a helper that parses the body of the control using other
parsers, collecting their results in three lists:

ctrlBodyParser :: CharParser ([Value], [Property], [Control]) 
                             ([Value], [Property], [Control])
ctrlBodyParser =
    do { c <- ctrlParser -- parse child control
       ; (vs, ps, cs) <- getState
       ; setState (vs, ps, (c : cs))
       ; ctrlBodyParser
       }
    <|>
    do { p <- propParser -- parse child property
       ; (vs, ps, cs) <- getState
       ; setState (vs, (p : ps), cs)
       ; ctrlBodyParser
       }
    <|>
    do { v <- valueParser -- parse value
       ; (vs, ps, cs) <- getState
       ; setState ((v : vs), ps, cs)
       ; ctrlBodyParser
       }
    <|>
    do { getState } -- we're finished, return children

GHC error:
---8<---
Couldn't match `()' against `(a, b, c)'
  Expected type: ()
  Inferred type: (a, b, c)
When checking the pattern: (vs, ps, cs)
In a 'do' expression: (vs, ps, cs) <- getState
--->8---

So, I have a problem with the state handling. Any hints? 

Some other questions: Do I need to supply the ctrlBodyParser with an initial
state when I call it from the ctrlParser? Should I modify the last alternative
in the ctrlBodyParser so that it resets the state before calling return with the
collected results?

Thanks,

  Niklas



More information about the Haskell-Cafe mailing list