[Haskell-cafe] Re: ANNOUNCE: fixpoint 0.1

Roman Leshchinskiy rl at cse.unsw.edu.au
Wed Nov 21 03:55:27 EST 2007


apfelmus wrote:
> Bertram Felgenhauer wrote:
>> [redirecting from haskell at ...]
>> apfelmus wrote:
>> [...]
>>> I wonder whether a multi parameter type class without 
>>> fundeps/associated types would be better.
>>>
>>>   class Fixpoint f t where
>>>     inject  :: f t -> t
>>>     project ::   t -> f t
>>>
>> [...]
>>> Interestingly, this even gives slightly shorter type signatures
>>>
>>>   cata :: Fixpoint f t => (f s -> s) -> t -> s
>>>   size :: (Fixpoint f t, Foldable f) => t -> Int
>>
>> size can't be used now though, because there is no way to infer f.
> 
> Ah, of course, stupid me.
> 
> Making  f  an associacted type synonym / fundep  instead of a associated 
> data type is still worth it, since we can use it for  Mu f

I originally considered the following:

class Functor (Pre t) => Fixpoint t where
   type Pre t :: * -> *

instance Fixpoint (Mu f) where
   type Pre (Mu f) = f

But alas, this breaks hylomorphisms:

hylo :: Fixpoint t => (Pre t s -> s) -> (p -> Pre t p) -> p -> s

If Pre is a type function, there is no way to infer t.

Roman



More information about the Haskell-Cafe mailing list