Issue with type families
Daniel Fischer
daniel.is.fischer at web.de
Wed Mar 3 18:35:26 EST 2010
Am Donnerstag 04 März 2010 00:17:09 schrieb Tyson Whitehead:
> The following code
>
> {-# LANGUAGE FlexibleInstances, TypeFamilies #-}
>
> import Control.Applicative
>
> class Z t where
> type W t
> z :: t -> W t
>
> instance Z (a -> b) where
> type W (a -> b) = a -> b
> z = id
>
> instance Z (IO (a -> b)) where
> type W (IO (a -> b)) = IO a -> IO b
> z = (<*>)
>
> works fine, but if I try and generalize to from IO to the Applicative
> classes
>
> instance (Applicative m) => Z (m (a -> b)) where
> type W (m (a -> b)) = m a -> m b
> z = (<*>)
>
> I get the following error
>
> Temp.hs:10:9:
> Conflicting family instance declarations:
> type instance W (a -> b) -- Defined at Temp.hs:10:9
> type instance W (m (a -> b)) -- Defined at Temp.hs:14:9
> Failed, modules loaded: none.
>
> unless I remove one of the instances, and then it is happy.
>
> Is this correct? I don't claim to really understand the rules regarding
> type classes, but I can't see why these are overlapping.
>
> Thanks! -Tyson
Because:
instance Applicative ((->) a) -- Defined in Control.Applicative
so, from the instance Z (a -> b), with b == c -> d, we have an
instance Z (a -> (b -> c))
and from instance Z (m (u -> v)), we have, with m == ((->) x), an
instance Z (x -> (u -> v))
More information about the Glasgow-haskell-users
mailing list