X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Ftypecheck%2FTcInstDcls.lhs;h=ba57563806500a6094a0432f507c10db4fb1794f;hb=15cb792d18b1094e98c035dca6ecec5dad516056;hp=45338d0a1eced7142a06bad9fe3735ddb7d1f1e2;hpb=0065d5ab628975892cea1ec7303f968c3338cbe1;p=ghc-hetmet.git diff --git a/compiler/typecheck/TcInstDcls.lhs b/compiler/typecheck/TcInstDcls.lhs index 45338d0..ba57563 100644 --- a/compiler/typecheck/TcInstDcls.lhs +++ b/compiler/typecheck/TcInstDcls.lhs @@ -14,9 +14,9 @@ import TcClassDcl ( tcMethodBind, mkMethodBind, badMethodErr, tcClassDecl2, getGenericInstances ) import TcRnMonad import TcMType ( tcSkolSigType, checkValidInstance, checkValidInstHead ) -import TcType ( mkClassPred, tcSplitSigmaTy, tcSplitDFunHead, mkTyVarTys, - SkolemInfo(InstSkol), tcSplitDFunTy ) -import Inst ( tcInstClassOp, newDicts, instToId, showLIE, +import TcType ( mkClassPred, tcSplitSigmaTy, tcSplitDFunHead, + SkolemInfo(InstSkol), tcSplitDFunTy, mkFunTy ) +import Inst ( newDictBndr, newDictBndrs, instToId, showLIE, getOverlapFlag, tcExtendLocalInstEnv ) import InstEnv ( mkLocalInstance, instanceDFunId ) import TcDeriv ( tcDeriving ) @@ -25,11 +25,15 @@ import TcEnv ( InstInfo(..), InstBindings(..), ) import TcHsType ( kcHsSigType, tcHsKindedType ) import TcUnify ( checkSigTyVars ) -import TcSimplify ( tcSimplifyCheck, tcSimplifySuperClasses ) -import Type ( zipOpenTvSubst, substTheta, substTys ) -import DataCon ( classDataCon ) +import TcSimplify ( tcSimplifySuperClasses ) +import Type ( zipOpenTvSubst, substTheta, mkTyConApp, mkTyVarTy ) +import Coercion ( mkAppCoercion, mkAppsCoercion ) +import TyCon ( TyCon, newTyConCo ) +import DataCon ( classDataCon, dataConTyCon, dataConInstArgTys ) import Class ( classBigSig ) -import Var ( Id, idName, idType ) +import Var ( TyVar, Id, idName, idType ) +import Id ( mkSysLocal ) +import UniqSupply ( uniqsFromSupply, splitUniqSupply ) import MkId ( mkDictFunId ) import Name ( Name, getSrcLoc ) import Maybe ( catMaybes ) @@ -51,7 +55,6 @@ pass, when the class-instance envs and GVE contain all the info from all the instance and value decls. Indeed that's the reason we need two passes over the instance decls. - Here is the overall algorithm. Assume that we have an instance declaration @@ -176,7 +179,8 @@ tcLocalInstDecl1 :: LInstDecl Name -- Type-check all the stuff before the "where" -- -- We check for respectable instance type, and context -tcLocalInstDecl1 decl@(L loc (InstDecl poly_ty binds uprags)) +tcLocalInstDecl1 decl@(L loc (InstDecl poly_ty binds uprags ats)) + -- !!!TODO: Handle the `ats' parameter!!! -=chak = -- Prime error recovery, set source location recoverM (returnM Nothing) $ setSrcSpan loc $ @@ -303,8 +307,95 @@ First comes the easy case of a non-local instance decl. \begin{code} tcInstDecl2 :: InstInfo -> TcM (LHsBinds Id) +-- Returns a binding for the dfun -tcInstDecl2 (InstInfo { iSpec = ispec, iBinds = binds }) +------------------------ +-- Derived newtype instances +-- +-- We need to make a copy of the dictionary we are deriving from +-- because we may need to change some of the superclass dictionaries +-- see Note [Newtype deriving superclasses] in TcDeriv.lhs +-- +-- In the case of a newtype, things are rather easy +-- class Show a => Foo a b where ... +-- newtype T a = MkT (Tree [a]) deriving( Foo Int ) +-- The newtype gives an FC axiom looking like +-- axiom CoT a :: Tree [a] = T a +-- +-- So all need is to generate a binding looking like +-- dfunFooT :: forall a. (Foo Int (Tree [a], Show (T a)) => Foo Int (T a) +-- dfunFooT = /\a. \(ds:Show (T a)) (df:Foo (Tree [a])). +-- case df `cast` (Foo Int (CoT a)) of +-- Foo _ op1 .. opn -> Foo ds op1 .. opn + +tcInstDecl2 (InstInfo { iSpec = ispec, + iBinds = NewTypeDerived tycon rep_tys }) + = do { let dfun_id = instanceDFunId ispec + rigid_info = InstSkol dfun_id + origin = SigOrigin rigid_info + inst_ty = idType dfun_id + ; inst_loc <- getInstLoc origin + ; (tvs, theta, inst_head) <- tcSkolSigType rigid_info inst_ty + ; dicts <- newDictBndrs inst_loc theta + ; uniqs <- newUniqueSupply + ; let (cls, cls_inst_tys) = tcSplitDFunHead inst_head + ; this_dict <- newDictBndr inst_loc (mkClassPred cls rep_tys) + ; let (rep_dict_id:sc_dict_ids) + | null dicts = [instToId this_dict] + | otherwise = map instToId dicts + + -- (Here, we are relying on the order of dictionary + -- arguments built by NewTypeDerived in TcDeriv.) + + wrap_fn = mkCoTyLams tvs <.> mkCoLams (rep_dict_id:sc_dict_ids) + + coerced_rep_dict = mkHsCoerce (co_fn tvs cls_tycon) (HsVar rep_dict_id) + + body | null sc_dict_ids = coerced_rep_dict + | otherwise = HsCase (noLoc coerced_rep_dict) $ + MatchGroup [the_match] (mkFunTy in_dict_ty inst_head) + in_dict_ty = mkTyConApp cls_tycon cls_inst_tys + + the_match = mkSimpleMatch [noLoc the_pat] the_rhs + the_rhs = mkHsConApp cls_data_con cls_inst_tys (map HsVar (sc_dict_ids ++ op_ids)) + + (uniqs1, uniqs2) = splitUniqSupply uniqs + + op_ids = zipWith (mkSysLocal FSLIT("op")) + (uniqsFromSupply uniqs1) op_tys + + dict_ids = zipWith (mkSysLocal FSLIT("dict")) + (uniqsFromSupply uniqs2) (map idType sc_dict_ids) + + the_pat = ConPatOut { pat_con = noLoc cls_data_con, pat_tvs = [], + pat_dicts = dict_ids, + pat_binds = emptyLHsBinds, + pat_args = PrefixCon (map nlVarPat op_ids), + pat_ty = in_dict_ty} + + cls_data_con = classDataCon cls + cls_tycon = dataConTyCon cls_data_con + cls_arg_tys = dataConInstArgTys cls_data_con cls_inst_tys + + n_dict_args = if length dicts == 0 then 0 else length dicts - 1 + op_tys = drop n_dict_args cls_arg_tys + + dict = mkHsCoerce wrap_fn body + ; return (unitBag (noLoc $ VarBind dfun_id (noLoc dict))) } + where + co_fn :: [TyVar] -> TyCon -> ExprCoFn + co_fn tvs cls_tycon | Just co_con <- newTyConCo tycon + = ExprCoFn (mkAppCoercion -- (mkAppsCoercion + (mkTyConApp cls_tycon []) + -- rep_tys) + (mkTyConApp co_con (map mkTyVarTy tvs))) + | otherwise + = idCoercion + +------------------------ +-- Ordinary instances + +tcInstDecl2 (InstInfo { iSpec = ispec, iBinds = VanillaInst monobinds uprags }) = let dfun_id = instanceDFunId ispec rigid_info = InstSkol dfun_id @@ -329,9 +420,11 @@ tcInstDecl2 (InstInfo { iSpec = ispec, iBinds = binds }) origin = SigOrigin rigid_info in -- Create dictionary Ids from the specified instance contexts. - newDicts InstScOrigin sc_theta' `thenM` \ sc_dicts -> - newDicts origin dfun_theta' `thenM` \ dfun_arg_dicts -> - newDicts origin [mkClassPred clas inst_tys'] `thenM` \ [this_dict] -> + getInstLoc InstScOrigin `thenM` \ sc_loc -> + newDictBndrs sc_loc sc_theta' `thenM` \ sc_dicts -> + getInstLoc origin `thenM` \ inst_loc -> + newDictBndrs inst_loc dfun_theta' `thenM` \ dfun_arg_dicts -> + newDictBndr inst_loc (mkClassPred clas inst_tys') `thenM` \ this_dict -> -- Default-method Ids may be mentioned in synthesised RHSs, -- but they'll already be in the environment. @@ -341,7 +434,7 @@ tcInstDecl2 (InstInfo { iSpec = ispec, iBinds = binds }) in tcMethods origin clas inst_tyvars' dfun_theta' inst_tys' avail_insts - op_items binds `thenM` \ (meth_ids, meth_binds) -> + op_items monobinds uprags `thenM` \ (meth_ids, meth_binds) -> -- Figure out bindings for the superclass context -- Don't include this_dict in the 'givens', else @@ -356,12 +449,7 @@ tcInstDecl2 (InstInfo { iSpec = ispec, iBinds = binds }) checkSigTyVars inst_tyvars' `thenM_` -- Deal with 'SPECIALISE instance' pragmas - let - specs = case binds of - VanillaInst _ prags -> filter isSpecInstLSig prags - other -> [] - in - tcPrags dfun_id specs `thenM` \ prags -> + tcPrags dfun_id (filter isSpecInstLSig uprags) `thenM` \ prags -> -- Create the result bindings let @@ -405,7 +493,7 @@ tcInstDecl2 (InstInfo { iSpec = ispec, iBinds = binds }) tcMethods origin clas inst_tyvars' dfun_theta' inst_tys' - avail_insts op_items (VanillaInst monobinds uprags) + avail_insts op_items monobinds uprags = -- Check that all the method bindings come from this class let sel_names = [idName sel_id | (sel_id, _) <- op_items] @@ -451,48 +539,16 @@ tcMethods origin clas inst_tyvars' dfun_theta' inst_tys' let prag_fn = mkPragFun uprags all_insts = avail_insts ++ catMaybes meth_insts - tc_method_bind = tcMethodBind inst_tyvars' dfun_theta' all_insts prag_fn + sig_fn n = Just [] -- No scoped type variables, but every method has + -- a type signature, in effect, so that we check + -- the method has the right type + tc_method_bind = tcMethodBind inst_tyvars' dfun_theta' all_insts sig_fn prag_fn meth_ids = [meth_id | (_,meth_id,_) <- meth_infos] in mapM tc_method_bind meth_infos `thenM` \ meth_binds_s -> returnM (meth_ids, unionManyBags meth_binds_s) - - --- Derived newtype instances -tcMethods origin clas inst_tyvars' dfun_theta' inst_tys' - avail_insts op_items (NewTypeDerived rep_tys) - = getInstLoc origin `thenM` \ inst_loc -> - mapAndUnzip3M (do_one inst_loc) op_items `thenM` \ (meth_ids, meth_binds, rhs_insts) -> - - tcSimplifyCheck - (ptext SLIT("newtype derived instance")) - inst_tyvars' avail_insts rhs_insts `thenM` \ lie_binds -> - - -- I don't think we have to do the checkSigTyVars thing - - returnM (meth_ids, lie_binds `unionBags` listToBag meth_binds) - - where - do_one inst_loc (sel_id, _) - = -- The binding is like "op @ NewTy = op @ RepTy" - -- Make the *binder*, like in mkMethodBind - tcInstClassOp inst_loc sel_id inst_tys' `thenM` \ meth_inst -> - - -- Make the *occurrence on the rhs* - tcInstClassOp inst_loc sel_id rep_tys' `thenM` \ rhs_inst -> - let - meth_id = instToId meth_inst - in - return (meth_id, noLoc (VarBind meth_id (nlHsVar (instToId rhs_inst))), rhs_inst) - - -- Instantiate rep_tys with the relevant type variables - -- This looks a bit odd, because inst_tyvars' are the skolemised version - -- of the type variables in the instance declaration; but rep_tys doesn't - -- have the skolemised version, so we substitute them in here - rep_tys' = substTys subst rep_tys - subst = zipOpenTvSubst inst_tyvars' (mkTyVarTys inst_tyvars') \end{code}