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

C.M.Brown cmb21 at kent.ac.uk
Mon Jun 4 10:58:59 EDT 2007


Hi Juozas,

> ---------------------
>
> 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)  -- LINE 34
> --------------------

I tried the above in both ghci and hugs. The problem that I found was that
firstly both interpreters were trying to load the default implementations
of return and >>=. The problem specifically lies within the "do" notation.
This is special syntactical sugar Haskell uses to allow the laying out of
monadic code more aesthetically pleasing. What is also happening is that
the particular Haskell implementations automatically use the default
implementations for return and >>= (defined within the Prelude library).

Try the following:

module Arb where

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

return2 :: a -> Parser a
return2 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 = item >>=> (\x -> (item >>=> (\_ -> item >>=> (\y -> return2 (x,y)))))


In the above p is written using lambda expressions.

f = p >>= (\x -> return x) can be read the same as:

f = do
        x <- p
        return x


I hope that gives some insight.

Kind regards,
Chris.


More information about the Haskell-Cafe mailing list