
I discovered that closed type classes can be implicitly defined using GADTs. The GADT value itself acts like a class dictionary. However, GHC (6.8.3) doesn't know anything about these type classes, and it won't infer any class memberships. In the example below, an instance of Eq is not recognized. So is this within the domain of GHC's type inference, not something it shoud infer, or a bug? {-# OPTIONS_GHC -XTypeFamilies -XGADTs -XEmptyDataDecls #-} module CaseAnalysisOnGADTs where -- Commutative and associative operators. data CAOp a where Sum :: CAOp Int Disj :: CAOp Bool Concat :: CAOp String {- For any non-bottom value of type 'CAOp a', the value will have type -- CAOp Int, CAOp Bool, or CAOp String. Int, Bool, and String are all -- members of Eq. Therefore, if we have a non-bottom value of type -- 'CAOp a' then 'a' is a member of Eq. -} data D a = D !(CAOp a) (a, a) -- However, GHC won't figure this out. noEvidenceOfEq :: D a -> Bool noEvidenceOfEq (D op (e1, e2)) = e1 == e2 -- Error, no instance (Eq a) -- Unless you force it to do case analysis on constructors. evidenceOfEq :: CAOp a -> a -> a -> Bool evidenceOfEq Sum = (==) evidenceOfEq Disj = (==) evidenceOfEq Concat = (==) -- Then you can use the result from that, but GHC still won't -- recognize it as an Eq instance. useEvidenceOfEq :: D a -> Bool useEvidenceOfEq (D op (e1, e2)) = evidenceOfEq op e1 e2 _________________________________________________________________ You live life beyond your PC. So now Windows goes beyond your PC. http://clk.atdmt.com/MRT/go/115298556/direct/01/

On Wed, Oct 29, 2008 at 10:20 PM, C Rodrigues
I discovered that closed type classes can be implicitly defined using GADTs The GADT value itself acts like a class dictionary. However, GHC (6.83) doesn't know anything about these type classes, and it won't infer any class memberships. In the example below, an instance of Eq is not recognized.
So is this within the domain of GHC's type inference, not something it shoud infer, or a bug?
{-# OPTIONS_GHC -XTypeFamilies -XGADTs -XEmptyDataDecls #-} module CaseAnalysisOnGADTs where
-- Commutative and associative operators. data CAOp a where Sum :: CAOp Int Disj :: CAOp Bool Concat :: CAOp String
I guess when you write something like this the type checker doesn't look at the closed set of types that 'a' can take on. I don't know why that would be a problem in your example, but if we did this: data CAOp a where Sum :: CAOp Int Disj :: CAOP Bool Concat :: CAOp String Weird :: Show a => CAOp a Now we have a problem, because the set of types for is { Int, Bool, String, forall a. Show a => a}. It's not a closed set anymore. And I think, but I'm just making this up, that the above set of type must be hard to reason about. I think it would essentially be: data Show a => CAOp a where ... And GHC won't allow that, presumably for a good reason. Neat example, and I hope someone sheds more light on this. By the way, since you mention ghc6.8.3, does that mean some other version of GHC permits noEvidenceOfEq to type check? I tried 6.6.1 but that didn't accept it either. Jason

Jason Dagit wrote:
On Wed, Oct 29, 2008 at 10:20 PM, C Rodrigues
wrote: I discovered that closed type classes can be implicitly defined using GADTs The GADT value itself acts like a class dictionary. However, GHC (6.83) doesn't know anything about these type classes, and it won't infer any class memberships. In the example below, an instance of Eq is not recognized.
So is this within the domain of GHC's type inference, not something it shoud infer, or a bug?
{-# OPTIONS_GHC -XTypeFamilies -XGADTs -XEmptyDataDecls #-} module CaseAnalysisOnGADTs where
-- Commutative and associative operators. data CAOp a where Sum :: CAOp Int Disj :: CAOp Bool Concat :: CAOp String
I guess when you write something like this the type checker doesn't look at the closed set of types that 'a' can take on. I don't know why that would be a problem in your example, but if we did this:
data CAOp a where Sum :: CAOp Int Disj :: CAOP Bool Concat :: CAOp String Weird :: Show a => CAOp a
Now we have a problem, because the set of types for is { Int, Bool, String, forall a. Show a => a}. It's not a closed set anymore. And I think, but I'm just making this up, that the above set of type must be hard to reason about. I think it would essentially be:
data Show a => CAOp a where ...
I agree with Jason here. Actually we can think of quite a lot of examples where the type checker _can_ know something what we see as obvious. But that something is a special case of a more general situation which is far less obvious and knowing it may require serious program analysis. Then, regarding handling some special cases, I think it's a matter of keeping type checker predictable and clean. In this particular case, handling this situation would require type checker to look at the _values_ of the given datatype, which as I understand Haskell type checker doesn't. If we later add members to CAOp the valid program may become invalid, though the "signature" of CAOp hasn't changed. That doesn't look good. Not all members of CAOp may be exported from a module, that would have to be taken into account as well, probably. In your example, why not just do traditionalEvidenceOfEq :: Eq a => D a -> Bool -- Daniil Elovkov
participants (3)
-
C Rodrigues
-
Daniil Elovkov
-
Jason Dagit