[project @ 2001-12-07 07:37:43 by sof]
[ghc-hetmet.git] / ghc / compiler / rename / RnNames.lhs
index 51918de..8fe5622 100644 (file)
@@ -13,7 +13,7 @@ module RnNames (
 import CmdLineOpts     ( DynFlag(..) )
 
 import HsSyn           ( HsModule(..), HsDecl(..), IE(..), ieName, ImportDecl(..),
-                         ForeignDecl(..), ForKind(..), isDynamicExtName,
+                         ForeignDecl(..), 
                          collectLocatedHsBinders
                        )
 import RdrHsSyn                ( RdrNameIE, RdrNameImportDecl,
@@ -32,7 +32,7 @@ import NameSet
 import NameEnv
 import HscTypes                ( Provenance(..), ImportReason(..), GlobalRdrEnv,
                          GenAvailInfo(..), AvailInfo, Avails, AvailEnv, 
-                         Deprecations(..), ModIface(..)
+                         Deprecations(..), ModIface(..), emptyAvailEnv
                        )
 import RdrName         ( rdrNameOcc, setRdrNameOcc )
 import OccName         ( setOccNameSpace, dataName )
@@ -161,9 +161,10 @@ importsFromImportDecl this_mod_name (ImportDecl imp_mod_name from qual_only as_m
     else
 
        -- Complain if we import a deprecated module
-    (case deprecs of   
-       DeprecAll txt -> addWarnRn (moduleDeprec imp_mod_name txt)
-       other         -> returnRn ()
+    ifOptRn Opt_WarnDeprecations       (
+       case deprecs of 
+         DeprecAll txt -> addWarnRn (moduleDeprec imp_mod_name txt)
+         other         -> returnRn ()
     )                                                  `thenRn_`
 
        -- Filter the imports according to the import list
@@ -176,8 +177,8 @@ importsFromImportDecl this_mod_name (ImportDecl imp_mod_name from qual_only as_m
                        Just another_name -> another_name
 
        mk_prov name = NonLocalDef (UserImport imp_mod iloc (name `elemNameSet` explicits)) 
-       gbl_env      = mkGlobalRdrEnv qual_mod unqual_imp True hides mk_prov filtered_avails deprecs
-       exports      = mkExportAvails qual_mod unqual_imp gbl_env            filtered_avails
+       gbl_env      = mkGlobalRdrEnv qual_mod unqual_imp mk_prov filtered_avails hides deprecs
+       exports      = mkExportAvails qual_mod unqual_imp gbl_env hides filtered_avails
     in
     returnRn (gbl_env, exports)
 \end{code}
@@ -211,7 +212,7 @@ importsFromLocalDecls this_mod decls
        mk_prov n  = LocalDef   -- Provenance is local
        hides      = []         -- Hide nothing
 
-       gbl_env    = mkGlobalRdrEnv mod_name unqual_imp True hides mk_prov avails NoDeprecs
+       gbl_env    = mkGlobalRdrEnv mod_name unqual_imp mk_prov avails hides NoDeprecs
            -- NoDeprecs: don't complain about locally defined names
            -- For a start, we may be exporting a deprecated thing
            -- Also we may use a deprecated thing in the defn of another
@@ -219,7 +220,7 @@ importsFromLocalDecls this_mod decls
            -- the defn of a non-deprecated thing, when changing a module's 
            -- interface
 
-       exports    = mkExportAvails mod_name unqual_imp gbl_env            avails
+       exports    = mkExportAvails mod_name unqual_imp gbl_env hides avails
     in
     returnRn (gbl_env, exports)
 
@@ -243,17 +244,11 @@ getLocalDeclBinders mod (ValD binds)
     new (rdr_name, loc) = newTopBinder mod rdr_name loc        `thenRn` \ name ->
                          returnRn (Avail name)
 
-getLocalDeclBinders mod (ForD (ForeignDecl nm kind _ ext_nm _ loc))
-  | binds_haskell_name kind
+getLocalDeclBinders mod (ForD (ForeignImport nm _ _ loc))
   = newTopBinder mod nm loc        `thenRn` \ name ->
     returnRn [Avail name]
-
-  | otherwise          -- a foreign export
+getLocalDeclBinders mod (ForD _)
   = returnRn []
-  where
-    binds_haskell_name (FoImport _) = True
-    binds_haskell_name FoLabel      = True
-    binds_haskell_name FoExport     = isDynamicExtName ext_nm
 
 getLocalDeclBinders mod (FixD _)    = returnRn []
 getLocalDeclBinders mod (DeprecD _) = returnRn []
@@ -277,12 +272,12 @@ filterImports :: ModuleName                       -- The module being imported
              -> WhereFrom                      -- Tells whether it's a {-# SOURCE #-} import
              -> Maybe (Bool, [RdrNameIE])      -- Import spec; True => hiding
              -> [AvailInfo]                    -- What's available
-             -> RnMG ([AvailInfo],             -- What's actually imported
-                      [AvailInfo],             -- What's to be hidden
-                                               -- (the unqualified version, that is)
-                       -- (We need to return both the above sets, because
-                       --  the qualified version is never hidden; so we can't
-                       --  implement hiding by reducing what's imported.)
+             -> RnMG ([AvailInfo],             -- "chosens"
+                      [AvailInfo],             -- "hides"
+                       -- The true imports are "chosens" - "hides"
+                       -- (It's convenient to return both the above sets, because
+                       --  the substraction can be done more efficiently when
+                       --  building the environment.)
                       NameSet)                 -- What was imported explicitly
 
        -- Complains if import spec mentions things that the module doesn't export
@@ -315,6 +310,7 @@ filterImports mod from (Just (want_hiding, import_items)) total_avails
     bale_out item = addErrRn (badImportItemErr mod from item)  `thenRn_`
                    returnRn []
 
+    get_item :: RdrNameIE -> RnMG [(AvailInfo, [Name])]
     get_item item@(IEModuleContents _) = bale_out item
 
     get_item item@(IEThingAll _)
@@ -323,14 +319,14 @@ filterImports mod from (Just (want_hiding, import_items)) total_avails
          Just avail@(AvailTC _ [n]) ->         -- This occurs when you import T(..), but
                                                -- only export T abstractly.  The single [n]
                                                -- in the AvailTC is the type or class itself
-                                       addWarnRn (dodgyImportWarn mod item)    `thenRn_`
+                                       ifOptRn Opt_WarnMisc (addWarnRn (dodgyImportWarn mod item))     `thenRn_`
                                        returnRn [(avail, [availName avail])]
          Just avail                 -> returnRn [(avail, [availName avail])]
 
     get_item item@(IEThingAbs n)
       | want_hiding    -- hiding( C ) 
                        -- Here the 'C' can be a data constructor *or* a type/class
-      = case catMaybes [check_item item, check_item (IEThingAbs data_n)] of
+      = case catMaybes [check_item item, check_item (IEVar data_n)] of
                []     -> bale_out item
                avails -> returnRn [(a, []) | a <- avails]
                                -- The 'explicits' list is irrelevant when hiding
@@ -371,8 +367,8 @@ filterImports mod from (Just (want_hiding, import_items)) total_avails
 mkEmptyExportAvails :: ModuleName -> ExportAvails
 mkEmptyExportAvails mod_name = (unitFM mod_name [], emptyNameEnv)
 
-mkExportAvails :: ModuleName -> Bool -> GlobalRdrEnv -> [AvailInfo] -> ExportAvails
-mkExportAvails mod_name unqual_imp gbl_env avails
+mkExportAvails :: ModuleName -> Bool -> GlobalRdrEnv -> [AvailInfo] -> [AvailInfo] -> ExportAvails
+mkExportAvails mod_name unqual_imp gbl_env hides avails 
   = (mod_avail_env, entity_avail_env)
   where
     mod_avail_env = unitFM mod_name unqual_avails 
@@ -387,7 +383,7 @@ mkExportAvails mod_name unqual_imp gbl_env avails
                  | otherwise      = mapMaybe prune avails
 
     prune (Avail n) | unqual_in_scope n = Just (Avail n)
-    prune (Avail n) | otherwise                = Nothing
+                    | otherwise                = Nothing
     prune (AvailTC n ns) | null uqs     = Nothing
                         | otherwise    = Just (AvailTC n uqs)
                         where
@@ -395,8 +391,27 @@ mkExportAvails mod_name unqual_imp gbl_env avails
 
     unqual_in_scope n = unQualInScope gbl_env n
 
-    entity_avail_env = mkNameEnv [ (name,avail) | avail <- avails, 
-                                                 name  <- availNames avail]
+
+    entity_avail_env  = mkNameEnv ([ (availName avail,avail) | avail <- effective_avails ] ++
+                                       -- sigh - need to have the method/field names in
+                                       -- the environment also, so that export lists
+                                       -- can be computed precisely (cf. exportsFromAvail)
+                                  [ (name,avail) | avail <- effective_avails,
+                                                   name  <- availNames avail ])
+
+       -- remove 'hides' names from the avail list.
+    effective_avails = foldl wipeOut avails hides
+      where
+        wipeOut as (Avail n)       = mapMaybe (delName n) as
+       wipeOut as (AvailTC n ns)  = foldl wipeOut as (map Avail ns)
+
+       delName x a@(Avail n) 
+         | n == x    = Nothing
+          | otherwise = Just a
+       delName x (AvailTC n ns) 
+         = case (filter (/=x) ns) of
+             [] -> Nothing
+             xs -> Just (AvailTC n xs)
 
 plusExportAvails ::  ExportAvails ->  ExportAvails ->  ExportAvails
 plusExportAvails (m1, e1) (m2, e2)