newbie question on Parsers from "Programming In Haskell"

Hello, I am a somewhat experienced programmer and a complete Haskell newbie, so I hope this is the correct ML for my question. I have decided to learn Haskell and started with Graham Hutton's book. Everything was going nicely until section 8.4, on sequencing functional parsers. I am trying to write an elementary parser that produces the 1st and 3d elements from a string. I am using the code from the book. --------------------- 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 -------------------- BUT, when I try to :load parse.hs from hugs I get the following error: ERROR "parse.hs":34 - Last generator in do {...} must be an expression I have no idea what I am doing wrong and why Hugs is complaining. I hope this question is not too simply for this mailing list, but I have honestly googled for an answer and had found nothing. Juozas Gaigalas

On 6/4/07, Juozas Gaigalas
Hello,
I am a somewhat experienced programmer and a complete Haskell newbie, so I hope this is the correct ML for my question.
I have decided to learn Haskell and started with Graham Hutton's book. Everything was going nicely until section 8.4, on sequencing functional parsers. I am trying to write an elementary parser that produces the 1st and 3d elements from a string. I am using the code from the book.
---------------------
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 --------------------
BUT, when I try to :load parse.hs from hugs I get the following error:
ERROR "parse.hs":34 - Last generator in do {...} must be an expression
Although the error is not really friendly (your "supposedly" last generator in do is an expression) the problem probably is indentation: Try like this
p = do x <- item item y <- item return (x, y) -- LINE 34
Hugs is probably complaining because it identifies "x <- item" (which is not a simple expression) as the last element of do.

On 04/06/07, Alfonso Acosta
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@gmail.com

David House wrote:
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:
Is this true? I thought do (like all sugar) was desugared before semantic analysis. So long as you have the right >>=, return, and fail in scope, I would have thought the desugaring is oblivious to their definition (and particularly ignorant of instancing of the Monad typeclass). Dan

Dan Weston wrote:
Is this true? I thought do (like all sugar) was desugared before semantic analysis. So long as you have the right >>=, return, and fail in scope, I would have thought the desugaring is oblivious to their definition (and particularly ignorant of instancing of the Monad typeclass).
Some compilers also type-check when desugaring; if actions in the do-block are not of a Monad instance type, it is rejected. See also an earlier thread on the validity of "do { 1 }".

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.

On Mon, Jun 04, 2007 at 05:42:35PM +0300, Juozas Gaigalas wrote:
Hello,
I am a somewhat experienced programmer and a complete Haskell newbie, so I hope this is the correct ML for my question.
I have decided to learn Haskell and started with Graham Hutton's book. Everything was going nicely until section 8.4, on sequencing functional parsers. I am trying to write an elementary parser that produces the 1st and 3d elements from a string. I am using the code from the book.
---------------------
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 --------------------
BUT, when I try to :load parse.hs from hugs I get the following error:
ERROR "parse.hs":34 - Last generator in do {...} must be an expression
I have no idea what I am doing wrong and why Hugs is complaining. I hope this question is not too simply for this mailing list, but I have honestly googled for an answer and had found nothing.
If you wish to use 'do' notation with your parser, you must declare it as an instance of Monad class.
Juozas Gaigalas
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (7)
-
Albert Y. C. Lai
-
Alfonso Acosta
-
C.M.Brown
-
Dan Weston
-
David House
-
Ilya Tsindlekht
-
Juozas Gaigalas