diff options
author | simonpj <unknown> | 2000-11-08 14:52:08 +0000 |
---|---|---|
committer | simonpj <unknown> | 2000-11-08 14:52:08 +0000 |
commit | f74e9e28c66072f93150fe026f87549e2f255128 (patch) | |
tree | a1b9fd07625ff2d096e57d3c3f0ecd93e7972471 /ghc/compiler/rename | |
parent | 9c1c10c2783701db404035994b84af310021fccf (diff) | |
download | haskell-f74e9e28c66072f93150fe026f87549e2f255128.tar.gz |
[project @ 2000-11-08 14:52:06 by simonpj]
Compiles most of the Prelude; versioning still not good
Diffstat (limited to 'ghc/compiler/rename')
-rw-r--r-- | ghc/compiler/rename/Rename.lhs | 61 | ||||
-rw-r--r-- | ghc/compiler/rename/RnMonad.lhs | 10 | ||||
-rw-r--r-- | ghc/compiler/rename/RnNames.lhs | 17 |
3 files changed, 52 insertions, 36 deletions
diff --git a/ghc/compiler/rename/Rename.lhs b/ghc/compiler/rename/Rename.lhs index 75a8f6f329..023145c8a3 100644 --- a/ghc/compiler/rename/Rename.lhs +++ b/ghc/compiler/rename/Rename.lhs @@ -25,9 +25,9 @@ import RnIfaces ( slurpImpDecls, mkImportInfo, getInterfaceExports, closeDecls, RecompileRequired, outOfDate, recompileRequired ) -import RnHiFiles ( readIface, removeContext, +import RnHiFiles ( readIface, removeContext, loadInterface, loadExports, loadFixDecls, loadDeprecs ) -import RnEnv ( availsToNameSet, +import RnEnv ( availsToNameSet, availName, emptyAvailEnv, unitAvailEnv, availEnvElts, plusAvailEnv, groupAvails, warnUnusedImports, warnUnusedLocalBinds, warnUnusedModules, lookupOrigNames, lookupSrcName, newGlobalName @@ -37,11 +37,10 @@ import Module ( Module, ModuleName, WhereFrom(..), mkModuleInThisPackage, mkModuleName, moduleEnvElts ) import Name ( Name, NamedThing(..), getSrcLoc, - nameIsLocalOrFrom, - nameOccName, nameModule, + nameIsLocalOrFrom, nameOccName, nameModule, ) import Name ( mkNameEnv, nameEnvElts, extendNameEnv ) -import RdrName ( elemRdrEnv, foldRdrEnv, isQual ) +import RdrName ( rdrEnvToList, elemRdrEnv, foldRdrEnv, isQual ) import OccName ( occNameFlavour ) import NameSet import TysWiredIn ( unitTyCon, intTyCon, boolTyCon ) @@ -65,7 +64,7 @@ import HscTypes ( PersistentCompilerState, HomeIfaceTable, HomeSymbolTable, ModIface(..), WhatsImported(..), VersionInfo(..), ImportVersion, IfaceDecls, mkIfaceDecls, dcl_tycl, dcl_rules, dcl_insts, - GlobalRdrEnv, AvailEnv, GenAvailInfo(..), AvailInfo, + GlobalRdrEnv, AvailEnv, GenAvailInfo(..), AvailInfo, Avails, Provenance(..), ImportReason(..), initialVersionInfo, Deprecations(..), lookupDeprec, lookupIface ) @@ -137,7 +136,7 @@ rename this_module contents@(HsModule _ _ _ imports local_decls mod_deprec loc) -- SLURP IN ALL THE NEEDED DECLARATIONS implicitFVs mod_name rn_local_decls `thenRn` \ implicit_fvs -> let - slurp_fvs = implicit_fvs `plusFV` source_fvs + slurp_fvs = implicit_fvs `plusFV` source_fvs -- It's important to do the "plus" this way round, so that -- when compiling the prelude, locally-defined (), Bool, etc -- override the implicit ones. @@ -181,19 +180,11 @@ rename this_module contents@(HsModule _ _ _ imports local_decls mod_deprec loc) mi_deprecs = my_deprecs, mi_decls = panic "mi_decls" } - - -- The export_fvs make the exported names look just as if they - -- occurred in the source program. - -- We only need the 'parent name' of the avail; - -- that's enough to suck in the declaration. - export_fvs = availsToNameSet export_avails - used_vars = source_fvs `plusFV` export_fvs - in -- REPORT UNUSED NAMES, AND DEBUG DUMP reportUnusedNames mod_iface imports global_avail_env - used_vars rn_imp_decls `thenRn_` + source_fvs export_avails rn_imp_decls `thenRn_` returnRn (Just (mod_iface, final_decls)) where @@ -404,9 +395,7 @@ loadOldIface :: ParsedIface -> RnMG ModIface loadOldIface parsed_iface = let iface = parsed_iface - in -- RENAME IT - let mod = pi_mod iface - doc_str = ptext SLIT("need usage info from") <+> ppr mod + mod = pi_mod iface in initIfaceRnMS mod ( loadHomeDecls (pi_decls iface) `thenRn` \ decls -> @@ -523,16 +512,18 @@ closeIfaceDecls dflags hit hst pcs \begin{code} reportUnusedNames :: ModIface -> [RdrNameImportDecl] -> AvailEnv - -> NameSet + -> NameSet -- Used in this module + -> Avails -- Exported by this module -> [RenamedHsDecl] -> RnMG () reportUnusedNames my_mod_iface imports avail_env - used_names imported_decls + source_fvs export_avails imported_decls = warnUnusedModules unused_imp_mods `thenRn_` warnUnusedLocalBinds bad_locals `thenRn_` warnUnusedImports bad_imp_names `thenRn_` printMinimalImports this_mod minimal_imports `thenRn_` - warnDeprecations this_mod my_deprecs really_used_names `thenRn_` + warnDeprecations this_mod export_avails my_deprecs + really_used_names `thenRn_` traceRn (text "Used" <+> fsep (map ppr (nameSetToList used_names))) `thenRn_` returnRn () @@ -541,6 +532,11 @@ reportUnusedNames my_mod_iface imports avail_env gbl_env = mi_globals my_mod_iface my_deprecs = mi_deprecs my_mod_iface + -- The export_fvs make the exported names look just as if they + -- occurred in the source program. + export_fvs = availsToNameSet export_avails + used_names = source_fvs `plusFV` export_fvs + -- Now, a use of C implies a use of T, -- if C was brought into scope by T(..) or T(C) really_used_names = used_names `unionNameSets` @@ -637,13 +633,17 @@ reportUnusedNames my_mod_iface imports avail_env module_unused :: Module -> Bool module_unused mod = moduleName mod `elem` unused_imp_mods - -warnDeprecations this_mod my_deprecs used_names +warnDeprecations this_mod export_avails my_deprecs used_names = doptRn Opt_WarnDeprecations `thenRn` \ warn_drs -> if not warn_drs then returnRn () else - getIfacesRn `thenRn` \ ifaces -> - getHomeIfaceTableRn `thenRn` \ hit -> + -- The home modules for things in the export list + -- may not have been loaded yet; do it now, so + -- that we can see their deprecations, if any + mapRn_ load_home export_mods `thenRn_` + + getIfacesRn `thenRn` \ ifaces -> + getHomeIfaceTableRn `thenRn` \ hit -> let pit = iPIT ifaces deprecs = [ (n,txt) @@ -653,6 +653,13 @@ warnDeprecations this_mod my_deprecs used_names mapRn_ warnDeprec deprecs where + export_mods = nub [ moduleName (nameModule name) + | avail <- export_avails, + let name = availName avail, + not (nameIsLocalOrFrom this_mod name) ] + + load_home m = loadInterface (text "Check deprecations for" <+> ppr m) m ImportBySystem + lookup_deprec hit pit n | nameIsLocalOrFrom this_mod n = lookupDeprec my_deprecs n @@ -752,7 +759,7 @@ getRnStats imported_decls ifaces stats = vcat [int n_mods <+> text "interfaces read", - hsep [ int n_decls_slurped, text "class decls imported, out of", + hsep [ int n_decls_slurped, text "type/class/variable imported, out of", int (n_decls_slurped + n_decls_left), text "read"], hsep [ int n_insts_slurped, text "instance decls imported, out of", int (n_insts_slurped + n_insts_left), text "read"], diff --git a/ghc/compiler/rename/RnMonad.lhs b/ghc/compiler/rename/RnMonad.lhs index b5978923f7..edb98f8677 100644 --- a/ghc/compiler/rename/RnMonad.lhs +++ b/ghc/compiler/rename/RnMonad.lhs @@ -52,7 +52,7 @@ import RdrName ( RdrName, dummyRdrVarName, rdrNameModule, rdrNameOcc, RdrNameEnv, emptyRdrEnv, extendRdrEnv, addListToRdrEnv, rdrEnvToList, rdrEnvElts ) -import Name ( Name, OccName, NamedThing(..), getSrcLoc, +import Name ( Name, OccName, NamedThing(..), nameOccName, decode, mkLocalName, mkKnownKeyGlobal ) @@ -450,7 +450,8 @@ mapRn :: (a -> RnM d b) -> [a] -> RnM d [b] mapRn_ :: (a -> RnM d b) -> [a] -> RnM d () mapMaybeRn :: (a -> RnM d (Maybe b)) -> [a] -> RnM d [b] flatMapRn :: (a -> RnM d [b]) -> [a] -> RnM d [b] -sequenceRn :: [RnM d a] -> RnM d [a] +sequenceRn :: [RnM d a] -> RnM d [a] +sequenceRn_ :: [RnM d a] -> RnM d () foldlRn :: (b -> a -> RnM d b) -> b -> [a] -> RnM d b mapAndUnzipRn :: (a -> RnM d (b,c)) -> [a] -> RnM d ([b],[c]) fixRn :: (a -> RnM d a) -> RnM d a @@ -466,9 +467,12 @@ andRn combiner m1 m2 gdown ldown sequenceRn [] = returnRn [] sequenceRn (m:ms) = m `thenRn` \ r -> - sequenceRn ms `thenRn` \ rs -> + sequenceRn ms `thenRn` \ rs -> returnRn (r:rs) +sequenceRn_ [] = returnRn () +sequenceRn_ (m:ms) = m `thenRn_` sequenceRn_ ms + mapRn f [] = returnRn [] mapRn f (x:xs) = f x `thenRn` \ r -> diff --git a/ghc/compiler/rename/RnNames.lhs b/ghc/compiler/rename/RnNames.lhs index a66c4510bf..0e4d05111d 100644 --- a/ghc/compiler/rename/RnNames.lhs +++ b/ghc/compiler/rename/RnNames.lhs @@ -182,7 +182,7 @@ importsFromImportDecl this_mod_name is_unqual (ImportDecl imp_mod_name from qual -- then you'll get a 'B does not export AType' message. Oh well. in - filterImports imp_mod_name import_spec avails `thenRn` \ (filtered_avails, hides, explicits) -> + filterImports imp_mod_name from import_spec avails `thenRn` \ (filtered_avails, hides, explicits) -> let mk_provenance name = NonLocalDef (UserImport imp_mod iloc (name `elemNameSet` explicits)) @@ -277,6 +277,7 @@ available, and filters it through the import spec (if any). \begin{code} 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 @@ -289,10 +290,10 @@ filterImports :: ModuleName -- The module being imported -- Complains if import spec mentions things that the module doesn't export -- Warns/informs if import spec contains duplicates. -filterImports mod Nothing imports +filterImports mod from Nothing imports = returnRn (imports, [], emptyNameSet) -filterImports mod (Just (want_hiding, import_items)) total_avails +filterImports mod from (Just (want_hiding, import_items)) total_avails = flatMapRn get_item import_items `thenRn` \ avails_w_explicits -> let (item_avails, explicits_s) = unzip avails_w_explicits @@ -314,7 +315,7 @@ filterImports mod (Just (want_hiding, import_items)) total_avails -- they won't make any difference because naked entities like T -- in an import list map to TcOccs, not VarOccs. - bale_out item = addErrRn (badImportItemErr mod item) `thenRn_` + bale_out item = addErrRn (badImportItemErr mod from item) `thenRn_` returnRn [] get_item item@(IEModuleContents _) = bale_out item @@ -604,9 +605,13 @@ mk_export_fn exported_names = \name -> name `elemNameSet` exported_names %************************************************************************ \begin{code} -badImportItemErr mod ie - = sep [ptext SLIT("Module"), quotes (ppr mod), +badImportItemErr mod from ie + = sep [ptext SLIT("Module"), quotes (ppr mod), source_import, ptext SLIT("does not export"), quotes (ppr ie)] + where + source_import = case from of + ImportByUserSource -> ptext SLIT("(hi-boot interface)") + other -> empty dodgyImportWarn mod item = dodgyMsg (ptext SLIT("import")) item dodgyExportWarn item = dodgyMsg (ptext SLIT("export")) item |