Massive patch for the first months work adding System FC to GHC #34
[ghc-hetmet.git] / compiler / typecheck / TcDeriv.lhs
index 601f0de..46e702c 100644 (file)
@@ -31,22 +31,22 @@ import RnEnv                ( bindLocalNames )
 import HscTypes                ( FixityEnv )
 
 import Class           ( className, classArity, classKey, classTyVars, classSCTheta, Class )
-import Type            ( zipOpenTvSubst, substTheta, pprThetaArrow, pprClassPred )
+import Type            ( zipOpenTvSubst, substTheta, pprThetaArrow, pprClassPred, mkTyVarTy )
 import ErrUtils                ( dumpIfSet_dyn )
 import MkId            ( mkDictFunId )
-import DataCon         ( isNullarySrcDataCon, isVanillaDataCon, dataConOrigArgTys )
+import DataCon         ( isNullarySrcDataCon, isVanillaDataCon, dataConOrigArgTys, dataConInstOrigArgTys )
 import Maybes          ( catMaybes )
 import RdrName         ( RdrName )
 import Name            ( Name, getSrcLoc )
 import NameSet         ( duDefs )
-import Kind            ( splitKindFunTys )
+import Type            ( splitKindFunTys )
 import TyCon           ( tyConTyVars, tyConDataCons, tyConArity, tyConHasGenerics,
                          tyConStupidTheta, isProductTyCon, isDataTyCon, newTyConRhs,
                          isEnumerationTyCon, isRecursiveTyCon, TyCon
                        )
 import TcType          ( TcType, ThetaType, mkTyVarTys, mkTyConApp, tcTyConAppTyCon,
                          isUnLiftedType, mkClassPred, tyVarsOfType,
-                         isArgTypeKind, tcEqTypes, tcSplitAppTys, mkAppTys )
+                         isSubArgTypeKind, tcEqTypes, tcSplitAppTys, mkAppTys )
 import Var             ( TyVar, tyVarKind, varName )
 import VarSet          ( mkVarSet, subVarSet )
 import PrelNames
@@ -350,6 +350,10 @@ makeDerivEqns overlap_flag tycl_decls
         mk_eqn_help gla_exts new_or_data tycon deriv_tvs clas tys
 
     ------------------------------------------------------------------
+    -- data/newtype T a = ... deriving( C t1 t2 )
+    --   leads to a call to mk_eqn_help with
+    --         tycon = T, deriv_tvs = ftv(t1,t2), clas = C, tys = [t1,t2]
+
     mk_eqn_help gla_exts DataType tycon deriv_tvs clas tys
       | Just err <- checkSideConditions gla_exts tycon deriv_tvs clas tys
       = bale_out (derivingThingErr clas tys tycon (tyConTyVars tycon) err)
@@ -434,7 +438,7 @@ makeDerivEqns overlap_flag tycl_decls
                -- We must pass the superclasses; the newtype might be an instance
                -- of them in a different way than the representation type
                -- E.g.         newtype Foo a = Foo a deriving( Show, Num, Eq )
-               -- Then the Show instance is not done via isomprphism; it shows
+               -- Then the Show instance is not done via isomorphism; it shows
                --      Foo 3 as "Foo 3"
                -- The Num instance is derived via isomorphism, but the Show superclass
                -- dictionary must the Show instance for Foo, *not* the Show dictionary
@@ -568,7 +572,7 @@ mkDataTypeEqn tycon clas
     ordinary_constraints
       = [ mkClassPred clas [arg_ty] 
         | data_con <- tyConDataCons tycon,
-          arg_ty   <- dataConOrigArgTys data_con,
+          arg_ty <- dataConInstOrigArgTys data_con (map mkTyVarTy (tyConTyVars tycon)),
           not (isUnLiftedType arg_ty)  -- No constraints for unlifted types?
         ]
 
@@ -649,7 +653,7 @@ cond_typeableOK :: Condition
 --           (b) 7 or fewer args
 cond_typeableOK (gla_exts, tycon)
   | tyConArity tycon > 7                                     = Just too_many
-  | not (all (isArgTypeKind . tyVarKind) (tyConTyVars tycon)) = Just bad_kind
+  | not (all (isSubArgTypeKind . tyVarKind) (tyConTyVars tycon)) = Just bad_kind
   | otherwise                                                = Nothing
   where
     too_many = quotes (ppr tycon) <+> ptext SLIT("has too many arguments")