[Haskell-cafe] Equality constraints in type families

Hugo Pacheco hpacheco at gmail.com
Tue Mar 11 10:39:26 EDT 2008


Yes, I have tried both implementations at the start and solved it by
choosing for the following:
type family F a :: * -> *
type FList a x = Either () (a,x)
type instance F [a] = FList a

instance (Functor (F [a])) where
fmap _ (Left _) = Left ()
fmap f (Right (a,x)) = Right (a,f x)

The option was:

type family F a x :: *
type instance F [a] x = Either() (a,x)

instance (Functor (F [a])) where -- error, not enough parameters passed to F
fmap _ (Left _) = Left ()
fmap f (Right (a,x)) = Right (a,f x)

So, indeed, with either implementation I have a problem.

>I have my suspicions about your mentioning of both Functor (F d) and
>Functor (F a) in the signature. Which implementation of fmap do you want?
>Or should they be both the same (i.e. F d ~ F a)?

This is an hard question to which the answer is both.

In the definition of an hylomorphism I want the fmap from (F d):

hylo :: (Functor (F d)) => d -> (F d c -> c) -> (a -> F d a) -> a -> c
hylo d g h = g . fmap (hylo d g h) . h

However, those constraints I have asked about would allow me to encode a
paramorphism as an hylomorphism:

class Mu a where
    inn :: F a a -> a
    out :: a -> F a a

para :: (Mu a, Functor (F a),Mu d, Functor (F d),F d a ~ F a (a,a), F d c ~
F a (c,a)) => d -> (F a (c,a) -> c) -> a -> c
para d f = hylo d f (fmap (id /\ id) . out)

In para, I would want the fmap from (F a) but that would be implicitly
forced by the usage of out :: a -> F a a

Sorry for all the details, ignore them if they are too confusing.
Do you think there might be a definition that would satisfy me both Functor
instances and equality?

Thanks for your pacience,
hugo
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080311/ff319b2c/attachment.htm


More information about the Haskell-Cafe mailing list