[project @ 2000-10-12 13:44:59 by simonpj]
[ghc-hetmet.git] / ghc / compiler / typecheck / TcDeriv.lhs
index 59f1e2f..75f8d34 100644 (file)
@@ -183,14 +183,13 @@ context to the instance decl.  The "offending classes" are
 %************************************************************************
 
 \begin{code}
-tcDeriving  :: Module                  -- name of module under scrutiny
-           -> FixityEnv                -- for the deriving code (Show/Read.)
-           -> RnNameSupply             -- for "renaming" bits of generated code
+tcDeriving  :: PersistentRenamerState
+           -> Module                   -- name of module under scrutiny
            -> Bag InstInfo             -- What we already know about instances
-           -> TcM s (Bag InstInfo,     -- The generated "instance decls".
+           -> TcM (Bag InstInfo,       -- The generated "instance decls".
                      RenamedHsBinds)   -- Extra generated bindings
 
-tcDeriving mod fixs rn_name_supply inst_decl_infos_in
+tcDeriving prs mod inst_decl_infos_in
   = recoverTc (returnTc (emptyBag, EmptyBinds)) $
 
        -- Fish the "deriving"-related information out of the TcEnv
@@ -214,17 +213,18 @@ tcDeriving mod fixs rn_name_supply inst_decl_infos_in
     gen_taggery_Names new_inst_infos           `thenTc` \ nm_alist_etc ->
 
 
+    tcGetEnv                                   `thenNF_Tc` \ env ->
     let
        extra_mbind_list = map gen_tag_n_con_monobind nm_alist_etc
        extra_mbinds     = foldr AndMonoBinds EmptyMonoBinds extra_mbind_list
-       method_binds_s   = map (gen_bind fixs) new_inst_infos
+       method_binds_s   = map (gen_bind (tcGST env)) new_inst_infos
        mbinders         = collectLocatedMonoBinders extra_mbinds
        
        -- Rename to get RenamedBinds.
        -- The only tricky bit is that the extra_binds must scope over the
        -- method bindings for the instances.
        (rn_method_binds_s, rn_extra_binds)
-               = renameSourceCode mod rn_name_supply (
+               = renameSourceCode mod prs (
                        bindLocatedLocalsRn (ptext (SLIT("deriving"))) mbinders $ \ _ ->
                        rnTopMonoBinds extra_mbinds []          `thenRn` \ (rn_extra_binds, _) ->
                        mapRn rn_meths method_binds_s           `thenRn` \ rn_method_binds_s ->
@@ -279,7 +279,7 @@ or} has just one data constructor (e.g., tuples).
 all those.
 
 \begin{code}
-makeDerivEqns :: TcM s [DerivEqn]
+makeDerivEqns :: TcM [DerivEqn]
 
 makeDerivEqns
   = tcGetEnv                       `thenNF_Tc` \ env ->
@@ -311,7 +311,7 @@ makeDerivEqns
       = (c1 `compare` c2) `thenCmp` (t1 `compare` t2)
 
     ------------------------------------------------------------------
-    mk_eqn :: (Class, TyCon) -> NF_TcM s (Maybe DerivEqn)
+    mk_eqn :: (Class, TyCon) -> NF_TcM (Maybe DerivEqn)
        -- we swizzle the tyvars and datacons out of the tycon
        -- to make the rest of the equation
 
@@ -385,7 +385,7 @@ ordered by sorting on type varible, tv, (major key) and then class, k,
 \begin{code}
 solveDerivEqns :: Bag InstInfo
               -> [DerivEqn]
-              -> TcM s [InstInfo]      -- Solns in same order as eqns.
+              -> TcM [InstInfo]        -- Solns in same order as eqns.
                                        -- This bunch is Absolutely minimal...
 
 solveDerivEqns inst_decl_infos_in orig_eqns
@@ -402,7 +402,7 @@ solveDerivEqns inst_decl_infos_in orig_eqns
        -- compares it with the current one; finishes if they are the
        -- same, otherwise recurses with the new solutions.
        -- It fails if any iteration fails
-    iterateDeriv :: [DerivSoln] ->TcM s [InstInfo]
+    iterateDeriv :: [DerivSoln] ->TcM [InstInfo]
     iterateDeriv current_solns
       = checkNoErrsTc (iterateOnce current_solns)      `thenTc` \ (new_inst_infos, new_solns) ->
        if (current_solns == new_solns) then
@@ -436,7 +436,7 @@ solveDerivEqns inst_decl_infos_in orig_eqns
 \begin{code}
 add_solns :: Bag InstInfo                      -- The global, non-derived ones
          -> [DerivEqn] -> [DerivSoln]
-         -> NF_TcM s ([InstInfo],              -- The new, derived ones
+         -> NF_TcM ([InstInfo],                -- The new, derived ones
                       InstEnv)
     -- the eqns and solns move "in lockstep"; we have the eqns
     -- because we need the LHS info for addClassInstance.
@@ -547,7 +547,7 @@ the renamer.  What a great hack!
 -- Generate the method bindings for the required instance
 -- (paired with class name, as we need that when generating dict
 --  names.)
-gen_bind :: FixityEnv -> InstInfo -> RdrNameMonoBinds
+gen_bind :: GlobalSymbolTable -> InstInfo -> RdrNameMonoBinds
 gen_bind fixities inst
   | not (isLocallyDefined tycon) = EmptyMonoBinds
   | clas `hasKey` showClassKey   = gen_Show_binds fixities tycon
@@ -602,7 +602,7 @@ If we have a @tag2con@ function, we also generate a @maxtag@ constant.
 
 \begin{code}
 gen_taggery_Names :: [InstInfo]
-                 -> TcM s [(RdrName,   -- for an assoc list
+                 -> TcM [(RdrName,     -- for an assoc list
                             TyCon,     -- related tycon
                             TagThingWanted)]