[project @ 2003-02-07 09:39:02 by simonpj]
[ghc-hetmet.git] / ghc / compiler / rename / RnNames.lhs
index 126ddd8..74d183c 100644 (file)
@@ -6,7 +6,7 @@
 \begin{code}
 module RnNames (
        rnImports, importsFromLocalDecls, exportsFromAvail,
-       reportUnusedNames, mkModDeps
+       reportUnusedNames, mkModDeps, main_RDR_Unqual
     ) where
 
 #include "HsVersions.h"
@@ -38,12 +38,14 @@ import HscTypes             ( Provenance(..), ImportReason(..), GlobalRdrEnv,
                          IsBootInterface,
                          availName, availNames, availsToNameSet, 
                          Deprecations(..), ModIface(..), Dependencies(..),
-                         GlobalRdrElt(..), unQualInScope, isLocalGRE
+                         GlobalRdrElt(..), unQualInScope, isLocalGRE, pprNameProvenance
                        )
-import RdrName         ( RdrName, rdrNameOcc, setRdrNameSpace, lookupRdrEnv,
-                         emptyRdrEnv, foldRdrEnv, mkRdrUnqual, isQual )
+import OccName         ( varName )
+import RdrName         ( RdrName, rdrNameOcc, setRdrNameSpace, lookupRdrEnv, rdrEnvToList,
+                         emptyRdrEnv, foldRdrEnv, rdrEnvElts, mkRdrUnqual, isQual, mkUnqual )
 import Outputable
-import Maybe           ( isJust, isNothing, catMaybes )
+import Maybe           ( isJust, isNothing, catMaybes, fromMaybe )
+import Maybes          ( orElse, expectJust )
 import ListSetOps      ( removeDups )
 import Util            ( sortLt, notNull )
 import List            ( partition, insert )
@@ -531,22 +533,39 @@ exportsFromAvail :: Maybe [RdrNameIE] -> TcRn m Avails
        -- Complains if two distinct exports have same OccName
         -- Warns about identical exports.
        -- Complains about exports items not in scope
-exportsFromAvail Nothing 
+
+exportsFromAvail exports
+ = do { TcGblEnv { tcg_rdr_env = rdr_env, 
+                  tcg_imports = imports } <- getGblEnv ;
+       exports_from_avail exports rdr_env imports }
+
+exports_from_avail Nothing rdr_env
+                  imports@(ImportAvails { imp_env = entity_avail_env })
  = do { this_mod <- getModule ;
        if moduleName this_mod == mAIN_Name then
-          return []
-              -- Export nothing; Main.$main is automatically exported
-       else
-         exportsFromAvail (Just [IEModuleContents (moduleName this_mod)])
-              -- but for all other modules export everything.
+          exports_from_avail (Just [IEVar main_RDR_Unqual]) rdr_env imports
+               -- Behave just as if we'd said module Main(main)
+               -- This is particularly important if we compile module Main,
+               -- but then use ghci to call it... we jolly well expect to
+               -- see 'main'!
+       else 
+               -- Export all locally-defined things
+               -- We do this by filtering the global RdrEnv,
+               -- keeping only things that are (a) qualified,
+               -- (b) locally defined, (c) a 'main' name
+               -- Then we look up in the entity-avail-env
+       return [ avail
+              | (rdr_name, gres) <- rdrEnvToList rdr_env,
+                isQual rdr_name,       -- Avoid duplicates
+                GRE { gre_name   = name, 
+                      gre_parent = Nothing,    -- Main things only
+                      gre_prov   = LocalDef } <- gres,
+                let avail = expectJust "exportsFromAvail" 
+                                (lookupAvailEnv entity_avail_env name)
+              ]
     }
 
-exportsFromAvail (Just exports)
- = do { TcGblEnv { tcg_imports = imports } <- getGblEnv ;
-       warn_dup_exports <- doptM Opt_WarnDuplicateExports ;
-       exports_from_avail exports warn_dup_exports imports }
-
-exports_from_avail export_items warn_dup_exports
+exports_from_avail (Just export_items) rdr_env
                   (ImportAvails { imp_qual = mod_avail_env, 
                                   imp_env  = entity_avail_env }) 
   = foldlM exports_from_item emptyExportAccum
@@ -558,19 +577,20 @@ exports_from_avail export_items warn_dup_exports
 
     exports_from_item acc@(mods, occs, avails) ie@(IEModuleContents mod)
        | mod `elem` mods       -- Duplicate export of M
-       = warnIf warn_dup_exports (dupModuleExport mod) `thenM_`
-         returnM acc
+       = do { warn_dup_exports <- doptM Opt_WarnDuplicateExports ;
+              warnIf warn_dup_exports (dupModuleExport mod) ;
+              returnM acc }
 
        | otherwise
        = case lookupModuleEnvByName mod_avail_env mod of
-           Nothing             -> addErr (modExportErr mod)    `thenM_`
-                                  returnM acc
+           Nothing -> addErr (modExportErr mod)        `thenM_`
+                      returnM acc
+
            Just avail_env
-               -> getGlobalRdrEnv              `thenM` \ global_env ->
-                  let
+               -> let
                        mod_avails = [ filtered_avail
                                     | avail <- availEnvElts avail_env,
-                                      let mb_avail = filter_unqual global_env avail,
+                                      let mb_avail = filter_unqual rdr_env avail,
                                       isJust mb_avail,
                                       let Just filtered_avail = mb_avail]
                                                
@@ -580,24 +600,23 @@ exports_from_avail export_items warn_dup_exports
                -- and others, but also internally within this item.  That is,
                -- if 'M.x' is in scope in several ways, we'll have several
                -- members of mod_avails with the same OccName.
-                  foldlM (check_occs warn_dup_exports ie) 
-                         occs mod_avails       `thenM` \ occs' ->
 
+                  foldlM (check_occs ie) occs mod_avails       `thenM` \ occs' ->
                   returnM (mod:mods, occs', avails')
 
     exports_from_item acc@(mods, occs, avails) ie
        = lookupGRE (ieName ie)                 `thenM` \ mb_gre -> 
          case mb_gre of {
-               Nothing -> addErr (unknownNameErr (ieName ie))  `thenM_`
-                          returnM acc ;
-               Just gre ->             
+           Nothing  -> addErr (unknownNameErr (ieName ie))     `thenM_`
+                       returnM acc ;
+           Just gre ->         
 
                -- Get the AvailInfo for the parent of the specified name
-         case lookupAvailEnv entity_avail_env (gre_parent gre) of {
-            Nothing -> pprPanic "exportsFromAvail" 
-                               ((ppr (ieName ie)) <+> ppr gre) ;
-            Just avail ->
-
+         let
+           parent = gre_parent gre `orElse` gre_name gre
+           avail  = expectJust "exportsFromAvail2" 
+                       (lookupAvailEnv entity_avail_env parent)
+         in
                -- Filter out the bits we want
          case filterAvail ie avail of {
            Nothing ->  -- Not enough availability
@@ -608,9 +627,9 @@ exports_from_avail export_items warn_dup_exports
 
                -- Phew!  It's OK!  Now to check the occurrence stuff!
          warnIf (not (ok_item ie avail)) (dodgyExportWarn ie)  `thenM_`
-          check_occs warn_dup_exports ie occs export_avail     `thenM` \ occs' ->
+          check_occs ie occs export_avail                      `thenM` \ occs' ->
          returnM (mods, occs', addAvail avails export_avail)
-         }}}
+         }}
 
 
 -------------------------------
@@ -628,7 +647,10 @@ filter_unqual env (AvailTC n ns)
 in_scope :: GlobalRdrEnv -> Name -> Bool
 -- Checks whether the Name is in scope unqualified, 
 -- regardless of whether it's ambiguous or not
-in_scope env n = isJust (lookupRdrEnv env (mkRdrUnqual (nameOccName n)))
+in_scope env n 
+  = case lookupRdrEnv env (mkRdrUnqual (nameOccName n)) of
+       Nothing   -> False
+       Just gres -> or [n == gre_name g | g <- gres]
 
 
 -------------------------------
@@ -639,24 +661,33 @@ ok_item (IEThingAll _) (AvailTC _ [n]) = False
 ok_item _ _ = True
 
 -------------------------------
-check_occs :: Bool -> RdrNameIE -> ExportOccMap -> AvailInfo -> TcRn m ExportOccMap
-check_occs warn_dup_exports ie occs avail 
+check_occs :: RdrNameIE -> ExportOccMap -> AvailInfo -> TcRn m ExportOccMap
+check_occs ie occs avail 
   = foldlM check occs (availNames avail)
   where
     check occs name
       = case lookupFM occs name_occ of
-         Nothing           -> returnM (addToFM occs name_occ (name, ie))
+         Nothing -> returnM (addToFM occs name_occ (name, ie))
+
          Just (name', ie') 
-           | name == name' ->  -- Duplicate export
-                               warnIf warn_dup_exports
-                                       (dupExportWarn name_occ ie ie')
-                               `thenM_` returnM occs
-
-           | otherwise     ->  -- Same occ name but different names: an error
-                               addErr (exportClashErr name name' ie ie')       `thenM_`
-                               returnM occs
+           | name == name'     -- Duplicate export
+           ->  do { warn_dup_exports <- doptM Opt_WarnDuplicateExports ;
+                    warnIf warn_dup_exports (dupExportWarn name_occ ie ie') ;
+                    returnM occs }
+
+           | otherwise         -- Same occ name but different names: an error
+           ->  do { global_env <- getGlobalRdrEnv ;
+                    addErr (exportClashErr global_env name name' ie ie') ;
+                    returnM occs }
       where
        name_occ = nameOccName name
+
+----------------------------
+main_RDR_Unqual :: RdrName
+main_RDR_Unqual = mkUnqual varName FSLIT("main")
+       -- Don't get a RdrName from PrelNames.mainName, because 
+       -- nameRdrNamegets an Orig RdrName, and we want a Qual or Unqual one.  
+       -- An Unqual one will do just fine
 \end{code}
 
 %*********************************************************
@@ -683,9 +714,11 @@ reportUnusedNames gbl_env used_names
     -- if C was brought into scope by T(..) or T(C)
     really_used_names :: NameSet
     really_used_names = used_names `unionNameSets`
-                       mkNameSet [ gre_parent gre
-                                 | gre <- defined_names,
-                                   gre_name gre `elemNameSet` used_names]
+                       mkNameSet [ parent
+                                 | GRE{ gre_name   = name, 
+                                        gre_parent = Just parent } 
+                                     <- defined_names,
+                                   name `elemNameSet` used_names]
 
        -- Collect the defined names from the in-scope environment
        -- Look for the qualified ones only, else get duplicates
@@ -747,9 +780,9 @@ reportUnusedNames gbl_env used_names
        = acc
 
        -- n is the name of the thing, p is the name of its parent
-    mk_avail n p | n/=p                           = AvailTC p [p,n]
-                | isTcOcc (nameOccName p) = AvailTC n [n]
-                | otherwise               = Avail n
+    mk_avail n (Just p)                                 = AvailTC p [p,n]
+    mk_avail n Nothing | isTcOcc (nameOccName n) = AvailTC n [n]
+                      | otherwise               = Avail n
     
     add_inst_mod m acc 
       | m `elemFM` acc = acc   -- We import something already
@@ -849,22 +882,26 @@ exportItemErr export_item
   = sep [ ptext SLIT("The export item") <+> quotes (ppr export_item),
          ptext SLIT("attempts to export constructors or class methods that are not visible here") ]
 
-exportClashErr name1 name2 ie1 ie2
-  | different_items
-  = sep [ ptext SLIT("The export items") <+> quotes (ppr ie1)
-         <+> ptext SLIT("and") <+> quotes (ppr ie2)
-       , ptext SLIT("create") <+> name_msg <+> ptext SLIT("respectively") ]
-  | otherwise
-  = sep [ ptext SLIT("The export item") <+> quotes (ppr ie1)
-       , ptext SLIT("creates") <+> name_msg ]
+exportClashErr global_env name1 name2 ie1 ie2
+  = vcat [ ptext SLIT("Conflicting exports for") <+> quotes (ppr occ) <> colon
+        , ppr_export ie1 name1 
+        , ppr_export ie2 name2  ]
   where
-    name_msg = ptext SLIT("conflicting exports for") <+> quotes (ppr name1)
-              <+> ptext SLIT("and") <+> quotes (ppr name2)
-    different_items    -- This only comes into play when we have a single
-                       -- 'module M' export item which gives rise to conflicts
-       = case (ie1,ie2) of
-               (IEModuleContents m1, IEModuleContents m2) -> m1 /= m2
-               other -> True
+    occ = nameOccName name1
+    ppr_export ie name = nest 2 (quotes (ppr ie) <+> ptext SLIT("exports") <+> 
+                                quotes (ppr name) <+> pprNameProvenance (get_gre name))
+
+       -- get_gre finds a GRE for the Name, in a very inefficient way
+       -- There isn't a more efficient way to do it, because we don't necessarily
+       -- know the RdrName under which this Name is in scope.  So we just
+       -- search linearly.  Shouldn't matter because this only happens
+       -- in an error message.
+    get_gre name
+       = case [gre | gres <- rdrEnvElts global_env,
+                     gre  <- gres,
+                     gre_name gre == name] of
+            (gre:_) -> gre
+            []      -> pprPanic "exportClashErr" (ppr name)
 
 dupDeclErr (n:ns)
   = vcat [ptext SLIT("Multiple declarations of") <+> quotes (ppr n),