[Haskell-cafe] beginner question re example in Hutton's
"Programming in Haskell"
David Cabana
dcabana at nc.rr.com
Fri Feb 23 23:18:46 EST 2007
I have been trying to work through Graham Hutton's "Programming in
Haskell", but have hit something of a snag in chapter 8.4. Hutton
presents some sample code which I am trying to run, with no luck so
far. Here is the code as I constructed it by gathering snippets
presented across three pages.
<code>
module Main where
-- as per Hutton page 75
type Parser a = String -> [(a, String)]
-- page 75
return :: a -> Parser a
return v = \inp -> [(v,inp)]
-- page 76
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
-- page 77
p :: Parser (Char, Char)
p = do x <- item
item
y <- item
return (x,y)
</code>
When I tried to load this code, I got this error message:
Ambiguous occurrence `return'
It could refer to either `return', defined at /Users/joe/haskell/
parse2.hs:8:0
or `return', imported from Prelude
OK. My reasoning was that Hutton took the trouble to define return,
so I decided to use the local definition instead of the one in the
Prelude. I changed the last line from "return (x,y)" to "Main.return
(x,y)". The new error message is worse:
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)</blockquote>
Hutton provided explicit type signatures, so I did not expect type
issues.
I decided to take another approach. The book has a website that lists
errata and provides code listings. The code for chapter eight is at
http://www.cs.nott.ac.uk/~gmh/Parsing.lhs
When I read Hutton's code, I noticed that he begins by importing
Monad. The code I list above is from chapter 8, pages 75-77 of the
book. Monads have not yet been mentioned. The book's index shows that
monads aren't mentioned till page 113, in chapter 10. I also notice
that in his code, Hutton makes repeated use of a symbol P whose
meaning I do not know.
What do I have to do to make this code work?
I know I can use Hutton's code from the website, but I expected the
code presented in the book to work, or the code on the website to
restrict itself to what has been discussed in the book. Am I missing
something here?
Thanks,
David Cabana
More information about the Haskell-Cafe
mailing list