[Haskell-cafe] Type level splices and instance deriving

Khudyakov Alexey alexey.skladnoy at gmail.com
Sat Jan 23 10:22:58 EST 2010


Hello

GHC 6.12 introduced type level splices. They are great for instances 
generation. They allow for much clearer and easier to understand code.

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.

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 } |]


--
  Khudyakov Alexey


More information about the Haskell-Cafe mailing list