New syntax for stand-alone deriving. Implemented fully.
[ghc-hetmet.git] / compiler / typecheck / TcInstDcls.lhs
index 2d59676..3236b67 100644 (file)
@@ -146,12 +146,13 @@ Gather up the instance declarations from their various sources
 tcInstDecls1   -- Deal with both source-code and imported instance decls
    :: [LTyClDecl Name]         -- For deriving stuff
    -> [LInstDecl Name]         -- Source code instance decls
+   -> [LDerivDecl Name]                -- Source code stand-alone deriving decls
    -> TcM (TcGblEnv,           -- The full inst env
           [InstInfo],          -- Source-code instance decls to process; 
                                -- contains all dfuns for this module
           HsValBinds Name)     -- Supporting bindings for derived instances
 
-tcInstDecls1 tycl_decls inst_decls
+tcInstDecls1 tycl_decls inst_decls deriv_decls
   = checkNoErrs $
     do {        -- Stop if addInstInfos etc discovers any errors
                -- (they recover, so that we get more than one error each
@@ -178,14 +179,11 @@ tcInstDecls1 tycl_decls inst_decls
                -- (3) Instances from generic class declarations
        ; generic_inst_info <- getGenericInstances clas_decls
 
-               -- Next, construct the instance environment so far, consisting
-               -- of 
-               --   a) local instance decls
-               --   b) generic instances
-               --   c) local family instance decls
-       ; addInsts local_info         $ do {
-       ; addInsts generic_inst_info  $ do {
-       ; addFamInsts at_idx_tycon    $ do {
+       -- (3) Compute instances from "deriving" clauses; 
+       -- This stuff computes a context for the derived instance decl, so it
+       -- needs to know about all the instances possible; hence inst_env4
+    tcDeriving tycl_decls      `thenM` \ (deriv_inst_info, deriv_binds) ->
+    addInsts deriv_inst_info   $
 
                -- (4) Compute instances from "deriving" clauses; 
                -- This stuff computes a context for the derived instance
@@ -505,11 +503,11 @@ tcInstDecl2 (InstInfo { iSpec = ispec, iBinds = NewTypeDerived mb_preds })
         ; let (cls, cls_inst_tys) = tcSplitDFunHead inst_head_ty
              cls_tycon           = classTyCon cls
              the_coercion        = make_coercion cls_tycon cls_inst_tys
-              coerced_rep_dict           = mkHsCoerce the_coercion (HsVar rep_dict_id)
+              coerced_rep_dict           = mkHsWrap the_coercion (HsVar rep_dict_id)
 
        ; body <- make_body cls_tycon cls_inst_tys sc_dict_ids coerced_rep_dict
               
-        ; return (sc_binds `snocBag` (noLoc $ VarBind dfun_id $ noLoc $ mkHsCoerce wrap_fn body)) }
+        ; return (sc_binds `snocBag` (noLoc $ VarBind dfun_id $ noLoc $ mkHsWrap wrap_fn body)) }
   where
 
       -----------------------
@@ -527,12 +525,12 @@ tcInstDecl2 (InstInfo { iSpec = ispec, iBinds = NewTypeDerived mb_preds })
           ; sc_binds <- addErrCtxt superClassCtxt (tcSimplifySuperClasses [] [] dicts)
                -- Use tcSimplifySuperClasses to avoid creating loops, for the
                -- same reason as Note [SUPERCLASS-LOOP 1] in TcSimplify
-          ; return (map instToId dicts, idCoercion, sc_binds) }
+          ; return (map instToId dicts, idHsWrapper, sc_binds) }
 
     make_wrapper inst_loc tvs theta Nothing    -- Case (b)
       = do { dicts <- newDictBndrs inst_loc theta
           ; let dict_ids = map instToId dicts
-          ; return (dict_ids, mkCoTyLams tvs <.> mkCoLams dict_ids, emptyBag) }
+          ; return (dict_ids, mkWpTyLams tvs <.> mkWpLams dict_ids, emptyBag) }
 
       -----------------------
       --       make_coercion
@@ -548,9 +546,9 @@ tcInstDecl2 (InstInfo { iSpec = ispec, iBinds = NewTypeDerived mb_preds })
        , (tycon, tc_args) <- tcSplitTyConApp last_ty   -- Should not fail
        , Just co_con <- newTyConCo_maybe tycon
        , let co = mkSymCoercion (mkTyConApp co_con tc_args)
-        = ExprCoFn (mkTyConApp cls_tycon (all_tys_but_last ++ [co]))
+        = WpCo (mkTyConApp cls_tycon (all_tys_but_last ++ [co]))
         | otherwise    -- The newtype is transparent; no need for a cast
-        = idCoercion
+        = idHsWrapper
 
       -----------------------
       --       make_body