Hi Simon,
>>>>> "Simon" == Simon Peyton-Jones <[EMAIL PROTECTED]> writes:

    > | Subject: Type signatures in instance declarations?
    > ......
    > | I think it would be even useful to the compiler when one has a
    > | polymorphic recursion.  ISTR occasions when I wasn't able to define
    > | fmap directly (eg. for a nested datatype for lambda calculus terms),
    > | but had to define another name for it with a polymorphic declaration,
    > | then equate fmap to it in the instance declaration.

    > Interesting: so you wanted to write a type signature that was *more general*
    > than the one for the instance decl?  Right?   

Not exactly. Actually, I was wrong.  Here's how you can write some
code that needs polymorphic recursion *without* an explicit type
declaration!

data L x = Var x | App (L x) (L x) | Abs (L (Maybe x))
instance Functor L where
  fmap f z = case z of Var x -> Var (f x)
                       App e1 e2 -> App (fmap f e1) (fmap f e2) 
                       Abs e -> Abs (fmap (fmap f) e)
instance Monad L where 
  return = Var
  e >>= f = 
   case e of Var x      -> f x
             App e1 e2  -> App (e1 >>= f) (e2 >>= f)
             Abs bd     -> Abs (bd >>= f') 
                           where f' m = case m of
                                         Just x -> fmap Just (f x)
                                         Nothing   -> Var Nothing
Well, you live and learn...
Cheers,
Peter

Reply via email to