I'm trying to write some code to do folds on nested datatypes as in 
http://web.comlab.ox.ac.uk/people/Jeremy.Gibbons/publications/efolds.pdf but 
running into trouble getting things to typecheck.

Given the types

data Nest a = Nil | Cons(a, (Nest (Pair a)))
type Pair a = (a,a)

and the following function to map over pairs:

pair f (a,b) = (f a, f b)

the paper indicates that an efficient fold over a nest is defined as follows

efold :: forall n m b. 
  (forall a. n a) 
  -> (forall a . (m a, n (Pair a)) -> n a)
  -> (forall a. Pair (m a) -> m (Pair a))
  -> (forall l z. (l b -> m (z b)) -> Nest (l b) -> n (z b))
efold e f g h Nil = e
efold e f g h (Cons(x, xs)) = f(h x, efold e f g (g . pair h) xs)

However, when I try to compile this, I get the error "Couldn't match expected 
type `l' against inferred type `z'".  I'm new to Haskell so I'm probably 
missing something obvious, but this code looks to me like it ought to work.  
Any thoughts on what I'm doing wrong?

Thanks,
Keith

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to