..and a bit more
[ghc-hetmet.git] / compiler / typecheck / TcInstDcls.lhs
index 50640a3..b05b551 100644 (file)
@@ -319,7 +319,7 @@ tcInstDecl2 :: InstInfo -> TcM (LHsBinds Id)
 --     axiom CoT a :: Tree [a] = T a
 --
 -- So all need is to generate a binding looking like
---     dfunFooT :: forall a. (Show (T a), Foo Int (Tree [a]) => Foo Int (T a)
+--     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
@@ -332,25 +332,37 @@ tcInstDecl2 (InstInfo { iSpec = ispec,
              inst_ty      = idType dfun_id
               maybe_co_con = newTyConCo tycon
        ; (tvs, theta, inst_head) <- tcSkolSigType rigid_info inst_ty
-       ; rep_dict <- newDict origin (head theta)
-        ; if isSingleton theta then
-              return (unitBag (VarBind dfun_id $
-                case maybe_co_con of
-                  Nothing -> rep_dict
-                  Just co_con -> mkCoerce rep_dict $
-                                 mkAppCoercion (mkAppsCoercion tycon rep_tys) 
-                                               (mkTyConApp co_con tvs)))
-          else do
-         let rep_dict_id  = instToId rep_dict
-              coerced_dict = case maybe_co_con of
-                               Nothing -> rep_dict_id
-                               Just co_con -> mkCoerce rep_dict_id $
-                                 mkAppCoercion (mkAppsCoercion tycon rep_tys) 
-                                               (mkTyConApp co_con tvs)
-        ; return (unitBag (VarBind dfun_id 
-          co_fn = CoTyLams tvs <.> CoLams [rep_dict_id] <.> ExprCoFn cast
-
-       ; return (unitBag (VarBind dfun_id (HsCoerce co_fn (HsVar rep_dict_id))))
+       ; dicts <- newDicts origin theta
+       ; uniqs <- newUniqueSupply
+       ; let (rep_dict_id:sc_dict_ids) = map instToId dicts
+               -- (Here, wee are relying on the order of dictionary 
+               -- arguments built by NewTypeDerived in TcDeriv.)
+
+              wrap_fn = CoTyLams tvs <.> CoLams dict_ids
+        
+             coerced_rep_dict = mkHsCoerce co_fn (HsVar rep_dict_id)
+
+             body | null sc_dicts = coerced_rep_dict
+                  | otherwise = HsCase coerced_rep_dict $
+                                MatchGroup [the_match] inst_head
+             the_match = mkSimpleMatch [the_pat] the_rhs
+             op_ids = zipWith (mkSysLocal FSLIT("op"))
+                              (uniqsFromSupply uniqs) op_tys
+             the_pat = ConPatOut { pat_con = cls_data_con, pat_tvs = [],
+                                   pat_dicts = map (WildPat . idType) sc_dict_ids,
+                                   pat_binds = emptyDictBinds,
+                                   pat_args = PrefixCon (map VarPat op_ids), 
+                                   pat_ty = <type of pattern> }
+             the_rhs = mkHsApps (dataConWrapId cls_data_con) types sc_dict_ids (map HsVar op_ids)
+
+        ; return (unitBag (VarBind dfun_id (mkHsCoerce wrap_fn body))) }
+  where
+    co_fn :: ExprCoFn
+    co_fn | Just co_con <- newTyConCo tycon
+         = ExprCoFn (mkAppCoercion (mkAppsCoercion tycon rep_tys) 
+                                           (mkTyConApp co_con tvs))
+         | otherwise
+         = idCoerecion
 
 tcMethods origin clas inst_tyvars' dfun_theta' inst_tys' 
          avail_insts op_items (NewTypeDerived rep_tys)
@@ -539,44 +551,6 @@ tcMethods origin clas inst_tyvars' dfun_theta' inst_tys'
     mapM tc_method_bind meth_infos             `thenM` \ meth_binds_s ->
    
     returnM (meth_ids, unionManyBags meth_binds_s)
-v v v v v v v
-*************
-
-
--- Derived newtype instances
-tcMethods origin clas inst_tyvars' dfun_theta' inst_tys' 
-         avail_insts op_items (NewTypeDerived maybe_co 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}