Bertram Felgenhauer wrote:
[redirecting from [EMAIL PROTECTED]
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

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

Reply via email to