[Haskell-cafe] Re: ANNOUNCE: fixpoint 0.1

apfelmus apfelmus at quantentunnel.de
Wed Nov 21 03:46:25 EST 2007


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

   class Fixpoint f t where
     type F t a
     ...

   instance Fixpoint f (Mu f) where ..
     type F (Mu f) a = f a

Otherwise, we would have to deal with some kind of newtype

     data F (Mu f) a = MuF f a

Hm, but does  F (Mu f)  qualify as a type constructor of kind  * -> * 
for type inference/checking? Or is the situation the same as with normal 
type synonyms?


Regards,
apfelmus



More information about the Haskell-Cafe mailing list