[project @ 2005-10-26 12:35:12 by simonpj]
[ghc-hetmet.git] / ghc / compiler / rename / RnNames.lhs
index 7101c48..1fddb33 100644 (file)
@@ -16,8 +16,8 @@ module RnNames (
 
 import DynFlags                ( DynFlag(..), GhcMode(..) )
 import HsSyn           ( IE(..), ieName, ImportDecl(..), LImportDecl,
-                         ForeignDecl(..), HsGroup(..), HsBindGroup(..), 
-                         Sig(..), collectGroupBinders, tyClDeclNames 
+                         ForeignDecl(..), HsGroup(..), HsValBinds(..),
+                         Sig(..), collectHsBindLocatedBinders, tyClDeclNames 
                        )
 import RnEnv
 import IfaceEnv                ( ifaceExportNames )
@@ -221,11 +221,10 @@ importsFromImportDecl this_mod
                 ASSERT2( not (pkg `elem` dep_pkgs deps), ppr pkg <+> ppr (dep_pkgs deps) )
                 ([], pkg : dep_pkgs deps)
 
+       -- True <=> import M ()
        import_all = case imp_details of
-                       Just (is_hiding, ls)     -- Imports are spec'd explicitly
-                         | not is_hiding -> Just (not (null ls))
-                       _ -> Nothing            -- Everything is imported, 
-                                               -- (or almost everything [hiding])
+                       Just (is_hiding, ls) -> not is_hiding && null ls        
+                       other                -> False
 
        -- unqual_avails is the Avails that are visible in *unqualified* form
        -- We need to know this so we know what to export when we see
@@ -301,21 +300,21 @@ importsFromLocalDecls group
            ; this_mod = tcg_mod gbl_env
            ; imports = emptyImportAvails {
                          imp_env = unitModuleEnv this_mod $
-                                 mkNameSet filtered_names
+                                   mkNameSet filtered_names
                        }
            }
 
-       ; rdr_env' <- extendRdrEnvRn this_mod (tcg_rdr_env gbl_env) names
+       ; rdr_env' <- extendRdrEnvRn (tcg_rdr_env gbl_env) names
 
        ; returnM (gbl_env { tcg_rdr_env = rdr_env',
                             tcg_imports = imports `plusImportAvails` tcg_imports gbl_env }) 
        }
 
-extendRdrEnvRn :: Module -> GlobalRdrEnv -> [Name] -> RnM GlobalRdrEnv
+extendRdrEnvRn :: GlobalRdrEnv -> [Name] -> RnM GlobalRdrEnv
 -- Add the new locally-bound names one by one, checking for duplicates as
 -- we do so.  Remember that in Template Haskell the duplicates
 -- might *already be* in the GlobalRdrEnv from higher up the module
-extendRdrEnvRn mod rdr_env names
+extendRdrEnvRn rdr_env names
   = foldlM add_local rdr_env names
   where
     add_local rdr_env name
@@ -326,9 +325,7 @@ extendRdrEnvRn mod rdr_env names
        | otherwise
        = return (extendGlobalRdrEnv rdr_env new_gre)
        where
-         new_gre = GRE {gre_name = name, gre_prov = prov}
-
-    prov = LocalDef mod
+         new_gre = GRE {gre_name = name, gre_prov = LocalDef}
 \end{code}
 
 @getLocalDeclBinders@ returns the names for an @HsDecl@.  It's
@@ -338,7 +335,7 @@ used for source code.
 
 \begin{code}
 getLocalDeclBinders :: TcGblEnv -> HsGroup RdrName -> RnM [Name]
-getLocalDeclBinders gbl_env (HsGroup {hs_valds = val_decls, 
+getLocalDeclBinders gbl_env (HsGroup {hs_valds = ValBindsIn val_decls val_sigs, 
                                      hs_tyclds = tycl_decls, 
                                      hs_fords = foreign_decls })
   = do { tc_names_s <- mappM new_tc tycl_decls
@@ -354,9 +351,8 @@ getLocalDeclBinders gbl_env (HsGroup {hs_valds = val_decls,
 
     new_simple rdr_name = newTopSrcBinder mod Nothing rdr_name
 
-    sig_hs_bndrs = [nm | HsBindGroup _ lsigs _  <- val_decls, 
-                        L _ (Sig nm _) <- lsigs]
-    val_hs_bndrs = collectGroupBinders val_decls
+    sig_hs_bndrs = [nm | L _ (Sig nm _) <- val_sigs]
+    val_hs_bndrs = collectHsBindLocatedBinders val_decls
     for_hs_bndrs = [nm | L _ (ForeignImport nm _ _ _) <- foreign_decls]
 
     new_tc tc_decl 
@@ -735,7 +731,8 @@ gre_is_used used_names gre = gre_name gre `elemNameSet` used_names
 reportUnusedNames :: Maybe [Located (IE RdrName)]      -- Export list
                  -> TcGblEnv -> RnM ()
 reportUnusedNames export_decls gbl_env 
-  = do { warnUnusedTopBinds   unused_locals
+  = do { traceRn ((text "RUN") <+> (ppr (tcg_dus gbl_env)))
+       ; warnUnusedTopBinds   unused_locals
        ; warnUnusedModules    unused_imp_mods
        ; warnUnusedImports    unused_imports   
        ; warnDuplicateImports defined_and_used
@@ -848,7 +845,7 @@ reportUnusedNames export_decls gbl_env
    
     imports = tcg_imports gbl_env
 
-    direct_import_mods :: [(Module, Maybe Bool, SrcSpan)]
+    direct_import_mods :: [(Module, Bool, SrcSpan)]
        -- See the type of the imp_mods for this triple
     direct_import_mods = moduleEnvElts (imp_mods imports)
 
@@ -859,11 +856,11 @@ reportUnusedNames export_decls gbl_env
     --
     -- BUG WARNING: does not deal correctly with multiple imports of the same module
     --             becuase direct_import_mods has only one entry per module
-    unused_imp_mods = [(mod,loc) | (mod,imp,loc) <- direct_import_mods,
+    unused_imp_mods = [(mod,loc) | (mod,no_imp,loc) <- direct_import_mods,
                       not (mod `elemFM` minimal_imports1),
                       mod /= pRELUDE,
-                      imp /= Just False]
-       -- The Just False part is not to complain about
+                      not no_imp]
+       -- The not no_imp part is not to complain about
        -- import M (), which is an idiom for importing
        -- instance declarations