[project @ 2000-11-24 09:51:38 by simonpj]
[ghc-hetmet.git] / ghc / compiler / rename / Rename.lhs
index afc43b6..9e28cd9 100644 (file)
@@ -22,20 +22,23 @@ import RnMonad
 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, 
-                         emptyAvailEnv, unitAvailEnv, availEnvElts, plusAvailEnv, groupAvails,
-                         warnUnusedImports, warnUnusedLocalBinds, warnUnusedModules,
-                         lookupOrigNames, lookupSrcName, newGlobalName, unQualInScope
+                         loadExports, loadFixDecls, loadDeprecs,
+                         tryLoadInterface )
+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, lookupModuleEnv
+                         moduleEnvElts
                        )
 import Name            ( Name, NamedThing(..), getSrcLoc,
                          nameIsLocalOrFrom, nameOccName, nameModule,
@@ -52,7 +55,8 @@ import PrelNames      ( mAIN_Name, pREL_MAIN_Name, pRELUDE_Name,
                        )
 import PrelInfo                ( derivingOccurrences )
 import Type            ( funTyCon )
-import ErrUtils                ( dumpIfSet, showPass, printErrorsAndWarnings, errorsFound )
+import ErrUtils                ( dumpIfSet, dumpIfSet_dyn, showPass, 
+                         printErrorsAndWarnings, errorsFound )
 import Bag             ( bagToList )
 import FiniteMap       ( FiniteMap, fmToList, emptyFM, lookupFM, 
                          addToFM_C, elemFM, addToFM
@@ -101,27 +105,51 @@ renameExpr :: DynFlags
           -> HomeIfaceTable -> HomeSymbolTable
           -> PersistentCompilerState 
           -> Module -> RdrNameHsExpr
-          -> IO (PersistentCompilerState, Maybe (PrintUnqualified, RenamedHsExpr))
+          -> 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,_) -> 
-
-           doptRn Opt_D_dump_rn `thenRn` \ dump_rn ->
-           ioToRnM (dumpIfSet dump_rn "Renamer:" (ppr e)) `thenRn_`
-
-           returnRn (Just (print_unqual, e)))
-       }
-
-  | otherwise
-  = do { printErrs alwaysQualify (ptext SLIT("renameExpr: Bad module context") <+> ppr this_module)
-       ; return (pcs, Nothing)
-       }
+  = do { renameSource dflags hit hst pcs this_module $
+         tryLoadInterface doc (moduleName this_module) ImportByUser 
+                                               `thenRn` \ (iface, maybe_err) ->
+         case maybe_err of {
+           Just msg -> ioToRnM (printErrs alwaysQualify 
+                                (ptext SLIT("failed to load interface for") 
+                                 <+> quotes (ppr this_module) 
+                                 <>  char ':' <+> msg)) `thenRn_`
+                       returnRn Nothing;
+           Nothing -> 
+
+         let rdr_env      = mi_globals iface
+             print_unqual = unQualInScope rdr_env
+         in 
+         initRnMS rdr_env emptyLocalFixityEnv SourceMode (rnExpr expr) 
+                                               `thenRn` \ (e,fvs) -> 
+
+         checkErrsRn                           `thenRn` \ no_errs_so_far ->
+         if not no_errs_so_far then
+               -- Found errors already, so exit now
+               doDump e [] `thenRn_` 
+               returnRn Nothing
+         else
+
+         lookupOrigNames implicit_occs                 `thenRn` \ implicit_names ->
+         slurpImpDecls (fvs `plusFV` implicit_names)   `thenRn` \ decls ->
+
+         doDump e decls  `thenRn_`
+         returnRn (Just (print_unqual, (e, decls)))
+       }}
+  where
+     implicit_occs = string_occs
+     doc = text "context for compiling expression"
+
+     doDump :: RenamedHsExpr -> [RenamedHsDecl] -> RnMG (Either IOError ())
+     doDump e decls = 
+       getDOptsRn  `thenRn` \ dflags ->
+       ioToRnM (dumpIfSet_dyn dflags Opt_D_dump_rn "Renamer:" 
+                       (vcat (ppr e : map ppr decls)))
 \end{code}
 
 
@@ -196,6 +224,18 @@ rename this_module contents@(HsModule _ _ exports imports local_decls mod_deprec
        -- CHECK THAT main IS DEFINED, IF REQUIRED
     checkMain this_module local_gbl_env                `thenRn_`
 
+       -- EXIT IF ERRORS FOUND
+       -- We exit here if there are any errors in the source, *before*
+       -- we attempt to slurp the decls from the interfaces, otherwise
+       -- the slurped decls may get lost when we return up the stack
+       -- to hscMain/hscExpr.
+    checkErrsRn                                        `thenRn` \ no_errs_so_far ->
+    if not no_errs_so_far then
+       -- Found errors already, so exit now
+        rnDump [] rn_local_decls               `thenRn_` 
+       returnRn Nothing
+    else
+
        -- SLURP IN ALL THE NEEDED DECLARATIONS
     implicitFVs mod_name rn_local_decls        `thenRn` \ implicit_fvs -> 
     let
@@ -207,13 +247,7 @@ rename this_module contents@(HsModule _ _ exports imports local_decls mod_deprec
     traceRn (text "Source FVs:" <+> fsep (map ppr (nameSetToList slurp_fvs)))  `thenRn_`
     slurpImpDecls slurp_fvs            `thenRn` \ rn_imp_decls ->
 
-       -- EXIT IF ERRORS FOUND
     rnDump rn_imp_decls rn_local_decls         `thenRn_` 
-    checkErrsRn                                        `thenRn` \ no_errs_so_far ->
-    if not no_errs_so_far then
-       -- Found errors already, so exit now
-       returnRn Nothing
-    else
 
        -- GENERATE THE VERSION/USAGE INFO
     mkImportInfo mod_name imports                      `thenRn` \ my_usages ->
@@ -299,9 +333,6 @@ implicitFVs mod_name decls
        -- generate code
     implicit_occs = string_occs ++ foldr ((++) . get) implicit_main decls
 
-       -- Virtually every program has error messages in it somewhere
-    string_occs = [unpackCString_RDR, unpackCStringFoldr_RDR, 
-                  unpackCStringUtf8_RDR, eqString_RDR]
 
     get (TyClD (TyData _ _ _ _ _ _ (Just deriv_classes) _ _ _))
        = concat (map get_deriv deriv_classes)
@@ -310,6 +341,10 @@ implicitFVs mod_name decls
     get_deriv cls = case lookupUFM derivingOccurrences cls of
                        Nothing   -> []
                        Just occs -> occs
+
+-- Virtually every program has error messages in it somewhere
+string_occs = [unpackCString_RDR, unpackCStringFoldr_RDR, 
+              unpackCStringUtf8_RDR, eqString_RDR]
 \end{code}
 
 \begin{code}
@@ -488,7 +523,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
@@ -565,8 +600,19 @@ 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
-    closeDecls decls needed
+       -- Record that we have now got declarations for local_names
+    recordLocalSlurps local_names      `thenRn_`
+
+       -- Do the transitive closure
+    lookupOrigNames implicit_occs      `thenRn` \ implicit_names ->
+    closeDecls decls (needed `plusFV` implicit_names)
+  where
+    implicit_occs = string_occs        -- Data type decls with record selectors,
+                               -- which may appear in the decls, need unpackCString
+                               -- and friends. It's easier to just grab them right now.
 \end{code}
 
 %*********************************************************