[Haskell-cafe] Help with Programming in Haskell example

Andre Nathan andre at digirati.com.br
Fri May 18 14:55:16 EDT 2007


Hello

I've been reading Programming in Haskell, and I'm trying to go through
the parser examples in chapter. However, I'm getting a type error when
using the "do" notation. Here's the code I'm trying to load in ghci,
which is copied from the book:

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

type Parser a = String -> [(a, String)]

return :: a -> Parser a
return v = \inp -> [(v, inp)]

failure :: Parser a
failure = \inp -> []

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

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

(>>=) :: Parser a -> (a -> Parser b) -> Parser b
p >>= f = \inp -> case parse p inp of
                    []         -> []
                    [(v, out)] -> parse (f v) out

p :: Parser (Char, Char)
p = do x <- item
       item
       y <- item
       return (x, y)


The problem is in the definition of "p":

    Couldn't match expected type `Char'
           against inferred type `[(Char, String)]'
    In the expression: x
    In the first argument of `return', namely `(x, y)'
    In the expression: return (x, y)

Now if I define p as

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

it works fine, so I'm wondering what else I need to do for the "do"
notation to work.

Thanks in advance,
Andre



More information about the Haskell-Cafe mailing list