
Hello, I am trying to create some code involving type families and default signatures. I am getting a type error that I do not understand (as far as I can see the error is wrong). I removed all code that doesn't contribute to the error:
{-# LANGUAGE DeriveGeneric, UndecidableInstances, DefaultSignatures, TypeOperators, GADTs, FlexibleContexts, TypeFamilies, FlexibleInstances #-} module Database.DSH.Problem where
import GHC.Generics
data Exp a where UnitE :: Exp () ListE :: [Exp a] -> Exp [Exp a]
class GenericQA f where type GRep f type AltGRep f type AltGRep f = [Exp (GRep f)] gToExp :: f a -> Exp (GRep f) emptyAlt :: Exp (AltGRep f) default emptyAlt :: (AltGRep f ~ [Exp (GRep f)]) => Exp (AltGRep f) emptyAlt = ListE []
instance GenericQA U1 where type GRep U1 = () gToExp U1 = UnitE
This gives me the following type errors:
Problem.hs:19:10: Couldn't match type `AltGRep f0' with `[Exp ()]' Expected type: AltGRep U1 Actual type: AltGRep f0 Expected type: Exp (AltGRep U1) Actual type: Exp (AltGRep f0) In the expression: (Database.DSH.Problem.$gdmemptyAlt) In an equation for `emptyAlt': emptyAlt = (Database.DSH.Problem.$gdmemptyAlt)
Problem.hs:19:10: Couldn't match type `GRep f0' with `()' Expected type: [Exp (GRep f0)] Actual type: AltGRep f0 In the expression: (Database.DSH.Problem.$gdmemptyAlt) In an equation for `emptyAlt': emptyAlt = (Database.DSH.Problem.$gdmemptyAlt) In the instance declaration for `GenericQA U1'
In this error the type variable f0 is mentioned but as far as I understand it f should have been instantiated to U1 and not to a variable f0. I've tried many variations on the default type signature for emptyAlt but haven't found any that doesn't result in this error. Can somebody explain what is going wrong here? Cheers, Jeroen