[Haskell-beginners] Monads and infinite types

Tillmann Rendel rendel at daimi.au.dk
Sat Aug 30 23:32:49 EDT 2008


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


More information about the Beginners mailing list