
Hello-- I'm still trying to wade into Haskell after a fair amount of experience in other (mostly, but not exclusively, C-type) languages, and I'm finding this mind numbingly difficult. Usually the way I learn a new language is by finding an application for it and pounding my way through that application. In this case I've started by trying to parse apart a simple GPS NMEA sentence. I'm sure there are prefab libraries for parsing strings, but this seemed like a good way of getting aquatinted with the Monad. I've created a new data type similar to Maybe, but which can return no value, a single value, or a list of values. It seems to behave, but I haven't ruled it out as the cause of my frustration. The NMEAParser monad will eventually take a comma separated string and return a list of fields, lopping off the checksum at the end. Once I can do that, I can start adding other intelligence such as testing the checksum, bounds checking the fields, etc. At the bottom is the little bit of code I'm working with, and the error messages I'm getting out of ghci. Both errors confuse me-- infinite type message because I'm not sure where I've suggested that it build that type, and the "expected ZeroOrMore a but got ZeroOrMore b" message because I thought 'b' and 'a' were allowed to be different types but could also be the same. Any help wrapping my head around this would be appreciated, and will almost certainly be rewarded with more dumb questions in the near future. Thanks-- Greg --------------------------------- NMEATest.hs---------------------------------- module NMEATest where data ZeroOrMore a = NoVal | SingleVal a | MultiVal [a] deriving (Eq,Ord,Show) type Sentence = String newtype NMEAParser a = NMEAParser(Sentence -> (ZeroOrMore a, Sentence)) instance Monad NMEAParser where return a = NMEAParser(\s -> (SingleVal a,s)) NMEAParser k >>= f = NMEAParser(\s0 -> let (r1, s1) = k s0 k2 = f r1 (r2, s2) = k2 s1 in (r1,s2)) ------------------------------------------------------------------------------------ ------------------ghci output-------------------------------------------- Prelude> :l NMEATest.hs [1 of 1] Compiling NMEATest ( NMEATest.hs, interpreted ) NMEATest.hs:26:45: Occurs check: cannot construct the infinite type: a = ZeroOrMore a When generalising the type(s) for `k2' In the expression: let (r1, s1) = k s0 k2 = f r1 (r2, s2) = k2 s1 in (r1, s2) In the first argument of `NMEAParser', namely `(\ s0 -> let (r1, s1) = k s0 k2 = f r1 .... in (r1, s2))' NMEATest.hs:28:42: Couldn't match expected type `b' against inferred type `a' `b' is a rigid type variable bound by the type signature for `>>=' at <no location info> `a' is a rigid type variable bound by the type signature for `>>=' at <no location info> Expected type: ZeroOrMore b Inferred type: ZeroOrMore a In the expression: r1 In the expression: let (r1, s1) = k s0 k2 = f r1 (r2, s2) = k2 s1 in (r1, s2) Failed, modules loaded: none. Prelude> -------------------------------------------------------------------------------------------------

Greg Best wrote:
---------------------------------NMEATest.hs----------------------------------
module NMEATest where
data ZeroOrMore a = NoVal | SingleVal a | MultiVal [a] deriving (Eq,Ord,Show) type Sentence = String newtype NMEAParser a = NMEAParser(Sentence -> (ZeroOrMore a, Sentence))
instance Monad NMEAParser where return a = NMEAParser(\s -> (SingleVal a,s)) NMEAParser k >>= f = NMEAParser(\s0 -> let (r1, s1) = k s0 k2 = f r1 (r2, s2) = k2 s1 in (r1,s2)) ------------------------------------------------------------------------------------
NMEATest.hs:26:45: Occurs check: cannot construct the infinite type: a = ZeroOrMore a
f and r1 have types f :: a -> NMEAParser b r1 :: ZeroOrMore a so that your use of f r1 forces a = ZeroOrMore a which cannot be the case. You have to deconstruct r1 and do something appropriate for the three different cases.
NMEATest.hs:28:42: Couldn't match expected type `b' against inferred type `a' Expected type: ZeroOrMore b Inferred type: ZeroOrMore a
Your >>= returns r1, the result of executing the left hand side action, but the overall result of executing (k >>= f) should be the result of the right hand side, i.e. r2. Note that r1 and r2 have indeed the types r1 :: ZeroOrMore a r2 :: ZeroOrMore b. Tillmann

2008/8/31 Tillmann Rendel
instance Monad NMEAParser where return a = NMEAParser(\s -> (SingleVal a,s)) NMEAParser k >>= f = NMEAParser(\s0 -> let (r1, s1) = k s0 k2 = f r1 (r2, s2) = k2 s1 in (r1,s2))
"f r1" evaluates to a parser, you forgot to pattern match, k2 isn't a function, it's a parser. -- Jedaï
participants (3)
-
Chaddaï Fouché
-
Greg Best
-
Tillmann Rendel