Suppose I have the following code:
{-# LANGUAGE GADTs, DeriveDataTypeable, StandaloneDeriving #-}
import Data.Typeable
class Eq t => OnlyEq t
class (Eq t, Typeable t) => BothEqAndTypeable t
data Wrapper a where
Wrap :: BothEqAndTypeable a => a -> Wrapper a
deriving instance Eq (Wrapper a)
deriving instance Typeable1 Wrapper
Then, the following instance declaration works, without a constraint on t:
instance OnlyEq (Wrapper t)
and does what I expect it to do.
But the following instance declaration doesn't work:
instance BothEqAndTypeable (Wrapper t)
since GHC - I'm using 7.6.1 - complains that:
No instance for (Typeable t)
arising from the superclasses of an instance declaration
Possible fix:
add (Typeable t) to the context of the instance declaration
In the instance declaration for `BothEqAndTypeable (Wrapper t)'
Adding Typeable t to the context works, of course. But so does adding the following instance:
instance Typeable (Wrapper t) where
typeOf (Wrap x) = typeOf1 (Wrap x) `mkAppTy` typeOf x
Is there a way to get GHC to write this latter instance for me? If so, how? If not, why not?
I was hoping GHC would be able to pull the Typeable constraint from the context on the Wrap constructor, just as it did with the Eq constraint.
I think that my problems boils down to the fact that GHC explicitly disallows writing deriving instance Typeable (Wrapper t), and the standard (Typeable1 s, Typeable a) => Typeable (s a) instance can't 'look inside' s a to find a Typeable a dictionary.
If it had a
Wrapconstructor, it could pull theTypeableconstraint from it.But it doesn't have a
Wrapconstructor.The difference is that the
Eqinstance uses the value, so it's either aWrap something, where theWrapconstructor makes theEqdictionary for the wrapped type available, and everything is fine, or it's⊥, and then everything is fine too, evaluatingx == ybottoms out.Note that the derived
does not have an
Eqconstraint on the type variablea.But the
Typeableinstance must not make use of the value, so there's no bottoming out if the supplied value isn't aWrap something.Thus the derived
instance Typeable1 Wrappersuppliesbut not an unconstrained
and that unconstrained instance cannot be derived by GHC.
Hence you have to either provide a constrained
or an unconstrained
yourself.