..and a bit more
[ghc-hetmet.git] / compiler / typecheck / TcInstDcls.lhs
index cf27ead..b05b551 100644 (file)
@@ -305,9 +305,13 @@ First comes the easy case of a non-local instance decl.
 tcInstDecl2 :: InstInfo -> TcM (LHsBinds Id)
 -- Returns a binding for the dfun
 
-               ** Explain superclass stuff ***
-
+--
 -- 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 )
@@ -315,26 +319,50 @@ 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 = /\a. \(ds:Show (T a) (df:Foo (Tree [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
 
 tcInstDecl2 (InstInfo { iSpec = ispec, 
-                       iBinds = NewTypeDerived rep_tys })
-  = do { let dfun_id = instanceDFunId ispec 
-             rigid_info = InstSkol dfun_id
-             origin     = SigOrigin rigid_info
-             inst_ty    = idType dfun_id
+                       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
+              maybe_co_con = newTyConCo tycon
        ; (tvs, theta, inst_head) <- tcSkolSigType rigid_info inst_ty
-       ; ASSERT( isSingleton theta )   -- Always the case for NewTypeDerived
-         rep_dict <- newDict origin (head theta)
-
-       ; let rep_dict_id = instToId rep_dict
-             cast = 
-             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)