[Haskell-cafe] Type level splices and instance deriving

John Lato jwlato at gmail.com
Mon Jan 25 07:44:22 EST 2010


Hello,

> From: Khudyakov Alexey <alexey.skladnoy at gmail.com>
> Hello
>
> However I run into problem with them. It's possible to create instance for
> type class which doesn't have superclass. If it does have one compiler
> complains that it could not deduce context. All my attempts to provide context
> fail.

What have you tried?

>
> Is that accidental limitation or because of Some Good Reason? Or just due to
> lack of understanding on my side?
>
> Below is simplest example.
>> {-# LANGUAGE FlexibleInstances #-}
>> {-# LANGUAGE TemplateHaskell #-}
>> import Language.Haskell.TH
>>
>> -- OK but require FlexibleInstances
>> makeEq :: Name -> Q [Dec]
>> makeEq name =
>>     [d| instance Eq $(conT name) where
>>           (==) = undefined
>>      |]
>>
>> -- Could not deduce Eq context
>> makeOrd :: Name -> Q [Dec]
>> makeOrd name =
>>     [d| instance Ord $(conT name) where
>>           compare = undefined
>>      |]
>
> And GHC output:
>
> test.hs:14:17:
>    Could not deduce (Eq t) from the context ()
>      arising from the superclasses of an instance declaration
>                   at test.hs:14:17-32
>    Possible fix: add (Eq t) to the context of the instance declaration
>    In the instance declaration for `Ord t_aS5'
>    In the Template Haskell quotation
>      [d|
>          instance Ord $(conT name) where
>              { compare = undefined } |]
>    In the expression:
>        [d|
>            instance Ord $(conT name) where
>                { compare = undefined } |]

I think this will work if you add the Eq constraint in the instance definition:

makeOrd :: Name -> Q [Dec]
makeOrd name =
    [d| instance Eq $(conT name) => Ord $(conT name) where
          compare = undefined
     |]

The problem is that, when the (Ord t) instance is compiled, the
compiler needs to know where to find the (Eq t) dictionary because Eq
is a superclass of Ord.  If 't' is a concrete type, e.g. Int, the
compiler will look for the Eq instance and use it directly.  If 't' is
a type variable, as in your code, then the compiler needs to have the
Eq constraint so that it can find the dictionary.

In your case you provide an Eq instance for any type 't'.  In theory I
think the compiler could examine the instance, see that it's valid for
any 't', and use that in your definition, but I don't think it's a
good idea.  This would be an extra branch that would only apply to a
class that is instantiated for all types.  Such an instance couldn't
do anything useful; as an example your Eq instance is undefined.
That's why GHC doesn't look for instances like the one you provided
when determining type class constraints; they can't provide the
necessary functionality.

I suspect this feature could be added and then your code would
compile, but you couldn't use it for anything so there's no point to
doing so.

Cheers,
John


More information about the Haskell-Cafe mailing list