X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Frename%2FRename.lhs;h=f080bd942ef0c320444e181e11153926c64e6c9e;hb=5f67848a9c686f64bd4960a40a0e109f286df74b;hp=bc6cfa1b6bdcdd16ac95a7615732de0840ead956;hpb=61910d306d2bf9dfabc1e1e751485af73ef1250c;p=ghc-hetmet.git diff --git a/ghc/compiler/rename/Rename.lhs b/ghc/compiler/rename/Rename.lhs index bc6cfa1..f080bd9 100644 --- a/ghc/compiler/rename/Rename.lhs +++ b/ghc/compiler/rename/Rename.lhs @@ -4,166 +4,209 @@ \section[Rename]{Renaming and dependency analysis passes} \begin{code} -module Rename ( renameModule ) where +module Rename ( renameModule, closeIfaceDecls, checkOldIface ) where #include "HsVersions.h" import HsSyn -import RdrHsSyn ( RdrNameHsModule ) -import RnHsSyn ( RenamedHsModule, RenamedHsDecl, - extractHsTyNames, extractHsCtxtTyNames +import RdrHsSyn ( RdrNameHsModule, RdrNameHsDecl, RdrNameDeprecation, + RdrNameTyClDecl, RdrNameRuleDecl, RdrNameInstDecl, RdrNameImportDecl + ) +import RnHsSyn ( RenamedHsDecl, RenamedTyClDecl, RenamedRuleDecl, RenamedInstDecl, + extractHsTyNames, + instDeclFVs, tyClDeclFVs, ruleDeclFVs ) -import CmdLineOpts ( opt_HiMap, opt_D_dump_rn_trace, - opt_D_dump_rn, opt_D_dump_rn_stats, opt_WarnDeprecations - ) +import CmdLineOpts ( DynFlags, DynFlag(..), dopt ) import RnMonad import RnNames ( getGlobalNames ) -import RnSource ( rnSourceDecls, rnDecl ) -import RnIfaces ( getImportedInstDecls, importDecl, getImportVersions, - getImportedRules, loadHomeInterface, getSlurped, removeContext +import RnSource ( rnSourceDecls, rnTyClDecl, rnIfaceRuleDecl, rnInstDecl ) +import RnIfaces ( slurpImpDecls, mkImportInfo, + getInterfaceExports, closeDecls, + RecompileRequired, outOfDate, recompileRequired + ) +import RnHiFiles ( readIface, removeContext, + loadExports, loadFixDecls, loadDeprecs ) +import RnEnv ( availName, + emptyAvailEnv, unitAvailEnv, availEnvElts, plusAvailEnv, groupAvails, + warnUnusedImports, warnUnusedLocalBinds, warnUnusedModules, + lookupOrigNames, lookupGlobalRn, newGlobalName ) -import RnEnv ( availName, availsToNameSet, - warnUnusedImports, warnUnusedLocalBinds, lookupImplicitOccRn, - FreeVars, plusFVs, plusFV, unitFV, emptyFVs, isEmptyFVs +import Module ( Module, ModuleName, WhereFrom(..), + moduleNameUserString, moduleName, + mkModuleInThisPackage, mkModuleName, moduleEnvElts ) -import Module ( Module, ModuleName, mkSearchPath, mkThisModule ) -import Name ( Name, isLocallyDefined, NamedThing(..), getSrcLoc, - nameOccName, nameUnique, isUserImportedExplicitlyName, - maybeWiredInTyConName, maybeWiredInIdName, isWiredInName +import Name ( Name, NamedThing(..), getSrcLoc, + nameIsLocalOrFrom, + nameOccName, nameModule, ) +import Name ( mkNameEnv, nameEnvElts, extendNameEnv ) +import RdrName ( elemRdrEnv ) import OccName ( occNameFlavour ) -import Id ( idType ) -import TyCon ( isSynTyCon, getSynTyConDefn ) import NameSet -import PrelMods ( mAIN_Name, pREL_MAIN_Name ) -import TysWiredIn ( unitTyCon, intTyCon, doubleTyCon, boolTyCon ) -import PrelInfo ( ioTyCon_NAME, thinAirIdNames, fractionalClassKeys, derivingOccurrences ) -import Type ( namesOfType, funTyCon ) -import ErrUtils ( printErrorsAndWarnings, dumpIfSet, ghcExit ) -import BasicTypes ( NewOrData(..) ) -import Bag ( isEmptyBag, bagToList ) -import FiniteMap ( eltsFM ) -import UniqSupply ( UniqSupply ) +import TysWiredIn ( unitTyCon, intTyCon, boolTyCon ) +import PrelNames ( mAIN_Name, pREL_MAIN_Name, pRELUDE_Name, + ioTyCon_RDR, main_RDR, + unpackCString_RDR, unpackCStringFoldr_RDR, unpackCStringUtf8_RDR, + eqString_RDR + ) +import PrelInfo ( derivingOccurrences ) +import Type ( funTyCon ) +import ErrUtils ( dumpIfSet ) +import Bag ( bagToList ) +import FiniteMap ( FiniteMap, fmToList, emptyFM, lookupFM, + addToFM_C, elemFM, addToFM + ) import UniqFM ( lookupUFM ) -import Maybes ( maybeToBool ) +import Maybes ( maybeToBool, catMaybes ) import Outputable +import IO ( openFile, IOMode(..) ) +import HscTypes ( PersistentCompilerState, HomeIfaceTable, HomeSymbolTable, + ModIface(..), WhatsImported(..), + VersionInfo(..), ImportVersion, IfaceDecls(..), + GlobalRdrEnv, AvailEnv, GenAvailInfo(..), AvailInfo, + Provenance(..), ImportReason(..), initialVersionInfo, + Deprecations(..), lookupDeprec, lookupIface + ) +import List ( partition, nub ) \end{code} +%********************************************************* +%* * +\subsection{The main function: rename} +%* * +%********************************************************* + \begin{code} -renameModule :: UniqSupply - -> RdrNameHsModule - -> IO (Maybe - ( Module - , RenamedHsModule -- Output, after renaming - , InterfaceDetails -- Interface; for interface file generation - , RnNameSupply -- Final env; for renaming derivings - , [ModuleName] -- Imported modules; for profiling - )) - -renameModule us this_mod@(HsModule mod_name vers exports imports local_decls _ loc) +renameModule :: DynFlags + -> HomeIfaceTable -> HomeSymbolTable + -> PersistentCompilerState + -> Module -> RdrNameHsModule + -> IO (PersistentCompilerState, Maybe (ModIface, [RenamedHsDecl])) + -- Nothing => some error occurred in the renamer + +renameModule dflags hit hst old_pcs this_module rdr_module = -- Initialise the renamer monad - initRn mod_name us (mkSearchPath opt_HiMap) loc - (rename this_mod) >>= - \ ((maybe_rn_stuff, dump_action), rn_errs_bag, rn_warns_bag) -> + do { + (new_pcs, errors_found, maybe_rn_stuff) + <- initRn dflags hit hst old_pcs this_module (rename this_module rdr_module) ; + + -- Return results. No harm in updating the PCS + if errors_found then + return (new_pcs, Nothing) + else + return (new_pcs, maybe_rn_stuff) + } +\end{code} - -- Check for warnings - printErrorsAndWarnings rn_errs_bag rn_warns_bag >> +\begin{code} +rename :: Module -> RdrNameHsModule -> RnMG (Maybe (ModIface, [RenamedHsDecl])) +rename this_module contents@(HsModule _ _ _ imports local_decls mod_deprec loc) + = pushSrcLocRn loc $ - -- Dump any debugging output - dump_action >> + -- FIND THE GLOBAL NAME ENVIRONMENT + getGlobalNames this_module contents `thenRn` \ (gbl_env, local_gbl_env, + export_avails, global_avail_env) -> - -- Return results - if not (isEmptyBag rn_errs_bag) then - ghcExit 1 >> return Nothing + -- Exit if we've found any errors + checkErrsRn `thenRn` \ no_errs_so_far -> + if not no_errs_so_far then + -- Found errors already, so exit now + rnDump [] [] `thenRn_` + returnRn Nothing else - return maybe_rn_stuff -\end{code} + + -- DEAL WITH DEPRECATIONS + rnDeprecs local_gbl_env mod_deprec + [d | DeprecD d <- local_decls] `thenRn` \ my_deprecs -> - -\begin{code} -rename :: RdrNameHsModule - -> RnMG (Maybe (Module, RenamedHsModule, InterfaceDetails, RnNameSupply, [ModuleName]), IO ()) -rename this_mod@(HsModule mod_name vers _ imports local_decls mod_deprec loc) - = -- FIND THE GLOBAL NAME ENVIRONMENT - getGlobalNames this_mod `thenRn` \ maybe_stuff -> - - -- CHECK FOR EARLY EXIT - if not (maybeToBool maybe_stuff) then - -- Everything is up to date; no need to recompile further - rnDump [] [] `thenRn` \ dump_action -> - returnRn (Nothing, dump_action) - else - let - Just (export_env, gbl_env, fixity_env, global_avail_env) = maybe_stuff - in + -- DEAL WITH LOCAL FIXITIES + fixitiesFromLocalDecls local_gbl_env local_decls `thenRn` \ local_fixity_env -> -- RENAME THE SOURCE - initRnMS gbl_env fixity_env SourceMode ( + initRnMS gbl_env local_fixity_env SourceMode ( rnSourceDecls local_decls ) `thenRn` \ (rn_local_decls, source_fvs) -> + -- CHECK THAT main IS DEFINED, IF REQUIRED + checkMain this_module local_gbl_env `thenRn_` + -- SLURP IN ALL THE NEEDED DECLARATIONS implicitFVs mod_name rn_local_decls `thenRn` \ implicit_fvs -> let - real_source_fvs = implicit_fvs `plusFV` source_fvs + -- The export_fvs make the exported names look just as if they + -- occurred in the source program. For the reasoning, see the + -- comments with RnIfaces.getImportVersions. + -- We only need the 'parent name' of the avail; + -- that's enough to suck in the declaration. + export_fvs = mkNameSet (map availName export_avails) + real_source_fvs = source_fvs `plusFV` export_fvs + + slurp_fvs = implicit_fvs `plusFV` real_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. in - slurpImpDecls real_source_fvs `thenRn` \ rn_imp_decls -> - let - rn_all_decls = rn_local_decls ++ rn_imp_decls - - -- COLLECT ALL DEPRECATIONS - deprec_sigs = [ ds | ValD bnds <- rn_local_decls, ds <- collectDeprecs bnds ] - deprecs = case mod_deprec of - Nothing -> deprec_sigs - Just txt -> Deprecation (IEModuleContents undefined) txt : deprec_sigs - in + 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 - rnDump rn_imp_decls rn_all_decls `thenRn` \ dump_action -> - returnRn (Nothing, dump_action) + returnRn Nothing else -- GENERATE THE VERSION/USAGE INFO - getImportVersions mod_name export_env `thenRn` \ my_usages -> - getNameSupplyRn `thenRn` \ name_supply -> + mkImportInfo mod_name imports `thenRn` \ my_usages -> - -- REPORT UNUSED NAMES - reportUnusedNames gbl_env global_avail_env - export_env - source_fvs `thenRn_` - - -- RETURN THE RENAMED MODULE + -- BUILD THE MODULE INTERFACE let - has_orphans = any isOrphanDecl rn_local_decls - direct_import_mods = [mod | ImportDecl mod _ _ _ _ _ <- imports] - renamed_module = HsModule mod_name vers - trashed_exports trashed_imports - rn_all_decls - mod_deprec - loc + -- We record fixities even for things that aren't exported, + -- so that we can change into the context of this moodule easily + fixities = mkNameEnv [ (name, fixity) + | FixitySig name fixity loc <- nameEnvElts local_fixity_env + ] + + -- Sort the exports to make them easier to compare for versions + my_exports = groupAvails this_module export_avails + + final_decls = rn_local_decls ++ rn_imp_decls + is_orphan = any (isOrphanDecl this_module) rn_local_decls + + mod_iface = ModIface { mi_module = this_module, + mi_version = initialVersionInfo, + mi_usages = my_usages, + mi_boot = False, + mi_orphan = is_orphan, + mi_exports = my_exports, + mi_globals = gbl_env, + mi_fixities = fixities, + mi_deprecs = my_deprecs, + mi_decls = panic "mi_decls" + } in - rnDump rn_imp_decls rn_all_decls `thenRn` \ dump_action -> - returnRn (Just (mkThisModule mod_name, - renamed_module, - (InterfaceDetails has_orphans my_usages export_env deprecs), - name_supply, - direct_import_mods), dump_action) + + -- REPORT UNUSED NAMES, AND DEBUG DUMP + reportUnusedNames mod_iface imports global_avail_env + real_source_fvs rn_imp_decls `thenRn_` + + returnRn (Just (mod_iface, final_decls)) where - trashed_exports = {-trace "rnSource:trashed_exports"-} Nothing - trashed_imports = {-trace "rnSource:trashed_imports"-} [] + mod_name = moduleName this_module +\end{code} - collectDeprecs EmptyBinds = [] - collectDeprecs (ThenBinds x y) = collectDeprecs x ++ collectDeprecs y - collectDeprecs (MonoBind _ sigs _) = [ d | DeprecSig d _ <- sigs ] +Checking that main is defined + +\begin{code} +checkMain :: Module -> GlobalRdrEnv -> RnMG () +checkMain this_mod local_env + | moduleName this_mod == mAIN_Name + = checkRn (main_RDR `elemRdrEnv` local_env) noMainErr + | otherwise + = returnRn () \end{code} @implicitFVs@ forces the renamer to slurp in some things which aren't @@ -171,11 +214,9 @@ mentioned explicitly, but which might be needed by the type checker. \begin{code} implicitFVs mod_name decls - = mapRn lookupImplicitOccRn implicit_occs `thenRn` \ implicit_names -> - returnRn (implicit_main `plusFV` - mkNameSet (map getName default_tycons) `plusFV` - mkNameSet thinAirIdNames `plusFV` - mkNameSet implicit_names) + = lookupOrigNames implicit_occs `thenRn` \ implicit_names -> + returnRn (mkNameSet (map getName default_tycons) `plusFV` + implicit_names) where -- Add occurrences for Int, and (), because they -- are the types to which ambigious type variables may be defaulted by @@ -189,15 +230,19 @@ implicitFVs mod_name decls -- Add occurrences for IO or PrimIO implicit_main | mod_name == mAIN_Name - || mod_name == pREL_MAIN_Name = unitFV ioTyCon_NAME - | otherwise = emptyFVs + || mod_name == pREL_MAIN_Name = [ioTyCon_RDR] + | otherwise = [] -- Now add extra "occurrences" for things that -- the deriving mechanism, or defaulting, will later need in order to -- generate code - implicit_occs = foldr ((++) . get) [] decls + implicit_occs = string_occs ++ foldr ((++) . get) implicit_main decls - get (TyClD (TyData _ _ _ _ _ (Just deriv_classes) _ _)) + -- 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) get other = [] @@ -207,22 +252,24 @@ implicitFVs mod_name decls \end{code} \begin{code} -isOrphanDecl (InstD (InstDecl inst_ty _ _ _ _)) - = not (foldNameSet ((||) . isLocallyDefined) False (extractHsTyNames (removeContext inst_ty))) +isOrphanDecl this_mod (InstD (InstDecl inst_ty _ _ _ _)) + = not (foldNameSet ((||) . nameIsLocalOrFrom this_mod) False + (extractHsTyNames (removeContext inst_ty))) -- The 'removeContext' is because of -- instance Foo a => Baz T where ... -- The decl is an orphan if Baz and T are both not locally defined, -- even if Foo *is* locally defined -isOrphanDecl (RuleD (RuleDecl _ _ _ lhs _ _)) +isOrphanDecl this_mod (RuleD (HsRule _ _ _ lhs _ _)) = check lhs where -- At the moment we just check for common LHS forms -- Expand as necessary. Getting it wrong just means -- more orphans than necessary - check (HsVar v) = not (isLocallyDefined v) + check (HsVar v) = not (nameIsLocalOrFrom this_mod v) check (HsApp f a) = check f && check a check (HsLit _) = False + check (HsOverLit _) = False check (OpApp l o _ r) = check l && check o && check r check (NegApp e _) = check e check (HsPar e) = check e @@ -231,286 +278,251 @@ isOrphanDecl (RuleD (RuleDecl _ _ _ lhs _ _)) check other = True -- Safe fall through -isOrphanDecl other = False +isOrphanDecl _ _ = False \end{code} +%********************************************************* +%* * +\subsection{Fixities} +%* * +%********************************************************* + \begin{code} -dupDefaultDeclErrRn (DefaultDecl _ locn1 : dup_things) - = pushSrcLocRn locn1 $ - addErrRn msg +fixitiesFromLocalDecls :: GlobalRdrEnv -> [RdrNameHsDecl] -> RnMG LocalFixityEnv +fixitiesFromLocalDecls gbl_env decls + = doptRn Opt_WarnUnusedBinds `thenRn` \ warn_unused -> + foldlRn (getFixities warn_unused) emptyNameEnv decls `thenRn` \ env -> + traceRn (text "fixity env" <+> vcat (map ppr (nameEnvElts env))) + `thenRn_` + returnRn env where - msg = hang (ptext SLIT("Multiple default declarations")) - 4 (vcat (map pp dup_things)) - pp (DefaultDecl _ locn) = ptext SLIT("here was another default declaration") <+> ppr locn + getFixities :: Bool -> LocalFixityEnv -> RdrNameHsDecl -> RnMG LocalFixityEnv + getFixities warn_uu acc (FixD fix) + = fix_decl warn_uu acc fix + + getFixities warn_uu acc (TyClD (ClassDecl _ _ _ _ sigs _ _ _ )) + = foldlRn (fix_decl warn_uu) acc [sig | FixSig sig <- sigs] + -- Get fixities from class decl sigs too. + getFixities warn_uu acc other_decl + = returnRn acc + + fix_decl warn_uu acc sig@(FixitySig rdr_name fixity loc) + = -- Check for fixity decl for something not declared + pushSrcLocRn loc $ + lookupGlobalRn gbl_env rdr_name `thenRn` \ maybe_name -> + case maybe_name of { + Nothing -> checkRn (not warn_uu) (unusedFixityDecl rdr_name fixity) `thenRn_` + returnRn acc ; + + Just name -> + + -- Check for duplicate fixity decl + case lookupNameEnv acc name of { + Just (FixitySig _ _ loc') -> addErrRn (dupFixityDecl rdr_name loc loc') + `thenRn_` returnRn acc ; + + Nothing -> returnRn (extendNameEnv acc name (FixitySig name fixity loc)) + }} \end{code} %********************************************************* %* * -\subsection{Slurping declarations} +\subsection{Deprecations} %* * %********************************************************* -\begin{code} -------------------------------------------------------- -slurpImpDecls source_fvs - = traceRn (text "slurpImp" <+> fsep (map ppr (nameSetToList source_fvs))) `thenRn_` +For deprecations, all we do is check that the names are in scope. +It's only imported deprecations, dealt with in RnIfaces, that we +gather them together. - -- The current slurped-set records all local things - getSlurped `thenRn` \ source_binders -> - slurpSourceRefs source_binders source_fvs `thenRn` \ (decls, needed) -> +\begin{code} +rnDeprecs :: GlobalRdrEnv -> Maybe DeprecTxt + -> [RdrNameDeprecation] -> RnMG Deprecations +rnDeprecs gbl_env Nothing [] + = returnRn NoDeprecs + +rnDeprecs gbl_env (Just txt) decls + = mapRn (addErrRn . badDeprec) decls `thenRn_` + returnRn (DeprecAll txt) + +rnDeprecs gbl_env Nothing decls + = mapRn rn_deprec decls `thenRn` \ pairs -> + returnRn (DeprecSome (mkNameEnv (catMaybes pairs))) + where + rn_deprec (Deprecation rdr_name txt loc) + = pushSrcLocRn loc $ + lookupGlobalRn gbl_env rdr_name `thenRn` \ maybe_name -> + case maybe_name of + Just n -> returnRn (Just (n,(n,txt))) + Nothing -> returnRn Nothing +\end{code} - -- And finally get everything else - closeDecls decls needed -------------------------------------------------------- -slurpSourceRefs :: NameSet -- Variables defined in source - -> FreeVars -- Variables referenced in source - -> RnMG ([RenamedHsDecl], - FreeVars) -- Un-satisfied needs --- The declaration (and hence home module) of each gate has --- already been loaded - -slurpSourceRefs source_binders source_fvs - = go_outer [] -- Accumulating decls - emptyFVs -- Unsatisfied needs - emptyFVs -- Accumulating gates - (nameSetToList source_fvs) -- Things whose defn hasn't been loaded yet - where - -- The outer loop repeatedly slurps the decls for the current gates - -- and the instance decls - - -- The outer loop is needed because consider - -- instance Foo a => Baz (Maybe a) where ... - -- It may be that @Baz@ and @Maybe@ are used in the source module, - -- but not @Foo@; so we need to chase @Foo@ too. - -- - -- We also need to follow superclass refs. In particular, 'chasing @Foo@' must - -- include actually getting in Foo's class decl - -- class Wib a => Foo a where .. - -- so that its superclasses are discovered. The point is that Wib is a gate too. - -- We do this for tycons too, so that we look through type synonyms. - - go_outer decls fvs all_gates [] - = returnRn (decls, fvs) - - go_outer decls fvs all_gates refs -- refs are not necessarily slurped yet - = traceRn (text "go_outer" <+> ppr refs) `thenRn_` - go_inner decls fvs emptyFVs refs `thenRn` \ (decls1, fvs1, gates1) -> - getImportedInstDecls (all_gates `plusFV` gates1) `thenRn` \ inst_decls -> - rnInstDecls decls1 fvs1 gates1 inst_decls `thenRn` \ (decls2, fvs2, gates2) -> - go_outer decls2 fvs2 (all_gates `plusFV` gates2) - (nameSetToList (gates2 `minusNameSet` all_gates)) - -- Knock out the all_gates because even if we don't slurp any new - -- decls we can get some apparently-new gates from wired-in names - - go_inner decls fvs gates [] - = returnRn (decls, fvs, gates) - - go_inner decls fvs gates (wanted_name:refs) - | isWiredInName wanted_name - = load_home wanted_name `thenRn_` - go_inner decls fvs (gates `plusFV` getWiredInGates wanted_name) refs +%************************************************************************ +%* * +\subsection{Grabbing the old interface file and checking versions} +%* * +%************************************************************************ - | otherwise - = importDecl wanted_name `thenRn` \ maybe_decl -> - case maybe_decl of - Nothing -> go_inner decls fvs gates refs -- No declaration... (already slurped, or local) - Just decl -> rnIfaceDecl decl `thenRn` \ (new_decl, fvs1) -> - go_inner (new_decl : decls) - (fvs1 `plusFV` fvs) - (gates `plusFV` getGates source_fvs new_decl) - refs - - -- When we find a wired-in name we must load its - -- home module so that we find any instance decls therein - load_home name - | name `elemNameSet` source_binders = returnRn () - -- When compiling the prelude, a wired-in thing may - -- be defined in this module, in which case we don't - -- want to load its home module! - -- Using 'isLocallyDefined' doesn't work because some of - -- the free variables returned are simply 'listTyCon_Name', - -- with a system provenance. We could look them up every time - -- but that seems a waste. - | otherwise = loadHomeInterface doc name `thenRn_` - returnRn () - where - doc = ptext SLIT("need home module for wired in thing") <+> ppr name - -rnInstDecls decls fvs gates [] - = returnRn (decls, fvs, gates) -rnInstDecls decls fvs gates (d:ds) - = rnIfaceDecl d `thenRn` \ (new_decl, fvs1) -> - rnInstDecls (new_decl:decls) - (fvs1 `plusFV` fvs) - (gates `plusFV` getInstDeclGates new_decl) - ds +\begin{code} +checkOldIface :: DynFlags + -> HomeIfaceTable -> HomeSymbolTable + -> PersistentCompilerState + -> FilePath + -> Bool -- Source unchanged + -> Maybe ModIface -- Old interface from compilation manager, if any + -> IO (PersistentCompilerState, Bool, (RecompileRequired, Maybe ModIface)) + -- True <=> errors happened + +checkOldIface dflags hit hst pcs iface_path source_unchanged maybe_iface + = case maybe_iface of + Just old_iface -> -- Use the one we already have + startRn (mi_module old_iface) $ + check_versions old_iface + Nothing -- try and read it from a file + -> do read_result <- readIface do_traceRn iface_path + case read_result of + Left err -> -- Old interface file not found, or garbled; give up + return (pcs, False, (outOfDate, Nothing)) + Right parsed_iface + -> startRn (pi_mod parsed_iface) $ + loadOldIface parsed_iface `thenRn` \ m_iface -> + check_versions m_iface + where + check_versions :: ModIface -> RnMG (RecompileRequired, Maybe ModIface) + check_versions iface + = -- Check versions + recompileRequired iface_path source_unchanged iface + `thenRn` \ recompile -> + returnRn (recompile, Just iface) + + do_traceRn = dopt Opt_D_dump_rn_trace dflags + ioTraceRn sdoc = if do_traceRn then printErrs sdoc else return () + startRn mod = initRn dflags hit hst pcs mod \end{code} +I think the following function should now have a more representative name, +but what? \begin{code} -------------------------------------------------------- --- closeDecls keeps going until the free-var set is empty -closeDecls decls needed - | not (isEmptyFVs needed) - = slurpDecls decls needed `thenRn` \ (decls1, needed1) -> - closeDecls decls1 needed1 +loadOldIface :: ParsedIface -> RnMG ModIface - | otherwise - = getImportedRules `thenRn` \ rule_decls -> - case rule_decls of - [] -> returnRn decls -- No new rules, so we are done - other -> rnIfaceDecls decls emptyFVs rule_decls `thenRn` \ (decls1, needed1) -> - closeDecls decls1 needed1 - - -------------------------------------------------------- -rnIfaceDecls :: [RenamedHsDecl] -> FreeVars - -> [(Module, RdrNameHsDecl)] - -> RnM d ([RenamedHsDecl], FreeVars) -rnIfaceDecls decls fvs [] = returnRn (decls, fvs) -rnIfaceDecls decls fvs (d:ds) = rnIfaceDecl d `thenRn` \ (new_decl, fvs1) -> - rnIfaceDecls (new_decl:decls) (fvs1 `plusFV` fvs) ds - -rnIfaceDecl (mod, decl) = initIfaceRnMS mod (rnDecl decl) - - -------------------------------------------------------- --- Augment decls with any decls needed by needed. --- Return also free vars of the new decls (only) -slurpDecls decls needed - = go decls emptyFVs (nameSetToList needed) +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 + in + initIfaceRnMS mod ( + loadHomeDecls (pi_decls iface) `thenRn` \ decls -> + loadHomeRules (pi_rules iface) `thenRn` \ rules -> + loadHomeInsts (pi_insts iface) `thenRn` \ insts -> + returnRn (decls, rules, insts) + ) + `thenRn` \ ((decls_vers, new_decls), (rule_vers, new_rules), new_insts) -> + + mapRn loadHomeUsage (pi_usages iface) `thenRn` \ usages -> + loadExports (pi_exports iface) `thenRn` \ (export_vers, avails) -> + loadFixDecls mod (pi_fixity iface) `thenRn` \ fix_env -> + loadDeprecs mod (pi_deprecs iface) `thenRn` \ deprec_env -> + let + version = VersionInfo { vers_module = pi_vers iface, + vers_exports = export_vers, + vers_rules = rule_vers, + vers_decls = decls_vers } + + decls = IfaceDecls { dcl_tycl = new_decls, + dcl_rules = new_rules, + dcl_insts = new_insts } + + mod_iface = ModIface { mi_module = mod, mi_version = version, + mi_exports = avails, mi_usages = usages, + 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" + } + in + returnRn mod_iface +\end{code} + +\begin{code} +loadHomeDecls :: [(Version, RdrNameTyClDecl)] + -> RnMS (NameEnv Version, [RenamedTyClDecl]) +loadHomeDecls decls = foldlRn loadHomeDecl (emptyNameEnv, []) decls + +loadHomeDecl :: (NameEnv Version, [RenamedTyClDecl]) + -> (Version, RdrNameTyClDecl) + -> RnMS (NameEnv Version, [RenamedTyClDecl]) +loadHomeDecl (version_map, decls) (version, decl) + = rnTyClDecl decl `thenRn` \ decl' -> + returnRn (extendNameEnv version_map (tyClDeclName decl') version, decl':decls) + +------------------ +loadHomeRules :: (Version, [RdrNameRuleDecl]) + -> RnMS (Version, [RenamedRuleDecl]) +loadHomeRules (version, rules) + = mapRn rnIfaceRuleDecl rules `thenRn` \ rules' -> + returnRn (version, rules') + +------------------ +loadHomeInsts :: [RdrNameInstDecl] + -> RnMS [RenamedInstDecl] +loadHomeInsts insts = mapRn rnInstDecl insts + +------------------ +loadHomeUsage :: ImportVersion OccName + -> RnMG (ImportVersion Name) +loadHomeUsage (mod_name, orphans, is_boot, whats_imported) + = rn_imps whats_imported `thenRn` \ whats_imported' -> + returnRn (mod_name, orphans, is_boot, whats_imported') where - go decls fvs [] = returnRn (decls, fvs) - go decls fvs (ref:refs) = slurpDecl decls fvs ref `thenRn` \ (decls1, fvs1) -> - go decls1 fvs1 refs - -------------------------------------------------------- -slurpDecl decls fvs wanted_name - = importDecl wanted_name `thenRn` \ maybe_decl -> - case maybe_decl of - -- No declaration... (wired in thing) - Nothing -> returnRn (decls, fvs) - - -- Found a declaration... rename it - Just decl -> rnIfaceDecl decl `thenRn` \ (new_decl, fvs1) -> - returnRn (new_decl:decls, fvs1 `plusFV` fvs) + rn_imps NothingAtAll = returnRn NothingAtAll + rn_imps (Everything v) = returnRn (Everything v) + rn_imps (Specifically mv ev items rv) = mapRn rn_imp items `thenRn` \ items' -> + returnRn (Specifically mv ev items' rv) + rn_imp (occ,vers) = newGlobalName mod_name occ `thenRn` \ name -> + returnRn (name,vers) \end{code} + %********************************************************* %* * -\subsection{Extracting the `gates'} +\subsection{Closing up the interface decls} %* * %********************************************************* -When we import a declaration like -\begin{verbatim} - data T = T1 Wibble | T2 Wobble -\end{verbatim} -we don't want to treat @Wibble@ and @Wobble@ as gates -{\em unless} @T1@, @T2@ respectively are mentioned by the user program. -If only @T@ is mentioned -we want only @T@ to be a gate; -that way we don't suck in useless instance -decls for (say) @Eq Wibble@, when they can't possibly be useful. - -@getGates@ takes a newly imported (and renamed) decl, and the free -vars of the source program, and extracts from the decl the gate names. +Suppose we discover we don't need to recompile. Then we start from the +IfaceDecls in the ModIface, and fluff them up by sucking in all the decls they need. \begin{code} -getGates source_fvs (SigD (IfaceSig _ ty _ _)) - = extractHsTyNames ty - -getGates source_fvs (TyClD (ClassDecl ctxt cls tvs _ sigs _ _ _ _ _ _)) - = (delListFromNameSet (foldr (plusFV . get) (extractHsCtxtTyNames ctxt) sigs) - (map getTyVarName tvs) - `addOneToNameSet` cls) - `plusFV` maybe_double - where - get (ClassOpSig n _ _ ty _) - | n `elemNameSet` source_fvs = extractHsTyNames ty - | otherwise = emptyFVs - - -- If we load any numeric class that doesn't have - -- Int as an instance, add Double to the gates. - -- This takes account of the fact that Double might be needed for - -- defaulting, but we don't want to load Double (and all its baggage) - -- if the more exotic classes aren't used at all. - maybe_double | nameUnique cls `elem` fractionalClassKeys - = unitFV (getName doubleTyCon) - | otherwise - = emptyFVs - -getGates source_fvs (TyClD (TySynonym tycon tvs ty _)) - = delListFromNameSet (extractHsTyNames ty) - (map getTyVarName tvs) - -- A type synonym type constructor isn't a "gate" for instance decls - -getGates source_fvs (TyClD (TyData _ ctxt tycon tvs cons _ _ _)) - = delListFromNameSet (foldr (plusFV . get) (extractHsCtxtTyNames ctxt) cons) - (map getTyVarName tvs) - `addOneToNameSet` tycon - where - get (ConDecl n tvs ctxt details _) - | n `elemNameSet` source_fvs - -- If the constructor is method, get fvs from all its fields - = delListFromNameSet (get_details details `plusFV` - extractHsCtxtTyNames ctxt) - (map getTyVarName tvs) - get (ConDecl n tvs ctxt (RecCon fields) _) - -- Even if the constructor isn't mentioned, the fields - -- might be, as selectors. They can't mention existentially - -- bound tyvars (typechecker checks for that) so no need for - -- the deleteListFromNameSet part - = foldr (plusFV . get_field) emptyFVs fields - - get other_con = emptyFVs - - get_details (VanillaCon tys) = plusFVs (map get_bang tys) - get_details (InfixCon t1 t2) = get_bang t1 `plusFV` get_bang t2 - get_details (RecCon fields) = plusFVs [get_bang t | (_, t) <- fields] - get_details (NewCon t _) = extractHsTyNames t - - get_field (fs,t) | any (`elemNameSet` source_fvs) fs = get_bang t - | otherwise = emptyFVs +closeIfaceDecls :: DynFlags + -> HomeIfaceTable -> HomeSymbolTable + -> PersistentCompilerState + -> ModIface -- Get the decls from here + -> IO (PersistentCompilerState, Bool, [RenamedHsDecl]) + -- True <=> errors happened +closeIfaceDecls dflags hit hst pcs + mod_iface@(ModIface { mi_module = mod, mi_decls = iface_decls }) + = initRn dflags hit hst pcs mod $ - get_bang (Banged t) = extractHsTyNames t - get_bang (Unbanged t) = extractHsTyNames t - get_bang (Unpacked t) = extractHsTyNames t - -getGates source_fvs other_decl = emptyFVs -\end{code} - -@getWiredInGates@ is just like @getGates@, but it sees a wired-in @Name@ -rather than a declaration. - -\begin{code} -getWiredInGates :: Name -> FreeVars -getWiredInGates name -- No classes are wired in - | is_id = getWiredInGates_s (namesOfType (idType the_id)) - | isSynTyCon the_tycon = getWiredInGates_s - (delListFromNameSet (namesOfType ty) (map getName tyvars)) - | otherwise = unitFV name - where - maybe_wired_in_id = maybeWiredInIdName name - is_id = maybeToBool maybe_wired_in_id - maybe_wired_in_tycon = maybeWiredInTyConName name - Just the_id = maybe_wired_in_id - Just the_tycon = maybe_wired_in_tycon - (tyvars,ty) = getSynTyConDefn the_tycon - -getWiredInGates_s names = foldr (plusFV . getWiredInGates) emptyFVs (nameSetToList names) -\end{code} - -\begin{code} -getInstDeclGates (InstD (InstDecl inst_ty _ _ _ _)) = extractHsTyNames inst_ty -getInstDeclGates other = emptyFVs + let + rule_decls = dcl_rules iface_decls + inst_decls = dcl_insts iface_decls + tycl_decls = dcl_tycl iface_decls + decls = map RuleD rule_decls ++ + map InstD inst_decls ++ + map TyClD tycl_decls + needed = unionManyNameSets (map ruleDeclFVs rule_decls) `unionNameSets` + unionManyNameSets (map instDeclFVs inst_decls) `unionNameSets` + unionManyNameSets (map tyClDeclFVs tycl_decls) + in + closeDecls decls needed \end{code} - %********************************************************* %* * \subsection{Unused names} @@ -518,61 +530,196 @@ getInstDeclGates other = emptyFVs %********************************************************* \begin{code} -reportUnusedNames :: GlobalRdrEnv -> NameEnv AvailInfo -> ExportEnv -> NameSet -> RnM d () -reportUnusedNames gbl_env avail_env (ExportEnv export_avails _ _) mentioned_names - = let - used_names = mentioned_names `unionNameSets` availsToNameSet export_avails - - -- 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` - mkNameSet [ availName avail - | sub_name <- nameSetToList used_names, - let avail = case lookupNameEnv avail_env sub_name of - Just avail -> avail - Nothing -> WARN( True, text "reportUnusedName: not in avail_env" <+> ppr sub_name ) - Avail sub_name - ] - - defined_names = mkNameSet (concat (rdrEnvElts gbl_env)) - defined_but_not_used = - nameSetToList (defined_names `minusNameSet` really_used_names) - - -- Filter out the ones only defined implicitly - bad_locals = [n | n <- defined_but_not_used, isLocallyDefined n] - bad_imps = [n | n <- defined_but_not_used, isUserImportedExplicitlyName n] - - deprec_used deprec_env = [ (n,txt) - | n <- nameSetToList mentioned_names, - not (isLocallyDefined n), - Just txt <- [lookupNameEnv deprec_env n] ] - in +reportUnusedNames :: ModIface -> [RdrNameImportDecl] + -> AvailEnv + -> NameSet + -> [RenamedHsDecl] + -> RnMG () +reportUnusedNames my_mod_iface imports avail_env + used_names imported_decls + = warnUnusedModules unused_imp_mods `thenRn_` warnUnusedLocalBinds bad_locals `thenRn_` - warnUnusedImports bad_imps `thenRn_` - getIfacesRn `thenRn` \ ifaces -> - (if opt_WarnDeprecations - then mapRn_ warnDeprec (deprec_used (iDeprecs ifaces)) - else returnRn ()) + warnUnusedImports bad_imp_names `thenRn_` + printMinimalImports this_mod minimal_imports `thenRn_` + warnDeprecations this_mod my_deprecs really_used_names `thenRn_` + returnRn () -warnDeprec :: (Name, DeprecTxt) -> RnM d () -warnDeprec (name, txt) - = pushSrcLocRn (getSrcLoc name) $ - addWarnRn $ - sep [ text "Using deprecated entity" <+> ppr name <> colon, nest 4 (ppr txt) ] + where + this_mod = mi_module my_mod_iface + gbl_env = mi_globals my_mod_iface + my_deprecs = mi_deprecs my_mod_iface + + -- 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` + mkNameSet [ parent_name + | sub_name <- nameSetToList used_names + + -- Usually, every used name will appear in avail_env, but there + -- is one time when it doesn't: tuples and other built in syntax. When you + -- write (a,b) that gives rise to a *use* of "(,)", so that the + -- instances will get pulled in, but the tycon "(,)" isn't actually + -- in scope. Also, (-x) gives rise to an implicit use of 'negate'; + -- similarly, 3.5 gives rise to an implcit use of :% + -- Hence the silent 'False' in all other cases + + , Just parent_name <- [case lookupNameEnv avail_env sub_name of + Just (AvailTC n _) -> Just n + other -> Nothing] + ] + + defined_names, defined_and_used, defined_but_not_used :: [(Name,Provenance)] + defined_names = concat (rdrEnvElts gbl_env) + (defined_and_used, defined_but_not_used) = partition used defined_names + used (name,_) = not (name `elemNameSet` really_used_names) + + -- Filter out the ones only defined implicitly + bad_locals :: [Name] + bad_locals = [n | (n,LocalDef) <- defined_but_not_used] + + bad_imp_names :: [(Name,Provenance)] + bad_imp_names = [(n,p) | (n,p@(NonLocalDef (UserImport mod _ True) _)) <- defined_but_not_used, + not (module_unused mod)] + + -- inst_mods are directly-imported modules that + -- contain instance decl(s) that the renamer decided to suck in + -- It's not necessarily redundant to import such modules. + -- + -- NOTE: Consider + -- module This + -- import M () + -- + -- The import M() is not *necessarily* redundant, even if + -- we suck in no instance decls from M (e.g. it contains + -- no instance decls, or This contains no code). It may be + -- that we import M solely to ensure that M's orphan instance + -- decls (or those in its imports) are visible to people who + -- import This. Sigh. + -- There's really no good way to detect this, so the error message + -- in RnEnv.warnUnusedModules is weakened instead + inst_mods :: [ModuleName] + inst_mods = [m | InstD (InstDecl _ _ _ (Just dfun) _) <- imported_decls, + let m = moduleName (nameModule dfun), + m `elem` direct_import_mods + ] + + -- To figure out the minimal set of imports, start with the things + -- that are in scope (i.e. in gbl_env). Then just combine them + -- into a bunch of avails, so they are properly grouped + minimal_imports :: FiniteMap ModuleName AvailEnv + minimal_imports0 = emptyFM + minimal_imports1 = foldr add_name minimal_imports0 defined_and_used + minimal_imports = foldr add_inst_mod minimal_imports1 inst_mods + + add_name (n,NonLocalDef (UserImport m _ _) _) acc = addToFM_C plusAvailEnv acc (moduleName (nameModule n)) + (unitAvailEnv (mk_avail n)) + add_name (n,other_prov) acc = acc + + mk_avail n = case lookupNameEnv avail_env n of + Just (AvailTC m _) | n==m -> AvailTC n [n] + | otherwise -> AvailTC m [n,m] + Just avail -> Avail n + Nothing -> pprPanic "mk_avail" (ppr n) + + add_inst_mod m acc + | m `elemFM` acc = acc -- We import something already + | otherwise = addToFM acc m emptyAvailEnv + -- Add an empty collection of imports for a module + -- from which we have sucked only instance decls + + direct_import_mods :: [ModuleName] + direct_import_mods = nub [m | ImportDecl m _ _ _ _ _ <- imports] + + -- unused_imp_mods are the directly-imported modules + -- that are not mentioned in minimal_imports + unused_imp_mods = [m | m <- direct_import_mods, + not (maybeToBool (lookupFM minimal_imports m)), + m /= pRELUDE_Name] + + module_unused :: Module -> Bool + module_unused mod = moduleName mod `elem` unused_imp_mods + + +warnDeprecations this_mod my_deprecs used_names + = doptRn Opt_WarnDeprecations `thenRn` \ warn_drs -> + if not warn_drs then returnRn () else + + getIfacesRn `thenRn` \ ifaces -> + getHomeIfaceTableRn `thenRn` \ hit -> + let + pit = iPIT ifaces + deprecs = [ (n,txt) + | n <- nameSetToList used_names, + Just txt <- [lookup_deprec hit pit n] ] + in + mapRn_ warnDeprec deprecs + + where + lookup_deprec hit pit n + | nameIsLocalOrFrom this_mod n + = lookupDeprec my_deprecs n + | otherwise + = case lookupIface hit pit this_mod n of + Just iface -> lookupDeprec (mi_deprecs iface) n + Nothing -> pprPanic "warnDeprecations:" (ppr n) + +-- ToDo: deal with original imports with 'qualified' and 'as M' clauses +printMinimalImports this_mod imps + = doptRn Opt_D_dump_minimal_imports `thenRn` \ dump_minimal -> + if not dump_minimal then returnRn () else + + mapRn to_ies (fmToList imps) `thenRn` \ mod_ies -> + ioToRnM (do { h <- openFile filename WriteMode ; + printForUser h (vcat (map ppr_mod_ie mod_ies)) + }) `thenRn_` + returnRn () + where + filename = moduleNameUserString (moduleName this_mod) ++ ".imports" + ppr_mod_ie (mod_name, ies) + | mod_name == pRELUDE_Name + = empty + | otherwise + = ptext SLIT("import") <+> ppr mod_name <> + parens (fsep (punctuate comma (map ppr ies))) + + to_ies (mod, avail_env) = mapRn to_ie (availEnvElts avail_env) `thenRn` \ ies -> + returnRn (mod, ies) + + to_ie :: AvailInfo -> RnMG (IE Name) + to_ie (Avail n) = returnRn (IEVar n) + to_ie (AvailTC n [m]) = ASSERT( n==m ) + returnRn (IEThingAbs n) + to_ie (AvailTC n ns) + = getInterfaceExports n_mod ImportBySystem `thenRn` \ (_, avails_by_module) -> + case [xs | (m,as) <- avails_by_module, + m == n_mod, + AvailTC x xs <- as, + x == n] of + [xs] | all (`elem` ns) xs -> returnRn (IEThingAll n) + | otherwise -> returnRn (IEThingWith n (filter (/= n) ns)) + other -> pprTrace "to_ie" (ppr n <+> ppr (nameModule n) <+> ppr other) $ + returnRn (IEVar n) + where + n_mod = moduleName (nameModule n) rnDump :: [RenamedHsDecl] -- Renamed imported decls -> [RenamedHsDecl] -- Renamed local decls - -> RnMG (IO ()) -rnDump imp_decls decls - | opt_D_dump_rn_trace || - opt_D_dump_rn_stats || - opt_D_dump_rn - = getRnStats imp_decls `thenRn` \ stats_msg -> - - returnRn (printErrs stats_msg >> - dumpIfSet opt_D_dump_rn "Renamer:" (vcat (map ppr decls))) - - | otherwise = returnRn (return ()) + -> RnMG () +rnDump imp_decls local_decls + = doptRn Opt_D_dump_rn_trace `thenRn` \ dump_rn_trace -> + doptRn Opt_D_dump_rn_stats `thenRn` \ dump_rn_stats -> + doptRn Opt_D_dump_rn `thenRn` \ dump_rn -> + getIfacesRn `thenRn` \ ifaces -> + + ioToRnM (do { dumpIfSet (dump_rn_trace || dump_rn_stats || dump_rn) + "Renamer statistics" + (getRnStats imp_decls ifaces) ; + + dumpIfSet dump_rn "Renamer:" + (vcat (map ppr (local_decls ++ imp_decls))) + }) `thenRn_` + + returnRn () \end{code} @@ -583,47 +730,45 @@ rnDump imp_decls decls %********************************************************* \begin{code} -getRnStats :: [RenamedHsDecl] -> RnMG SDoc -getRnStats imported_decls - = getIfacesRn `thenRn` \ ifaces -> - let - n_mods = length [() | (_, _, Just _) <- eltsFM (iImpModInfo ifaces)] - - decls_read = [decl | (_, avail, True, (_,decl)) <- nameEnvElts (iDecls ifaces), - -- Data, newtype, and class decls are in the decls_fm - -- under multiple names; the tycon/class, and each - -- constructor/class op too. - -- The 'True' selects just the 'main' decl - not (isLocallyDefined (availName avail)) - ] - - (cd_rd, dd_rd, nd_rd, sd_rd, vd_rd, _) = count_decls decls_read - (cd_sp, dd_sp, nd_sp, sd_sp, vd_sp, id_sp) = count_decls imported_decls - - unslurped_insts = iInsts ifaces - inst_decls_unslurped = length (bagToList unslurped_insts) - inst_decls_read = id_sp + inst_decls_unslurped - - stats = vcat - [int n_mods <+> text "interfaces read", - hsep [ int cd_sp, text "class decls imported, out of", - int cd_rd, text "read"], - hsep [ int dd_sp, text "data decls imported, out of", - int dd_rd, text "read"], - hsep [ int nd_sp, text "newtype decls imported, out of", - int nd_rd, text "read"], - hsep [int sd_sp, text "type synonym decls imported, out of", - int sd_rd, text "read"], - hsep [int vd_sp, text "value signatures imported, out of", - int vd_rd, text "read"], - hsep [int id_sp, text "instance decls imported, out of", - int inst_decls_read, text "read"], - text "cls dcls slurp" <+> fsep (map (ppr . tyClDeclName) - [d | TyClD d <- imported_decls, isClassDecl d]), - text "cls dcls read" <+> fsep (map (ppr . tyClDeclName) - [d | TyClD d <- decls_read, isClassDecl d])] - in - returnRn (hcat [text "Renamer stats: ", stats]) +getRnStats :: [RenamedHsDecl] -> Ifaces -> SDoc +getRnStats imported_decls ifaces + = hcat [text "Renamer stats: ", stats] + where + n_mods = length [() | _ <- moduleEnvElts (iPIT ifaces)] + -- This is really only right for a one-shot compile + + decls_read = [decl | (avail, True, (_,decl)) <- nameEnvElts (iDecls ifaces) + -- Data, newtype, and class decls are in the decls_fm + -- under multiple names; the tycon/class, and each + -- constructor/class op too. + -- The 'True' selects just the 'main' decl + ] + + (cd_rd, dd_rd, nd_rd, sd_rd, vd_rd) = countTyClDecls decls_read + (cd_sp, dd_sp, nd_sp, sd_sp, vd_sp, id_sp) = count_decls imported_decls + + unslurped_insts = iInsts ifaces + inst_decls_unslurped = length (bagToList unslurped_insts) + inst_decls_read = id_sp + inst_decls_unslurped + + stats = vcat + [int n_mods <+> text "interfaces read", + hsep [ int cd_sp, text "class decls imported, out of", + int cd_rd, text "read"], + hsep [ int dd_sp, text "data decls imported, out of", + int dd_rd, text "read"], + hsep [ int nd_sp, text "newtype decls imported, out of", + int nd_rd, text "read"], + hsep [int sd_sp, text "type synonym decls imported, out of", + int sd_rd, text "read"], + hsep [int vd_sp, text "value signatures imported, out of", + int vd_rd, text "read"], + hsep [int id_sp, text "instance decls imported, out of", + int inst_decls_read, text "read"], + text "cls dcls slurp" <+> fsep (map (ppr . tyClDeclName) + [d | TyClD d <- imported_decls, isClassDecl d]), + text "cls dcls read" <+> fsep (map (ppr . tyClDeclName) + [d | d <- decls_read, isClassDecl d])] count_decls decls = (class_decls, @@ -634,9 +779,42 @@ count_decls decls inst_decls) where tycl_decls = [d | TyClD d <- decls] - (class_decls, data_decls, newtype_decls, syn_decls) = countTyClDecls tycl_decls + (class_decls, data_decls, newtype_decls, syn_decls, val_decls) = countTyClDecls tycl_decls - val_decls = length [() | SigD _ <- decls] inst_decls = length [() | InstD _ <- decls] \end{code} + +%************************************************************************ +%* * +\subsection{Errors and warnings} +%* * +%************************************************************************ + +\begin{code} +warnDeprec :: (Name, DeprecTxt) -> RnM d () +warnDeprec (name, txt) + = pushSrcLocRn (getSrcLoc name) $ + addWarnRn $ + sep [ text (occNameFlavour (nameOccName name)) <+> ppr name <+> + text "is deprecated:", nest 4 (ppr txt) ] + + +unusedFixityDecl rdr_name fixity + = hsep [ptext SLIT("Unused fixity declaration for"), quotes (ppr rdr_name)] + +dupFixityDecl rdr_name loc1 loc2 + = vcat [ptext SLIT("Multiple fixity declarations for") <+> quotes (ppr rdr_name), + ptext SLIT("at ") <+> ppr loc1, + ptext SLIT("and") <+> ppr loc2] + +badDeprec d + = sep [ptext SLIT("Illegal deprecation when whole module is deprecated"), + nest 4 (ppr d)] + +noMainErr + = hsep [ptext SLIT("Module"), quotes (ppr mAIN_Name), + ptext SLIT("must include a definition for"), quotes (ptext SLIT("main"))] +\end{code} + +