[project @ 2000-11-21 13:13:25 by simonpj]
[ghc-hetmet.git] / ghc / compiler / rename / Rename.lhs
index ad60177..67195e2 100644 (file)
@@ -4,37 +4,38 @@
 \section[Rename]{Renaming and dependency analysis passes}
 
 \begin{code}
-module Rename ( renameModule, closeIfaceDecls, checkOldIface ) where
+module Rename ( renameModule, renameExpr, closeIfaceDecls, checkOldIface ) where
 
 #include "HsVersions.h"
 
 import HsSyn
-import RdrHsSyn                ( RdrNameHsModule, RdrNameHsDecl, RdrNameDeprecation, 
+import RdrHsSyn                ( RdrNameHsModule, RdrNameHsDecl, RdrNameDeprecation, RdrNameHsExpr,
                          RdrNameTyClDecl, RdrNameRuleDecl, RdrNameInstDecl, RdrNameImportDecl
                        )
 import RnHsSyn         ( RenamedHsDecl, RenamedTyClDecl, RenamedRuleDecl, RenamedInstDecl,
-                         extractHsTyNames, 
+                         extractHsTyNames, RenamedHsExpr,
                          instDeclFVs, tyClDeclFVs, ruleDeclFVs
                        )
 
 import CmdLineOpts     ( DynFlags, DynFlag(..) )
 import RnMonad
-import RnNames         ( getGlobalNames )
+import RnExpr          ( rnExpr )
+import RnNames         ( getGlobalNames, exportsFromAvail )
 import RnSource                ( rnSourceDecls, rnTyClDecl, rnIfaceRuleDecl, rnInstDecl )
-import RnIfaces                ( slurpImpDecls, mkImportInfo, 
+import RnIfaces                ( slurpImpDecls, mkImportInfo, recordLocalSlurps,
                          getInterfaceExports, closeDecls,
                          RecompileRequired, outOfDate, recompileRequired
                        )
 import RnHiFiles       ( readIface, removeContext, loadInterface,
                          loadExports, loadFixDecls, loadDeprecs )
-import RnEnv           ( availsToNameSet, availName, 
+import RnEnv           ( availsToNameSet, availName, mkIfaceGlobalRdrEnv,
                          emptyAvailEnv, unitAvailEnv, availEnvElts, plusAvailEnv, groupAvails,
                          warnUnusedImports, warnUnusedLocalBinds, warnUnusedModules,
                          lookupOrigNames, lookupSrcName, newGlobalName, unQualInScope
                        )
 import Module           ( Module, ModuleName, WhereFrom(..),
                          moduleNameUserString, moduleName,
-                         moduleEnvElts
+                         moduleEnvElts, lookupModuleEnv
                        )
 import Name            ( Name, NamedThing(..), getSrcLoc,
                          nameIsLocalOrFrom, nameOccName, nameModule,
@@ -62,7 +63,7 @@ import Outputable
 import IO              ( openFile, IOMode(..) )
 import HscTypes                ( PersistentCompilerState, HomeIfaceTable, HomeSymbolTable, 
                          ModIface(..), WhatsImported(..), 
-                         VersionInfo(..), ImportVersion, 
+                         VersionInfo(..), ImportVersion, IsExported,
                          IfaceDecls, mkIfaceDecls, dcl_tycl, dcl_rules, dcl_insts,
                          GlobalRdrEnv, pprGlobalRdrEnv,
                          AvailEnv, GenAvailInfo(..), AvailInfo, Avails,
@@ -74,9 +75,10 @@ import List          ( partition, nub )
 
 
 
+
 %*********************************************************
 %*                                                      *
-\subsection{The main function: rename}
+\subsection{The two main wrappers}
 %*                                                      *
 %*********************************************************
 
@@ -85,24 +87,69 @@ renameModule :: DynFlags
             -> HomeIfaceTable -> HomeSymbolTable
             -> PersistentCompilerState 
             -> Module -> RdrNameHsModule 
-            -> IO (PersistentCompilerState, Maybe (PrintUnqualified, ModIface, [RenamedHsDecl]))
+            -> IO (PersistentCompilerState, Maybe (PrintUnqualified, (IsExported, ModIface, [RenamedHsDecl])))
        -- Nothing => some error occurred in the renamer
 
-renameModule dflags hit hst old_pcs this_module rdr_module
-  = do { showPass dflags "Renamer"
+renameModule dflags hit hst pcs this_module rdr_module
+  = renameSource dflags hit hst pcs this_module $
+    rename this_module rdr_module
+\end{code}
 
-               -- Initialise the renamer monad
-       ; (new_pcs, msgs, maybe_rn_stuff) <- initRn dflags hit hst old_pcs this_module 
-                                                   (rename this_module rdr_module)
 
-       ; let print_unqualified :: Name -> Bool -- Is this chap in scope unqualified?
-             print_unqualified = case maybe_rn_stuff of
-                                   Just (unqual, _, _) -> unqual
-                                   Nothing             -> alwaysQualify
+\begin{code}
+renameExpr :: DynFlags
+          -> HomeIfaceTable -> HomeSymbolTable
+          -> PersistentCompilerState 
+          -> Module -> RdrNameHsExpr
+          -> IO (PersistentCompilerState, Maybe (PrintUnqualified, (RenamedHsExpr, [RenamedHsDecl])))
+
+renameExpr dflags hit hst pcs this_module expr
+  | Just iface <- lookupModuleEnv hit this_module
+  = do { let rdr_env      = mi_globals iface
+       ; let print_unqual = unQualInScope rdr_env
+         
+       ; renameSource dflags hit hst pcs this_module $
+         initRnMS rdr_env emptyLocalFixityEnv SourceMode (rnExpr expr) `thenRn` \ (e,fvs) -> 
+         slurpImpDecls fvs                                             `thenRn` \ decls ->
+         doptRn Opt_D_dump_rn                                          `thenRn` \ dump_rn ->
+         ioToRnM (dumpIfSet dump_rn "Renamer:" (ppr e))                `thenRn_`
+         returnRn (Just (print_unqual, (e, decls)))
+       }
+
+  | otherwise
+  = do { printErrs alwaysQualify (ptext SLIT("renameExpr: Bad module context") <+> ppr this_module)
+       ; return (pcs, Nothing)
+       }
+\end{code}
+
+
+%*********************************************************
+%*                                                      *
+\subsection{The main function: rename}
+%*                                                      *
+%*********************************************************
+
+\begin{code}
+renameSource :: DynFlags
+            -> HomeIfaceTable -> HomeSymbolTable
+            -> PersistentCompilerState 
+            -> Module 
+            -> RnMG (Maybe (PrintUnqualified, r))
+            -> IO (PersistentCompilerState, Maybe (PrintUnqualified, r))
+       -- Nothing => some error occurred in the renamer
+
+renameSource dflags hit hst old_pcs this_module thing_inside
+  = do { showPass dflags "Renamer"
 
+               -- Initialise the renamer monad
+       ; (new_pcs, msgs, maybe_rn_stuff) <- initRn dflags hit hst old_pcs this_module thing_inside
 
                -- Print errors from renaming
-       ;  printErrorsAndWarnings print_unqualified msgs ;
+       ;  let print_unqual = case maybe_rn_stuff of
+                               Just (unqual, _) -> unqual
+                               Nothing          -> alwaysQualify
+
+       ;  printErrorsAndWarnings print_unqual msgs ;
 
                -- Return results.  No harm in updating the PCS
        ; if errorsFound msgs then
@@ -113,13 +160,12 @@ renameModule dflags hit hst old_pcs this_module rdr_module
 \end{code}
 
 \begin{code}
-rename :: Module -> RdrNameHsModule -> RnMG (Maybe (PrintUnqualified, ModIface, [RenamedHsDecl]))
-rename this_module contents@(HsModule _ _ _ imports local_decls mod_deprec loc)
+rename :: Module -> RdrNameHsModule -> RnMG (Maybe (PrintUnqualified, (IsExported, ModIface, [RenamedHsDecl])))
+rename this_module contents@(HsModule _ _ exports imports local_decls mod_deprec loc)
   = pushSrcLocRn loc           $
 
        -- FIND THE GLOBAL NAME ENVIRONMENT
-    getGlobalNames this_module contents        `thenRn` \ (gbl_env, local_gbl_env, 
-                                                           export_avails, global_avail_env) ->
+    getGlobalNames this_module contents        `thenRn` \ (gbl_env, local_gbl_env, all_avails@(_, global_avail_env)) ->
 
        -- Exit if we've found any errors
     checkErrsRn                                `thenRn` \ no_errs_so_far ->
@@ -129,6 +175,9 @@ rename this_module contents@(HsModule _ _ _ imports local_decls mod_deprec loc)
        returnRn Nothing 
     else
        
+       -- PROCESS EXPORT LIST 
+    exportsFromAvail mod_name exports all_avails gbl_env       `thenRn` \ export_avails ->
+       
     traceRn (text "Local top-level environment" $$ 
             nest 4 (pprGlobalRdrEnv local_gbl_env))    `thenRn_`
 
@@ -183,7 +232,7 @@ rename this_module contents@(HsModule _ _ _ imports local_decls mod_deprec loc)
 
        mod_iface = ModIface {  mi_module   = this_module,
                                mi_version  = initialVersionInfo,
-                               mi_usages = my_usages,
+                               mi_usages   = my_usages,
                                mi_boot     = False,
                                mi_orphan   = is_orphan,
                                mi_exports  = my_exports,
@@ -194,6 +243,8 @@ rename this_module contents@(HsModule _ _ _ imports local_decls mod_deprec loc)
                    }
 
        print_unqualified = unQualInScope gbl_env
+       is_exported name  = name `elemNameSet` exported_names
+       exported_names    = availsToNameSet export_avails
     in
 
        -- REPORT UNUSED NAMES, AND DEBUG DUMP 
@@ -201,7 +252,7 @@ rename this_module contents@(HsModule _ _ _ imports local_decls mod_deprec loc)
                      imports global_avail_env
                      source_fvs export_avails rn_imp_decls     `thenRn_`
 
-    returnRn (Just (print_unqualified, mod_iface, final_decls))
+    returnRn (Just (print_unqualified, (is_exported, mod_iface, final_decls)))
   where
     mod_name = moduleName this_module
 \end{code}
@@ -435,7 +486,7 @@ loadOldIface parsed_iface
                               mi_boot = False, mi_orphan = pi_orphan iface, 
                               mi_fixities = fix_env, mi_deprecs = deprec_env,
                               mi_decls   = decls,
-                              mi_globals = panic "No mi_globals in old interface"
+                              mi_globals = mkIfaceGlobalRdrEnv avails
                    }
     in
     returnRn mod_iface
@@ -512,7 +563,10 @@ closeIfaceDecls dflags hit hst pcs
        needed = unionManyNameSets (map ruleDeclFVs rule_decls) `unionNameSets`
                 unionManyNameSets (map instDeclFVs inst_decls) `unionNameSets`
                 unionManyNameSets (map tyClDeclFVs tycl_decls)
+       local_names    = foldl add emptyNameSet tycl_decls
+       add names decl = addListToNameSet names (map fst (tyClDeclSysNames decl ++ tyClDeclNames decl))
     in
+    recordLocalSlurps local_names      `thenRn_`
     closeDecls decls needed
 \end{code}
 
@@ -676,7 +730,7 @@ warnDeprecations this_mod export_avails my_deprecs used_names
        | nameIsLocalOrFrom this_mod n
        = lookupDeprec my_deprecs n 
        | otherwise
-       = case lookupIface hit pit this_mod n of
+       = case lookupIface hit pit n of
                Just iface -> lookupDeprec (mi_deprecs iface) n
                Nothing    -> pprPanic "warnDeprecations:" (ppr n)