[project @ 2000-11-14 08:07:11 by simonpj]
[ghc-hetmet.git] / ghc / compiler / rename / RnEnv.lhs
index 782ae26..74d6b2e 100644 (file)
@@ -11,7 +11,7 @@ module RnEnv where            -- Export everything
 import HsSyn
 import RdrHsSyn                ( RdrNameIE )
 import RdrName         ( RdrName, rdrNameModule, rdrNameOcc, isQual, isUnqual, isOrig,
-                         mkRdrUnqual, mkRdrUnqual, qualifyRdrName, lookupRdrEnv
+                         mkRdrUnqual, mkRdrUnqual, qualifyRdrName, lookupRdrEnv, foldRdrEnv
                        )
 import HsTypes         ( hsTyVarName, replaceTyVarName )
 import HscTypes                ( Provenance(..), pprNameProvenance, hasBetterProv,
@@ -20,7 +20,7 @@ import HscTypes               ( Provenance(..), pprNameProvenance, hasBetterProv,
 import RnMonad
 import Name            ( Name, NamedThing(..),
                          getSrcLoc, 
-                         mkLocalName, mkImportedLocalName, mkGlobalName,
+                         mkLocalName, mkGlobalName,
                          mkIPName, nameOccName, nameModule_maybe,
                          setNameModuleAndLoc
                        )
@@ -265,10 +265,6 @@ calls it at all I think).
 
   \fbox{{\em Jan 98: this comment is wrong: @rnHsType@ uses it quite a bit.}}
 
-For List and Tuple types it's important to get the correct
-@isLocallyDefined@ flag, which is used in turn when deciding
-whether there are any instance decls in this module are ``special''.
-The name cache should have the correct provenance, though.
 
 \begin{code}
 lookupOrigNames :: [RdrName] -> RnM d NameSet
@@ -361,7 +357,7 @@ bindCoreLocalRn rdr_name enclosed_scope
     let
        (us', us1) = splitUniqSupply us
        uniq       = uniqFromSupply us1
-       name       = mkImportedLocalName uniq (rdrNameOcc rdr_name) loc
+       name       = mkLocalName uniq (rdrNameOcc rdr_name) loc
     in
     setNameSupplyRn (us', cache, ipcache)      `thenRn_`
     let
@@ -539,11 +535,12 @@ in error messages.
 \begin{code}
 unQualInScope :: GlobalRdrEnv -> Name -> Bool
 unQualInScope env
-  = lookup
+  = (`elemNameSet` unqual_names)
   where
-    lookup name = case lookupRdrEnv env (mkRdrUnqual (nameOccName name)) of
-                          Just [(name',_)] -> name == name'
-                          other            -> False
+    unqual_names :: NameSet
+    unqual_names = foldRdrEnv add emptyNameSet env
+    add rdr_name [(name,_)] unquals | isUnqual rdr_name = addOneToNameSet unquals name
+    add _        _          unquals                    = unquals
 \end{code}
 
 
@@ -746,7 +743,7 @@ warnUnusedGroup names
        = case prov1 of
                LocalDef -> (True, getSrcLoc name1, text "Defined but not used")
 
-               NonLocalDef (UserImport mod loc _) _ 
+               NonLocalDef (UserImport mod loc _)
                        -> (True, loc, text "Imported from" <+> quotes (ppr mod) <+> text "but not used")
 
     reportable (name,_) = case occNameUserString (nameOccName name) of