[Haskell-cafe] newbie question on Parsers from "Programming In Haskell"

David House dmhouse at gmail.com
Mon Jun 4 10:58:54 EDT 2007


On 04/06/07, Alfonso Acosta <alfonso.acosta at gmail.com> wrote:
> Hugs is probably complaining because it identifies "x <- item" (which
> is not a simple expression) as the last element of do.

That was my first guess, too, but it's not the case, switch to a
monospaced font to see this.

Juozas, you could only use do-notation if your Parser type were
declared an instance of the Haskell type-class Monad. Seeing as you
haven't done this, you have to stick to the "de-sugared" version
involving (>>=) and return:

p :: Parser (Char, Char)
p = item >>= \x ->
    item >>= \_ ->
    item >>= \y ->
    return (x, y)  -- LINE 34

You might also need a line at the top of your file that looks like this:

import Prelude hiding (return, (>>=))

This instructs Hugs not to load the default Haskell definitions of
return and (>>=), so that you can use the versions you've defined in
your file.

The proper solution is to declare Parser an instance of Monad.
Unfortunately, this isn't as simple as writing "instance Monad Parser
where...", because 'Parser a' is a type synonym, and there's a rule
that type synonyms have to be fully applied, but 'Parser' on its own
is missing an argument. The only sane way to do it is to make a
newtype:

newtype Parser a = P (String -> [(a, String)])

Then you can write your instance declaration, using the definitions of
return and (>>=) you provided, modified slightly now that Parser has a
constructor we need to use:

instance Monad Parser where
  return v = P $ \inp -> [(v, inp)]
  fail _ = P $ \inp -> []
  p >>= f = P $ \inp -> case parse p inp of
                          [] -> []
                          [(v, out)] -> parse (f v) out

(Note also that it's called fail, not failure.) item and parse need to
change slightly to reflect the fact that you've got a P constructor
floating around:

item :: Parser Char
item = P $ \inp -> case inp of
                     [] -> []
                     (x:xs) -> [(x, xs)]

parse :: Parser a -> String -> [(a, String)]
parse (P p) inp = p inp

You should find with those definitions that you can write p as you would expect.

-- 
-David House, dmhouse at gmail.com


More information about the Haskell-Cafe mailing list