X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Frename%2FRename.lhs;h=2d8bd929457f7bee2a8ece74f39250a122c3c956;hb=f7ecf7234c224489be8a5e63fced903b655d92ee;hp=a2900c7671d8a6971e124e282c6943d4607cc1ea;hpb=e7d21ee4f8ac907665a7e170c71d59e13a01da09;p=ghc-hetmet.git diff --git a/ghc/compiler/rename/Rename.lhs b/ghc/compiler/rename/Rename.lhs index a2900c7..2d8bd92 100644 --- a/ghc/compiler/rename/Rename.lhs +++ b/ghc/compiler/rename/Rename.lhs @@ -1,145 +1,258 @@ % -% (c) The GRASP Project, Glasgow University, 1992-1994 +% (c) The GRASP Project, Glasgow University, 1992-1996 % \section[Rename]{Renaming and dependency analysis passes} \begin{code} #include "HsVersions.h" -module Rename ( - renameModule, - - -- for completeness - Module, Bag, InPat, ProtoNamePat(..), RenamedPat(..), Name, - ProtoName, SplitUniqSupply, PreludeNameFun(..), - PreludeNameFuns(..), Maybe, Error(..), Pretty(..), PprStyle, - PrettyRep, GlobalNameFuns(..), GlobalNameFun(..), - GlobalSwitch - ) where - -import AbsSyn -import Bag ( isEmptyBag, unionBags, Bag ) -import CmdLineOpts ( GlobalSwitch(..) ) -import RenameMonad12 -import Rename1 -import Rename2 -import Rename3 -import Rename4 -import RenameAuxFuns ( PreludeNameFuns(..), GlobalNameFuns(..) ) ---import Pretty -- ToDo: rm debugging -import SplitUniq ( splitUniqSupply, SplitUniqSupply ) -import Util +module Rename ( renameModule ) where + +import PreludeGlaST ( thenPrimIO ) + +IMP_Ubiq() +IMPORT_1_3(List(partition)) + +import HsSyn +import RdrHsSyn ( RdrNameHsModule(..), RdrNameImportDecl(..) ) +import RnHsSyn ( RnName(..){-.. is for Ix hack only-}, SYN_IE(RenamedHsModule), isRnTyConOrClass, isRnWired ) + +--ToDo:rm: all for debugging only +--import Maybes +--import Name +--import Outputable +--import RnIfaces +--import PprStyle +--import Pretty +--import FiniteMap +--import Util (pprPanic, pprTrace) + +import ParseUtils ( ParsedIface(..), RdrIfaceDecl(..), RdrIfaceInst(..), + UsagesMap(..), VersionsMap(..) + ) +import RnMonad +import RnNames ( getGlobalNames, SYN_IE(GlobalNameInfo) ) +import RnSource ( rnSource ) +import RnIfaces ( rnIfaces, initIfaceCache, IfaceCache ) +import RnUtils ( SYN_IE(RnEnv), extendGlobalRnEnv, emptyRnEnv ) + +import Bag ( isEmptyBag, unionBags, unionManyBags, bagToList, listToBag ) +import CmdLineOpts ( opt_HiMap, opt_NoImplicitPrelude ) +import ErrUtils ( SYN_IE(Error), SYN_IE(Warning) ) +import FiniteMap ( emptyFM, eltsFM, fmToList, addToFM, FiniteMap ) +import Maybes ( catMaybes ) +import Name ( isLocallyDefined, mkWiredInName, getLocalName, isLocalName, + origName, + Name, RdrName(..), ExportFlag(..) + ) +--import PprStyle -- ToDo:rm +import PrelInfo ( builtinNameMaps, builtinKeysMap, SYN_IE(BuiltinNames), SYN_IE(BuiltinKeys) ) +import Pretty +import Unique ( ixClassKey ) +import UniqFM ( emptyUFM, lookupUFM, addListToUFM_C, eltsUFM ) +import UniqSupply ( splitUniqSupply ) +import Util ( panic, assertPanic{-, pprTrace ToDo:rm-} ) \end{code} -Here's what the renamer does, basically: -\begin{description} -\item[@Rename1@:] -Flattens out the declarations from the interfaces which this module -imports. The result is a new module with no imports, but with more -declarations. (Obviously, the imported declarations have ``funny -names'' [@ProtoNames@] to indicate their origin.) Handles selective -import, renaming, \& such. - -%-------------------------------------------------------------------- -\item[@Rename2@:] -Removes duplicate declarations. Duplicates can arise when two -imported interface have a signature (or whatever) for the same -thing. We check that the two are consistent and then drop one. -Considerable huff and puff to pick the one with the ``better'' -pragmatic information. - -%-------------------------------------------------------------------- -\item[@Rename3@:] -Find all the top-level-ish (i.e., global) entities, assign them -@Uniques@, and make a \tr{ProtoName -> Name} mapping for them, -in preparation for... - -%-------------------------------------------------------------------- -\item[@Rename4@:] -Actually prepare the ``renamed'' module. In sticking @Names@ on -everything, it will catch out-of-scope errors (and a couple of similar -type-variable-use errors). We also our initial dependency analysis of -the program (required before typechecking). -\end{description} +\begin{code} +renameModule :: UniqSupply + -> RdrNameHsModule + + -> IO (RenamedHsModule, -- output, after renaming + RnEnv, -- final env (for renaming derivings) + [Module], -- imported modules; for profiling + + (Name -> ExportFlag, -- export info + ([(Name,ExportFlag)], + [(Name,ExportFlag)])), + + (UsagesMap, + VersionsMap, -- version info; for usage + [Module]), -- instance modules; for iface + + Bag Error, + Bag Warning) +\end{code} + +ToDo: May want to arrange to return old interface for this module! +ToDo: Deal with instances (instance version, this module on instance list ???) \begin{code} -renameModule :: (GlobalSwitch -> Bool) -- to check cmd-line opts - -> PreludeNameFuns -- lookup funs for deeply wired-in names - -> ProtoNameModule -- input - -> SplitUniqSupply - -> (RenamedModule, -- output, after renaming - [FAST_STRING], -- Names of the imported modules - -- (profiling needs to know this) - GlobalNameFuns, -- final name funs; used later - -- to rename generated `deriving' - -- bindings. - Bag Error -- Errors, from passes 1-4 - ) - --- Very space-leak sensitive - -renameModule sw_chkr gnfs@(val_pnf, tc_pnf) - input@(Module mod_name _ _ _ _ _ _ _ _ _ _ _ _) - uniqs - = let - use_mentioned_vars = sw_chkr UseGetMentionedVars +renameModule us input@(HsModule modname _ _ imports _ _ _ _ _ _ _ _ _ _) + + = {- + let + pp_pair (n,m) = ppBesides [ppPStr m,ppChar '.',ppPStr n] in - BIND ( - BSCC("Rename1") - initRn12 mod_name (rnModule1 gnfs use_mentioned_vars input) - ESCC - ) _TO_ ((mod1, imported_module_names), errs1) -> + pprTrace "builtins:\n" (case builtinNameMaps of { (builtin_ids, builtin_tcs) -> + ppAboves [ ppCat (map pp_pair (keysFM builtin_ids)) + , ppCat (map pp_pair (keysFM builtin_tcs)) + , ppCat (map pp_pair (keysFM builtinKeysMap)) + ]}) $ + -} + -- _scc_ "rnGlobalNames" + makeHiMap opt_HiMap >>= \ hi_files -> +-- pprTrace "HiMap:\n" (ppAboves [ ppCat [ppPStr m, ppStr p] | (m,p) <- fmToList hi_files]) + initIfaceCache modname hi_files >>= \ iface_cache -> - BIND ( - BSCC("Rename2") - initRn12 mod_name (rnModule2 mod1) - ESCC - ) _TO_ (mod2, errs2) -> + fixIO ( \ ~(_, _, _, _, rec_occ_fm, ~(rec_export_fn,_)) -> + let + rec_occ_fn :: Name -> [RdrName] + rec_occ_fn n = case lookupUFM rec_occ_fm n of + Nothing -> [] + Just (rn,occs) -> occs --- pprTrace "rename2:" (ppr PprDebug mod2) ( + global_name_info = (builtinNameMaps, builtinKeysMap, rec_export_fn, rec_occ_fn) + in + getGlobalNames iface_cache global_name_info us1 input >>= + \ (occ_env, imp_mods, unqual_imps, imp_fixes, top_errs, top_warns) -> - BIND (splitUniqSupply uniqs) _TO_ (us1, us2) -> + if not (isEmptyBag top_errs) then + return (rn_panic, rn_panic, top_errs, top_warns, emptyUFM, rn_panic) + else - BIND ( - BSCC("Rename3") - initRn3 (rnModule3 gnfs imported_module_names mod2) us1 - ESCC - ) _TO_ (val_space, tc_space, v_gnf, tc_gnf, errs3) -> + -- No top-level name errors so rename source ... + -- _scc_ "rnSource" + case initRn True modname occ_env us2 + (rnSource imp_mods unqual_imps imp_fixes input) of { + ((rn_module, export_fn, module_dotdots, src_occs), src_errs, src_warns) -> + --pprTrace "renameModule:" (ppCat (map (ppr PprDebug . fst) (bagToList src_occs))) $ let - final_name_funs = (v_gnf, tc_gnf) + occ_fm :: UniqFM (RnName, [RdrName]) + + occ_list = [ (rn,(rn,[occ])) | (rn,occ) <- bagToList src_occs] + occ_fm = addListToUFM_C insert_occ emptyUFM occ_list - errs_so_far = errs1 `unionBags` errs2 `unionBags` errs3 - -- see note below about why we consult errs at this pt + insert_occ (rn,olds) (rn',[new]) = (rn, insert new olds) + + insert new [] = [new] + insert new xxs@(x:xs) = case cmp new x of LT_ -> new : xxs + EQ_ -> xxs + GT__ -> x : insert new xs + + occ_warns = map multipleOccWarn (filter multiple_occs (eltsUFM occ_fm)) + + multiple_occs (rn, (o1:o2:_)) = getLocalName o1 /= SLIT("negate") + -- the user is rarely responsible if + -- "negate" is mentioned in multiple ways + multiple_occs _ = False in - if not (isEmptyBag errs_so_far) then -- give up now - ( panic "rename", imported_module_names, final_name_funs, errs_so_far ) + return (rn_module, imp_mods, + top_errs `unionBags` src_errs, + top_warns `unionBags` src_warns `unionBags` listToBag occ_warns, + occ_fm, (export_fn, module_dotdots)) + + }) >>= \ (rn_module, imp_mods, errs_so_far, warns_so_far, occ_fm, export_stuff) -> + + if not (isEmptyBag errs_so_far) then + return (rn_panic, rn_panic, rn_panic, rn_panic, rn_panic, errs_so_far, warns_so_far) else - BIND ( - BSCC("Rename4") - initRn4 sw_chkr final_name_funs (rnModule4 mod2) us2 - ESCC - ) _TO_ (mod4, errs4) -> - - ( mod4, imported_module_names, final_name_funs, errs4 ) - BEND - BEND --- ) - BEND - BEND - BEND + + -- No errors renaming source so rename the interfaces ... + -- _scc_ "preRnIfaces" + let + -- split up all names that occurred in the source; between + -- those that are defined therein and those merely mentioned. + -- We also divide by tycon/class and value names (as usual). + + occ_rns = [ rn | (rn,_) <- eltsUFM occ_fm ] + -- all occurrence names, from this module and imported + + (defined_here, defined_elsewhere) + = partition isLocallyDefined occ_rns + + (_, imports_used) + = partition isRnWired defined_elsewhere + + (def_tcs, def_vals) = partition isRnTyConOrClass defined_here + (occ_tcs, occ_vals) = partition isRnTyConOrClass occ_rns + -- the occ stuff includes *all* occurrences, + -- including those for which we have definitions + + (orig_def_env, orig_def_dups) + = extendGlobalRnEnv emptyRnEnv (map pairify_rn def_vals) + (map pairify_rn def_tcs) + (orig_occ_env, orig_occ_dups) + = extendGlobalRnEnv emptyRnEnv (map pairify_rn occ_vals) + (map pairify_rn occ_tcs) + + -- This stuff is pretty dodgy right now: I think original + -- names and occurrence names may be getting entangled + -- when they shouldn't be... WDP 96/06 + + pairify_rn rn -- ToDo: move to Name? + = let + name = getName rn + in + (if isLocalName name + then Unqual (getLocalName name) + else case (origName "pairify_rn" name) of { OrigName m n -> + Qual m n } + , rn) + in +-- ASSERT (isEmptyBag orig_occ_dups) +-- (if (isEmptyBag orig_occ_dups) then \x->x +-- else pprTrace "orig_occ_dups:" (ppAboves [ ppCat [ppr PprDebug m, ppr PprDebug n, ppr PprDebug o] | (m,n,o) <- bagToList orig_occ_dups])) $ + ASSERT (isEmptyBag orig_def_dups) + + -- _scc_ "rnIfaces" + rnIfaces iface_cache imp_mods us3 orig_def_env orig_occ_env + rn_module (initMustHaves ++ imports_used) >>= + \ (rn_module_with_imports, final_env, + (implicit_val_fm, implicit_tc_fm), + usage_stuff, + (iface_errs, iface_warns)) -> + + return (rn_module_with_imports, + final_env, + imp_mods, + export_stuff, + usage_stuff, + errs_so_far `unionBags` iface_errs, + warns_so_far `unionBags` iface_warns) + where + rn_panic = panic "renameModule: aborted with errors" + + (us1, us') = splitUniqSupply us + (us2, us3) = splitUniqSupply us' + +initMustHaves :: [RnName] + -- things we *must* find declarations for, because the + -- compiler may eventually make reference to them (e.g., + -- class Eq) +initMustHaves + | opt_NoImplicitPrelude + = [{-no Prelude.hi, no point looking-}] + | otherwise + = [ name_fn (mkWiredInName u orig ExportAll) + | (orig@(OrigName mod str), (u, name_fn)) <- fmToList builtinKeysMap ] \end{code} -Why stop if errors in the first three passes: Suppose you're compiling -a module with a top-level definition named \tr{scaleFloat}. Sadly, -this is also a Prelude class-method name. \tr{rnModule3} will have -detected this error, but: it will also have picked (arbitrarily) one -of the two definitions for its final ``value'' name-function. If, by -chance, it should have picked the class-method... when it comes to pin -a Unique on the top-level (bogus) \tr{scaleFloat}, it will ask for the -class-method's Unique (!); it doesn't have one, and you will get a -panic. - -Another way to handle this would be for the duplicate detector to -clobber duplicates with some ``safe'' value. Then things would be -fine in \tr{rnModule4}. Maybe some other time... +\begin{code} +makeHiMap :: Maybe String -> IO (FiniteMap Module FilePath) + +makeHiMap Nothing = error "Rename.makeHiMap:no .hi map given by the GHC driver (?)" +makeHiMap (Just f) + = readFile f >>= \ cts -> + return (snag_mod emptyFM cts []) + where + -- we alternate between "snag"ging mod(ule names) and path(names), + -- accumulating names (reversed) and the final resulting map + -- as we move along. + + snag_mod map [] [] = map + snag_mod map (' ':cs) rmod = snag_path map (_PK_ (reverse rmod)) cs [] + snag_mod map (c:cs) rmod = snag_mod map cs (c:rmod) + + snag_path map mod [] rpath = addToFM map mod (reverse rpath) + snag_path map mod ('\n':cs) rpath = snag_mod (addToFM map mod (reverse rpath)) cs [] + snag_path map mod (c:cs) rpath = snag_path map mod cs (c:rpath) +\end{code} + +Warning message used herein: +\begin{code} +multipleOccWarn (name, occs) sty + = ppBesides [ppStr "warning:multiple names used to refer to `", ppr sty name, ppStr "': ", + ppInterleave ppComma (map (ppr sty) occs)] +\end{code}