[project @ 2001-03-22 11:19:28 by simonpj]
[ghc-hetmet.git] / ghc / compiler / rename / RnEnv.lhs
index 9005d08..e7f101f 100644 (file)
@@ -12,25 +12,25 @@ import {-# SOURCE #-} RnHiFiles
 
 import HscTypes                ( ModIface(..) )
 import HsSyn
-import RnHsSyn         ( RenamedHsDecl )
 import RdrHsSyn                ( RdrNameIE )
 import RdrName         ( RdrName, rdrNameModule, rdrNameOcc, isQual, isUnqual, isOrig,
-                         mkRdrUnqual, mkRdrQual, qualifyRdrName, lookupRdrEnv, foldRdrEnv
+                         mkRdrUnqual, mkRdrQual, lookupRdrEnv, foldRdrEnv
                        )
 import HsTypes         ( hsTyVarName, replaceTyVarName )
 import HscTypes                ( Provenance(..), pprNameProvenance, hasBetterProv,
                          ImportReason(..), GlobalRdrEnv, GlobalRdrElt(..), AvailEnv,
                          AvailInfo, Avails, GenAvailInfo(..), NameSupply(..), 
-                         Deprecations(..), lookupDeprec
+                         Deprecations(..), lookupDeprec,
+                         extendLocalRdrEnv
                        )
 import RnMonad
 import Name            ( Name,
-                         getSrcLoc, 
+                         getSrcLoc, nameIsLocalOrFrom,
                          mkLocalName, mkGlobalName,
                          mkIPName, nameOccName, nameModule_maybe,
-                         setNameModuleAndLoc, mkNameEnv
+                         setNameModuleAndLoc
                        )
-import Name            ( extendNameEnv_C, plusNameEnv_C, nameEnvElts )
+import NameEnv
 import NameSet
 import OccName         ( OccName, occNameUserString, occNameFlavour )
 import Module          ( ModuleName, moduleName, mkVanillaModule, 
@@ -42,7 +42,8 @@ import PrelNames      ( mkUnboundName, syntaxList, SyntaxMap, vanillaSyntaxMap,
                          boolTyConName, funTyConName,
                          unpackCStringName, unpackCStringFoldrName, unpackCStringUtf8Name,
                          eqStringName, printName, 
-                         hasKey, fractionalClassKey, numClassKey
+                         hasKey, fractionalClassKey, numClassKey,
+                         bindIOName, returnIOName, failIOName
                        )
 import TysWiredIn      ( unitTyCon )   -- A little odd
 import FiniteMap
@@ -193,16 +194,29 @@ lookupBndrRn rdr_name
          Nothing   -> lookupTopBndrRn rdr_name
 
 lookupTopBndrRn rdr_name
+-- Look up a top-level local binder.   We may be looking up an unqualified 'f',
+-- and there may be several imported 'f's too, which must not confuse us.
+-- So we have to filter out the non-local ones.
+-- A separate function (importsFromLocalDecls) reports duplicate top level
+-- decls, so here it's safe just to choose an arbitrary one.
   = getModeRn  `thenRn` \ mode ->
     if isInterfaceMode mode
        then lookupIfaceName rdr_name   
-       else     -- Source mode, so look up a *qualified* version
-                -- of the name, so that we get the right one even
-                -- if there are many with the same occ name
-                -- There must *be* a binding
-               getModuleRn             `thenRn` \ mod ->
-               getGlobalNameEnv        `thenRn` \ global_env ->
-               lookupSrcName global_env (qualifyRdrName (moduleName mod) rdr_name)
+    else 
+    getModuleRn                `thenRn` \ mod ->
+    getGlobalNameEnv   `thenRn` \ global_env ->
+    case lookup_local mod global_env rdr_name of
+       Just name -> returnRn name
+       Nothing   -> failWithRn (mkUnboundName rdr_name)
+                               (unknownNameErr rdr_name)
+  where
+    lookup_local mod global_env rdr_name
+      = case lookupRdrEnv global_env rdr_name of
+         Nothing   -> Nothing
+         Just gres -> case [n | GRE n _ _ <- gres, nameIsLocalOrFrom mod n] of
+                        []     -> Nothing
+                        (n:ns) -> Just n
+
 
 -- lookupSigOccRn is used for type signatures and pragmas
 -- Is this valid?
@@ -350,39 +364,20 @@ lookupSysBinder rdr_name
 %*                                                     *
 %*********************************************************
 
-@addImplicitFVs@ forces the renamer to slurp in some things which aren't
+@getXImplicitFVs@ forces the renamer to slurp in some things which aren't
 mentioned explicitly, but which might be needed by the type checker.
 
 \begin{code}
-addImplicitFVs :: GlobalRdrEnv
-              -> Maybe (ModuleName, [RenamedHsDecl])   -- Nothing when compling an expression
-              -> FreeVars                              -- Free in the source
-              -> RnMG (FreeVars, SyntaxMap)            -- Augmented source free vars
-
-addImplicitFVs gbl_env maybe_mod source_fvs
-  =    -- Find out what re-bindable names to use for desugaring
-     rnSyntaxNames gbl_env source_fvs          `thenRn` \ (source_fvs1, sugar_map) ->
-
-       -- Find implicit FVs thade
-    extra_implicits maybe_mod          `thenRn` \ extra_fvs ->
-    
-    let
-       implicit_fvs = ubiquitousNames `plusFV` extra_fvs
-       slurp_fvs    = implicit_fvs `plusFV` source_fvs1
-               -- It's important to do the "plus" this way round, so that
-               -- when compiling the prelude, locally-defined (), Bool, etc
-               -- override the implicit ones. 
-    in
-    returnRn (slurp_fvs, sugar_map)
-
+getImplicitStmtFVs     -- Compiling a statement
+  = returnRn (mkFVs [printName, bindIOName, returnIOName, failIOName]
+             `plusFV` ubiquitousNames)
+               -- These are all needed implicitly when compiling a statement
+               -- See TcModule.tc_stmts
+
+getImplicitModuleFVs mod_name decls    -- Compiling a module
+  = lookupOrigNames deriv_occs         `thenRn` \ deriving_names ->
+    returnRn (deriving_names `plusFV` implicit_main `plusFV` ubiquitousNames)
   where
-    extra_implicits Nothing            -- Compiling an expression
-      = returnRn (unitFV printName)    -- print :: a -> IO () may be needed later
-
-    extra_implicits (Just (mod_name, decls))   -- Compiling a module
-      = lookupOrigNames deriv_occs             `thenRn` \ deriving_names ->
-       returnRn (deriving_names `plusFV` implicit_main)
-      where
        -- Add occurrences for IO or PrimIO
        implicit_main |  mod_name == mAIN_Name
                      || mod_name == pREL_MAIN_Name = unitFV ioTyConName
@@ -540,10 +535,8 @@ bindCoreLocalsRn (b:bs) thing_inside = bindCoreLocalRn b   $ \ name' ->
 
 bindLocalNames names enclosed_scope
   = getLocalNameEnv            `thenRn` \ name_env ->
-    setLocalNameEnv (addListToRdrEnv name_env pairs)
+    setLocalNameEnv (extendLocalRdrEnv name_env names)
                    enclosed_scope
-  where
-    pairs = [(mkRdrUnqual (nameOccName n), n) | n <- names]
 
 bindLocalNamesFV names enclosed_scope
   = bindLocalNames names $
@@ -760,6 +753,8 @@ in error messages.
 
 \begin{code}
 unQualInScope :: GlobalRdrEnv -> Name -> Bool
+-- True if 'f' is in scope, and has only one binding
+-- (i.e. false if A.f and B.f are both in scope as unqualified 'f')
 unQualInScope env
   = (`elemNameSet` unqual_names)
   where