On Oct 23, 2010, at 1:27 PM, Sebastian Fischer wrote:
> 
> I think `Control.Functor.Categorical.CFunctor` is a more natural replacement 
> for functor here. One can define
> 
>    instance CFunctor (ListF a) ForceCat Hask
> 
> and I was hoping that I could define `fold` based on CFunctor but I did not 
> succeed. The usual definition of `fold` is
> 
>    fold :: Functor f => (f a -> a) -> Fix f -> a
>    fold f = f . fmap (fold f)
> 
> and I tried to replace this with
> 
>    fold :: CFunctor f ForceCat Hask => ...
> 
> but did not find a combination of type signature and definition that compiled.

The catamorphism lies in the ForceCat category. Also, you can't just pass "a" 
to "f" because Force a is undefined.

   data IdThunk a
   type instance Force (IdThunk a) = a

   cata :: CFunctor f ForceCat (->) => (f (IdThunk a) -> a) -> ForceCat 
(FixThunk f) (IdThunk a)
   cata alg = ForceCat $ alg . cmap (cata alg)

Then you can define fold as follows:

   fold :: CFunctor f ForceCat (->) => (f (IdThunk a) -> a) -> Fix f -> a
   fold = unForceCat . cata

Fortunately the IdThunk does not get in the way when defining algebras:

   sumAlg :: ListF Int (IdThunk Int) -> Int
   sumAlg Nil = 0
   sumAlg (Cons a r) = a + r

greetings,
Sjoerd Visscher




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

Reply via email to