Issue with type families
Tyson Whitehead
twhitehead at gmail.com
Wed Mar 3 20:39:30 EST 2010
On March 3, 2010 18:35:26 Daniel Fischer wrote:
> 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))
Thanks Daniel,
That makes sense. Strangely enough though, I had actually originally tried it
with my own Applicative class just in case I was being tripped up by something
like the (->) instance you pointed out, and it still didn't work. That is
{-# LANGUAGE FlexibleInstances, TypeFamilies #-}
newtype I a = I a
class A t where
ap :: t (a -> b) -> t a -> t b
class Z t where
type W t
z :: t -> W t
instance A I where
ap (I f) (I x) = I $ f x
instance Z (a -> b) where
type W (a -> b) = a -> b
z = id
instance A t => Z (t (a -> b)) where
type W (t (a -> b)) = t a -> t b
z = ap
also gives me
Temp.hs:17:9:
Conflicting family instance declarations:
type instance W (a -> b) -- Defined at Temp.hs:17:9
type instance W (t (a -> b)) -- Defined at Temp.hs:21:9
Failed, modules loaded: none.
Is the compiler somehow anticipating that I could add an instance for (->) to
A and thus be back to the Applicative class situation?
Thanks! -Tyson
PS: I asked this here because type classes is a GHC issue, would the haskell-
cafe list been a more appropriate place?
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: This is a digitally signed message part.
Url : http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20100303/c2bf677e/attachment.bin
More information about the Glasgow-haskell-users
mailing list