diff options
author | Sylvain Henry <sylvain@haskus.fr> | 2020-05-15 11:19:40 +0200 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2020-06-13 02:13:03 -0400 |
commit | 653d17bdd57ec8ca9b11b19e45860982bd1e7c9e (patch) | |
tree | a97c6257385e77280c6818612d041b3395684403 /compiler | |
parent | 55b4263e1a53cc27b1da9227249bdcd20139ddc9 (diff) | |
download | haskell-653d17bdd57ec8ca9b11b19e45860982bd1e7c9e.tar.gz |
Rename Package into Unit (2)
* rename PackageState into UnitState
* rename findWiredInPackages into findWiredInUnits
* rename lookupModuleInAll[Packages,Units]
* etc.
Diffstat (limited to 'compiler')
-rw-r--r-- | compiler/GHC/Builtin/Names.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Driver/Backpack.hs | 6 | ||||
-rw-r--r-- | compiler/GHC/Driver/Finder.hs | 6 | ||||
-rw-r--r-- | compiler/GHC/Driver/Make.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Driver/Session.hs | 8 | ||||
-rw-r--r-- | compiler/GHC/Driver/Session.hs-boot | 2 | ||||
-rw-r--r-- | compiler/GHC/Driver/Types.hs | 6 | ||||
-rw-r--r-- | compiler/GHC/Runtime/Loader.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Utils/Backpack.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Unit/Module/Location.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Unit/State.hs | 150 | ||||
-rw-r--r-- | compiler/GHC/Unit/State.hs-boot | 10 | ||||
-rw-r--r-- | compiler/GHC/Unit/Types.hs | 2 |
13 files changed, 101 insertions, 101 deletions
diff --git a/compiler/GHC/Builtin/Names.hs b/compiler/GHC/Builtin/Names.hs index a3d1fa5d5b..5b787ea0c7 100644 --- a/compiler/GHC/Builtin/Names.hs +++ b/compiler/GHC/Builtin/Names.hs @@ -144,7 +144,7 @@ When GHC reads the package data base, it (internally only) pretends it has UnitI `integer-wired-in` instead of the actual UnitId (which includes the version number); just like for `base` and other packages, as described in Note [Wired-in units] in GHC.Unit.Module. This is done in -GHC.Unit.State.findWiredInPackages. +GHC.Unit.State.findWiredInUnits. -} {-# LANGUAGE CPP #-} diff --git a/compiler/GHC/Driver/Backpack.hs b/compiler/GHC/Driver/Backpack.hs index 4cd7a993be..658750b1c9 100644 --- a/compiler/GHC/Driver/Backpack.hs +++ b/compiler/GHC/Driver/Backpack.hs @@ -561,14 +561,14 @@ type PackageNameMap a = Map PackageName a -- For now, something really simple, since we're not actually going -- to use this for anything -unitDefines :: PackageState -> LHsUnit PackageName -> (PackageName, HsComponentId) +unitDefines :: UnitState -> LHsUnit PackageName -> (PackageName, HsComponentId) unitDefines pkgstate (L _ HsUnit{ hsunitName = L _ pn@(PackageName fs) }) = (pn, HsComponentId pn (mkIndefUnitId pkgstate fs)) -bkpPackageNameMap :: PackageState -> [LHsUnit PackageName] -> PackageNameMap HsComponentId +bkpPackageNameMap :: UnitState -> [LHsUnit PackageName] -> PackageNameMap HsComponentId bkpPackageNameMap pkgstate units = Map.fromList (map (unitDefines pkgstate) units) -renameHsUnits :: PackageState -> PackageNameMap HsComponentId -> [LHsUnit PackageName] -> [LHsUnit HsComponentId] +renameHsUnits :: UnitState -> PackageNameMap HsComponentId -> [LHsUnit PackageName] -> [LHsUnit HsComponentId] renameHsUnits pkgstate m units = map (fmap renameHsUnit) units where diff --git a/compiler/GHC/Driver/Finder.hs b/compiler/GHC/Driver/Finder.hs index 48fe9edba3..f6f0814739 100644 --- a/compiler/GHC/Driver/Finder.hs +++ b/compiler/GHC/Driver/Finder.hs @@ -63,7 +63,7 @@ type BaseName = String -- Basename of file -- source, interface, and object files for that module live. -- It does *not* know which particular package a module lives in. Use --- Packages.lookupModuleInAllPackages for that. +-- Packages.lookupModuleInAllUnits for that. -- ----------------------------------------------------------------------------- -- The finder's cache @@ -758,7 +758,7 @@ cantFindErr cannot_find _ dflags mod_name find_result pp_sugg (SuggestVisible m mod o) = ppr m <+> provenance o where provenance ModHidden = Outputable.empty provenance (ModUnusable _) = Outputable.empty - provenance (ModOrigin{ fromOrigPackage = e, + provenance (ModOrigin{ fromOrigUnit = e, fromExposedReexport = res, fromPackageFlag = f }) | Just True <- e @@ -775,7 +775,7 @@ cantFindErr cannot_find _ dflags mod_name find_result pp_sugg (SuggestHidden m mod o) = ppr m <+> provenance o where provenance ModHidden = Outputable.empty provenance (ModUnusable _) = Outputable.empty - provenance (ModOrigin{ fromOrigPackage = e, + provenance (ModOrigin{ fromOrigUnit = e, fromHiddenReexport = rhs }) | Just False <- e = parens (text "needs flag -package-id" diff --git a/compiler/GHC/Driver/Make.hs b/compiler/GHC/Driver/Make.hs index d825435ecc..a9b93dbe44 100644 --- a/compiler/GHC/Driver/Make.hs +++ b/compiler/GHC/Driver/Make.hs @@ -1527,7 +1527,7 @@ upsweep mHscMessage old_hpt stable_mods cleanup sccs = do upsweep' old_hpt1 done' mods (mod_index+1) nmods uids_to_check' done_holes' --- | Return a list of instantiated units to type check from the PackageState. +-- | Return a list of instantiated units to type check from the UnitState. -- -- Use explicit (instantiated) units as roots and also return their -- instantiations that are themselves instantiations and so on recursively. diff --git a/compiler/GHC/Driver/Session.hs b/compiler/GHC/Driver/Session.hs index f301024c9a..d363eb2410 100644 --- a/compiler/GHC/Driver/Session.hs +++ b/compiler/GHC/Driver/Session.hs @@ -254,7 +254,7 @@ import GHC.Unit.Module import {-# SOURCE #-} GHC.Driver.Plugins import {-# SOURCE #-} GHC.Driver.Hooks import GHC.Builtin.Names ( mAIN ) -import {-# SOURCE #-} GHC.Unit.State (PackageState, emptyPackageState, UnitDatabase, updateIndefUnitId) +import {-# SOURCE #-} GHC.Unit.State (UnitState, emptyUnitState, UnitDatabase, updateIndefUnitId) import GHC.Driver.Phases ( Phase(..), phaseInputExt ) import GHC.Driver.Flags import GHC.Driver.Ways @@ -617,7 +617,7 @@ data DynFlags = DynFlags { -- *reverse* order that they're specified on the command line. -- This is intended to be applied with the list of "initial" -- package databases derived from @GHC_PACKAGE_PATH@; see - -- 'getPackageDbRefs'. + -- 'getUnitDbRefs'. ignorePackageFlags :: [IgnorePackageFlag], -- ^ The @-ignore-package@ flags from the command line. @@ -643,7 +643,7 @@ data DynFlags = DynFlags { -- `initUnits` is called again, it doesn't reload the databases from -- disk. - unitState :: PackageState, + unitState :: UnitState, -- ^ Consolidated unit database built by 'initUnits' from the unit -- databases in 'unitDatabases' and flags ('-ignore-package', etc.). -- @@ -1377,7 +1377,7 @@ defaultDynFlags mySettings llvmConfig = trustFlags = [], packageEnv = Nothing, unitDatabases = Nothing, - unitState = emptyPackageState, + unitState = emptyUnitState, ways = defaultWays mySettings, buildTag = waysTag (defaultWays mySettings), splitInfo = Nothing, diff --git a/compiler/GHC/Driver/Session.hs-boot b/compiler/GHC/Driver/Session.hs-boot index 0de689d2da..3dcc6b3a6e 100644 --- a/compiler/GHC/Driver/Session.hs-boot +++ b/compiler/GHC/Driver/Session.hs-boot @@ -9,7 +9,7 @@ data DynFlags targetPlatform :: DynFlags -> Platform pprUserLength :: DynFlags -> Int -unitState :: DynFlags -> PackageState +unitState :: DynFlags -> UnitState unsafeGlobalDynFlags :: DynFlags hasPprDebug :: DynFlags -> Bool hasNoDebugOutput :: DynFlags -> Bool diff --git a/compiler/GHC/Driver/Types.hs b/compiler/GHC/Driver/Types.hs index 2dabe1891f..01aaf82f20 100644 --- a/compiler/GHC/Driver/Types.hs +++ b/compiler/GHC/Driver/Types.hs @@ -2023,12 +2023,12 @@ mkQualModule dflags mod = False | otherwise = True - where lookup = lookupModuleInAllPackages (unitState dflags) (moduleName mod) + where lookup = lookupModuleInAllUnits (unitState dflags) (moduleName mod) -- | Creates a function for formatting packages based on two heuristics: -- (1) don't qualify if the package in question is "main", and (2) only qualify -- with a unit id if the package ID would be ambiguous. -mkQualPackage :: PackageState -> QueryQualifyPackage +mkQualPackage :: UnitState -> QueryQualifyPackage mkQualPackage pkgs uid | uid == mainUnit || uid == interactiveUnit -- Skip the lookup if it's main, since it won't be in the package @@ -2045,7 +2045,7 @@ mkQualPackage pkgs uid -- | A function which only qualifies package names if necessary; but -- qualifies all other identifiers. -pkgQual :: PackageState -> PrintUnqualified +pkgQual :: UnitState -> PrintUnqualified pkgQual pkgs = alwaysQualify { queryQualifyPackage = mkQualPackage pkgs } {- diff --git a/compiler/GHC/Runtime/Loader.hs b/compiler/GHC/Runtime/Loader.hs index 8eb48881c9..5d286587ef 100644 --- a/compiler/GHC/Runtime/Loader.hs +++ b/compiler/GHC/Runtime/Loader.hs @@ -244,7 +244,7 @@ lessUnsafeCoerce dflags context what = do lookupRdrNameInModuleForPlugins :: HscEnv -> ModuleName -> RdrName -> IO (Maybe (Name, ModIface)) lookupRdrNameInModuleForPlugins hsc_env mod_name rdr_name = do - -- First find the package the module resides in by searching exposed packages and home modules + -- First find the unit the module resides in by searching exposed units and home modules found_module <- findPluginModule hsc_env mod_name case found_module of Found _ mod -> do diff --git a/compiler/GHC/Tc/Utils/Backpack.hs b/compiler/GHC/Tc/Utils/Backpack.hs index 87890fa94d..1f6090c7b7 100644 --- a/compiler/GHC/Tc/Utils/Backpack.hs +++ b/compiler/GHC/Tc/Utils/Backpack.hs @@ -231,7 +231,7 @@ check_inst sig_inst = do -- | Return this list of requirement interfaces that need to be merged -- to form @mod_name@, or @[]@ if this is not a requirement. -requirementMerges :: PackageState -> ModuleName -> [InstantiatedModule] +requirementMerges :: UnitState -> ModuleName -> [InstantiatedModule] requirementMerges pkgstate mod_name = fmap fixupModule $ fromMaybe [] (Map.lookup mod_name (requirementContext pkgstate)) where diff --git a/compiler/GHC/Unit/Module/Location.hs b/compiler/GHC/Unit/Module/Location.hs index 7518bd63e8..6f239227f0 100644 --- a/compiler/GHC/Unit/Module/Location.hs +++ b/compiler/GHC/Unit/Module/Location.hs @@ -17,7 +17,7 @@ import GHC.Utils.Outputable -- Where a module lives on the file system: the actual locations -- of the .hs, .hi and .o files, if we have them. -- --- For a module in another package, the ml_hs_file and ml_obj_file components of +-- For a module in another unit, the ml_hs_file and ml_obj_file components of -- ModLocation are undefined. -- -- The locations specified by a ModLocation may or may not @@ -40,7 +40,7 @@ data ModLocation -- ^ Where the .o file is, whether or not it exists yet. -- (might not exist either because the module hasn't -- been compiled yet, or because it is part of a - -- package with a .a file) + -- unit with a .a file) ml_hie_file :: FilePath -- ^ Where the .hie file is, whether or not it exists diff --git a/compiler/GHC/Unit/State.hs b/compiler/GHC/Unit/State.hs index d6ac230d56..6862d32157 100644 --- a/compiler/GHC/Unit/State.hs +++ b/compiler/GHC/Unit/State.hs @@ -2,18 +2,18 @@ {-# LANGUAGE CPP, ScopedTypeVariables, BangPatterns, FlexibleContexts #-} --- | Package manipulation +-- | Unit manipulation module GHC.Unit.State ( module GHC.Unit.Info, -- * Reading the package config, and processing cmdline args - PackageState(..), + UnitState(..), UnitDatabase (..), - emptyPackageState, + emptyUnitState, initUnits, readUnitDatabases, readUnitDatabase, - getPackageDbRefs, + getUnitDbRefs, resolveUnitDatabase, listUnitInfo, @@ -30,7 +30,7 @@ module GHC.Unit.State ( searchPackageId, displayUnitId, listVisibleModuleNames, - lookupModuleInAllPackages, + lookupModuleInAllUnits, lookupModuleWithSuggestions, lookupPluginModuleWithSuggestions, LookupResult(..), @@ -66,8 +66,8 @@ module GHC.Unit.State ( updateIndefUnitId, unwireUnit, pprFlag, - pprPackages, - pprPackagesSimple, + pprUnits, + pprUnitsSimple, pprModuleMap, homeUnitIsIndefinite, homeUnitIsDefinite, @@ -114,14 +114,14 @@ import qualified Data.Map.Strict as MapStrict import qualified Data.Set as Set -- --------------------------------------------------------------------------- --- The Package state +-- The Unit state --- | Package state is all stored in 'DynFlags', including the details of --- all packages, which packages are exposed, and which modules they +-- | Unit state is all stored in 'DynFlags', including the details of +-- all units, which units are exposed, and which modules they -- provide. -- --- The package state is computed by 'initUnits', and kept in DynFlags. --- It is influenced by various package flags: +-- The unit state is computed by 'initUnits', and kept in DynFlags. +-- It is influenced by various command-line flags: -- -- * @-package <pkg>@ and @-package-id <pkg>@ cause @<pkg>@ to become exposed. -- If @-hide-all-packages@ was not specified, these commands also cause @@ -131,17 +131,17 @@ import qualified Data.Set as Set -- -- * (there are a few more flags, check below for their semantics) -- --- The package state has the following properties. +-- The unit state has the following properties. -- --- * Let @exposedPackages@ be the set of packages thus exposed. --- Let @depExposedPackages@ be the transitive closure from @exposedPackages@ of +-- * Let @exposedUnits@ be the set of packages thus exposed. +-- Let @depExposedUnits@ be the transitive closure from @exposedUnits@ of -- their dependencies. -- -- * When searching for a module from a preload import declaration, --- only the exposed modules in @exposedPackages@ are valid. +-- only the exposed modules in @exposedUnits@ are valid. -- -- * When searching for a module from an implicit import, all modules --- from @depExposedPackages@ are valid. +-- from @depExposedUnits@ are valid. -- -- * When linking in a compilation manager mode, we link in packages the -- program depends on (the compiler knows this list by the @@ -178,7 +178,7 @@ data ModuleOrigin = -- someone's @exported-modules@ list, but that package is hidden; -- @Just True@ means that it is available; @Nothing@ means neither -- applies. - fromOrigPackage :: Maybe Bool + fromOrigUnit :: Maybe Bool -- | Is the module available from a reexport of an exposed package? -- There could be multiple. , fromExposedReexport :: [UnitInfo] @@ -314,7 +314,7 @@ instance Monoid UnitVisibility where type ModuleNameProvidersMap = Map ModuleName (Map Module ModuleOrigin) -data PackageState = PackageState { +data UnitState = UnitState { -- | A mapping of 'Unit' to 'UnitInfo'. This list is adjusted -- so that only valid units are here. 'UnitInfo' reflects -- what was stored *on disk*, except for the 'trusted' flag, which @@ -370,8 +370,8 @@ data PackageState = PackageState { allowVirtualUnits :: !Bool } -emptyPackageState :: PackageState -emptyPackageState = PackageState { +emptyUnitState :: UnitState +emptyUnitState = UnitState { unitInfoMap = Map.empty, preloadClosure = emptyUniqSet, packageNameMap = Map.empty, @@ -393,10 +393,10 @@ data UnitDatabase unit = UnitDatabase type UnitInfoMap = Map UnitId UnitInfo -- | Find the unit we know about with the given unit, if any -lookupUnit :: PackageState -> Unit -> Maybe UnitInfo +lookupUnit :: UnitState -> Unit -> Maybe UnitInfo lookupUnit pkgs = lookupUnit' (allowVirtualUnits pkgs) (unitInfoMap pkgs) (preloadClosure pkgs) --- | A more specialized interface, which doesn't require a 'PackageState' (so it +-- | A more specialized interface, which doesn't require a 'UnitState' (so it -- can be used while we're initializing 'DynFlags') -- -- Parameters: @@ -422,7 +422,7 @@ lookupUnit' allowOnTheFlyInst pkg_map closure u = case u of Map.lookup (virtualUnitId i) pkg_map -- | Find the unit we know about with the given unit id, if any -lookupUnitId :: PackageState -> UnitId -> Maybe UnitInfo +lookupUnitId :: UnitState -> UnitId -> Maybe UnitInfo lookupUnitId state uid = lookupUnitId' (unitInfoMap state) uid -- | Find the unit we know about with the given unit id, if any @@ -431,13 +431,13 @@ lookupUnitId' db uid = Map.lookup uid db -- | Looks up the given unit in the package state, panicing if it is not found -unsafeLookupUnit :: HasDebugCallStack => PackageState -> Unit -> UnitInfo +unsafeLookupUnit :: HasDebugCallStack => UnitState -> Unit -> UnitInfo unsafeLookupUnit state u = case lookupUnit state u of Just info -> info Nothing -> pprPanic "unsafeLookupUnit" (ppr u) -- | Looks up the given unit id in the package state, panicing if it is not found -unsafeLookupUnitId :: HasDebugCallStack => PackageState -> UnitId -> UnitInfo +unsafeLookupUnitId :: HasDebugCallStack => UnitState -> UnitId -> UnitInfo unsafeLookupUnitId state uid = case lookupUnitId state uid of Just info -> info Nothing -> pprPanic "unsafeLookupUnitId" (ppr uid) @@ -445,11 +445,11 @@ unsafeLookupUnitId state uid = case lookupUnitId state uid of -- | Find the package we know about with the given package name (e.g. @foo@), if any -- (NB: there might be a locally defined unit name which overrides this) -lookupPackageName :: PackageState -> PackageName -> Maybe IndefUnitId +lookupPackageName :: UnitState -> PackageName -> Maybe IndefUnitId lookupPackageName pkgstate n = Map.lookup n (packageNameMap pkgstate) -- | Search for packages with a given package ID (e.g. \"foo-0.1\") -searchPackageId :: PackageState -> PackageId -> [UnitInfo] +searchPackageId :: UnitState -> PackageId -> [UnitInfo] searchPackageId pkgstate pid = filter ((pid ==) . unitPackageId) (listUnitInfo pkgstate) @@ -478,7 +478,7 @@ mkUnitInfoMap infos = foldl' add Map.empty infos -- this function, although all packages in this map are "visible", this -- does not imply that the exposed-modules of the package are available -- (they may have been thinned or renamed). -listUnitInfo :: PackageState -> [UnitInfo] +listUnitInfo :: UnitState -> [UnitInfo] listUnitInfo state = Map.elems (unitInfoMap state) -- ---------------------------------------------------------------------------- @@ -513,7 +513,7 @@ initUnits dflags = withTiming dflags | otherwise = read_pkg_dbs (pkg_state, preload, insts) - <- mkPackageState dflags pkg_dbs [] + <- mkUnitState dflags pkg_dbs [] return (dflags{ unitDatabases = Just read_pkg_dbs, unitState = pkg_state, homeUnitInstantiations = insts }, @@ -526,13 +526,13 @@ initUnits dflags = withTiming dflags readUnitDatabases :: DynFlags -> IO [UnitDatabase UnitId] readUnitDatabases dflags = do - conf_refs <- getPackageDbRefs dflags + conf_refs <- getUnitDbRefs dflags confs <- liftM catMaybes $ mapM (resolveUnitDatabase dflags) conf_refs mapM (readUnitDatabase dflags) confs -getPackageDbRefs :: DynFlags -> IO [PkgDbRef] -getPackageDbRefs dflags = do +getUnitDbRefs :: DynFlags -> IO [PkgDbRef] +getUnitDbRefs dflags = do let system_conf_refs = [UserPkgDb, GlobalPkgDb] e_pkg_path <- tryIO (getEnv $ map toUpper (programName dflags) ++ "_PACKAGE_PATH") @@ -972,7 +972,7 @@ pprTrustFlag flag = case flag of type WiringMap = Map UnitId UnitId -findWiredInPackages +findWiredInUnits :: DynFlags -> UnitPrecedenceMap -> [UnitInfo] -- database @@ -981,7 +981,7 @@ findWiredInPackages -> IO ([UnitInfo], -- package database updated for wired in WiringMap) -- map from unit id to wired identity -findWiredInPackages dflags prec_map pkgs vis_map = do +findWiredInUnits dflags prec_map pkgs vis_map = do -- Now we must find our wired-in packages, and rename them to -- their canonical names (eg. base-1.0 ==> base), as described -- in Note [Wired-in units] in GHC.Unit.Module @@ -1010,8 +1010,8 @@ findWiredInPackages dflags prec_map pkgs vis_map = do -- this works even when there is no exposed wired in package -- available. -- - findWiredInPackage :: [UnitInfo] -> UnitId -> IO (Maybe (UnitId, UnitInfo)) - findWiredInPackage pkgs wired_pkg = + findWiredInUnit :: [UnitInfo] -> UnitId -> IO (Maybe (UnitId, UnitInfo)) + findWiredInUnit pkgs wired_pkg = let all_ps = [ p | p <- pkgs, p `matches` wired_pkg ] all_exposed_ps = [ p | p <- all_ps @@ -1038,7 +1038,7 @@ findWiredInPackages dflags prec_map pkgs vis_map = do return (Just (wired_pkg, pkg)) - mb_wired_in_pkgs <- mapM (findWiredInPackage pkgs) wiredInUnitIds + mb_wired_in_pkgs <- mapM (findWiredInUnit pkgs) wiredInUnitIds let wired_in_pkgs = catMaybes mb_wired_in_pkgs @@ -1188,10 +1188,10 @@ reverseDeps db = Map.foldl' go Map.empty db -- remove those packages, plus any packages which depend on them. -- Returns the pruned database, as well as a list of 'UnitInfo's -- that was removed. -removePackages :: [UnitId] -> RevIndex +removeUnits :: [UnitId] -> RevIndex -> UnitInfoMap -> (UnitInfoMap, [UnitInfo]) -removePackages uids index m = go uids (m,[]) +removeUnits uids index m = go uids (m,[]) where go [] (m,pkgs) = (m,pkgs) go (uid:uids) (m,pkgs) @@ -1227,8 +1227,8 @@ depsAbiMismatch pkg_map pkg = map fst . filter (not . abiMatch) $ unitAbiDepends -- ----------------------------------------------------------------------------- -- Ignore packages -ignorePackages :: [IgnorePackageFlag] -> [UnitInfo] -> UnusableUnits -ignorePackages flags pkgs = Map.fromList (concatMap doit flags) +ignoreUnits :: [IgnorePackageFlag] -> [UnitInfo] -> UnusableUnits +ignoreUnits flags pkgs = Map.fromList (concatMap doit flags) where doit (IgnorePackage str) = case partition (matchingStr str) pkgs of @@ -1312,7 +1312,7 @@ validateDatabase dflags pkg_map1 = -- Find broken packages directly_broken = filter (not . null . depsNotAvailable pkg_map1) (Map.elems pkg_map1) - (pkg_map2, broken) = removePackages (map unitId directly_broken) index pkg_map1 + (pkg_map2, broken) = removeUnits (map unitId directly_broken) index pkg_map1 unusable_broken = mk_unusable BrokenDependencies depsNotAvailable pkg_map2 broken -- Find recursive packages @@ -1320,19 +1320,19 @@ validateDatabase dflags pkg_map1 = | pkg <- Map.elems pkg_map2 ] getCyclicSCC (CyclicSCC vs) = map unitId vs getCyclicSCC (AcyclicSCC _) = [] - (pkg_map3, cyclic) = removePackages (concatMap getCyclicSCC sccs) index pkg_map2 + (pkg_map3, cyclic) = removeUnits (concatMap getCyclicSCC sccs) index pkg_map2 unusable_cyclic = mk_unusable CyclicDependencies depsNotAvailable pkg_map3 cyclic -- Apply ignore flags - directly_ignored = ignorePackages ignore_flags (Map.elems pkg_map3) - (pkg_map4, ignored) = removePackages (Map.keys directly_ignored) index pkg_map3 + directly_ignored = ignoreUnits ignore_flags (Map.elems pkg_map3) + (pkg_map4, ignored) = removeUnits (Map.keys directly_ignored) index pkg_map3 unusable_ignored = mk_unusable IgnoredDependencies depsNotAvailable pkg_map4 ignored -- Knock out packages whose dependencies don't agree with ABI -- (i.e., got invalidated due to shadowing) directly_shadowed = filter (not . null . depsAbiMismatch pkg_map4) (Map.elems pkg_map4) - (pkg_map5, shadowed) = removePackages (map unitId directly_shadowed) index pkg_map4 + (pkg_map5, shadowed) = removeUnits (map unitId directly_shadowed) index pkg_map4 unusable_shadowed = mk_unusable ShadowedDependencies depsAbiMismatch pkg_map5 shadowed unusable = directly_ignored `Map.union` unusable_ignored @@ -1344,17 +1344,17 @@ validateDatabase dflags pkg_map1 = -- When all the command-line options are in, we can process our package -- settings and populate the package state. -mkPackageState +mkUnitState :: DynFlags -- initial databases, in the order they were specified on -- the command line (later databases shadow earlier ones) -> [UnitDatabase UnitId] -> [UnitId] -- preloaded packages - -> IO (PackageState, + -> IO (UnitState, [UnitId], -- new packages to preload [(ModuleName, Module)]) -mkPackageState dflags dbs preload0 = do +mkUnitState dflags dbs preload0 = do {- Plan. @@ -1494,7 +1494,7 @@ mkPackageState dflags dbs preload0 = do -- it modifies the unit ids of wired in packages, but when we process -- package arguments we need to key against the old versions. -- - (pkgs2, wired_map) <- findWiredInPackages dflags prec_map pkgs1 vis_map2 + (pkgs2, wired_map) <- findWiredInUnits dflags prec_map pkgs1 vis_map2 let pkg_db = mkUnitInfoMap pkgs2 -- Update the visibility map, so we treat wired packages as visible. @@ -1584,8 +1584,8 @@ mkPackageState dflags dbs preload0 = do FormatText (pprModuleMap mod_map) - -- Force pstate to avoid leaking the dflags passed to mkPackageState - let !pstate = PackageState + -- Force pstate to avoid leaking the dflags passed to mkUnitState + let !pstate = UnitState { preloadUnits = dep_preload , explicitUnits = explicit_pkgs , unitInfoMap = pkg_db @@ -1874,10 +1874,10 @@ getUnitFrameworks dflags pkgs = do -- | Takes a 'ModuleName', and if the module is in any package returns -- list of modules which take that name. -lookupModuleInAllPackages :: PackageState +lookupModuleInAllUnits :: UnitState -> ModuleName -> [(Module, UnitInfo)] -lookupModuleInAllPackages pkgs m +lookupModuleInAllUnits pkgs m = case lookupModuleWithSuggestions pkgs m Nothing of LookupFound a b -> [(a,b)] LookupMultiple rs -> map f rs @@ -1904,21 +1904,21 @@ data LookupResult = data ModuleSuggestion = SuggestVisible ModuleName Module ModuleOrigin | SuggestHidden ModuleName Module ModuleOrigin -lookupModuleWithSuggestions :: PackageState +lookupModuleWithSuggestions :: UnitState -> ModuleName -> Maybe FastString -> LookupResult lookupModuleWithSuggestions pkgs = lookupModuleWithSuggestions' pkgs (moduleNameProvidersMap pkgs) -lookupPluginModuleWithSuggestions :: PackageState +lookupPluginModuleWithSuggestions :: UnitState -> ModuleName -> Maybe FastString -> LookupResult lookupPluginModuleWithSuggestions pkgs = lookupModuleWithSuggestions' pkgs (pluginModuleNameProvidersMap pkgs) -lookupModuleWithSuggestions' :: PackageState +lookupModuleWithSuggestions' :: UnitState -> ModuleNameProvidersMap -> ModuleName -> Maybe FastString @@ -1965,10 +1965,10 @@ lookupModuleWithSuggestions' pkgs mod_map m mb_pn case o of ModHidden -> if go pkg then ModHidden else mempty (ModUnusable _) -> if go pkg then o else mempty - ModOrigin { fromOrigPackage = e, fromExposedReexport = res, + ModOrigin { fromOrigUnit = e, fromExposedReexport = res, fromHiddenReexport = rhs } -> ModOrigin { - fromOrigPackage = if go pkg then e else Nothing + fromOrigUnit = if go pkg then e else Nothing , fromExposedReexport = filter go res , fromHiddenReexport = filter go rhs , fromPackageFlag = False -- always excluded @@ -2079,7 +2079,7 @@ missingDependencyMsg (Just parent) -- these details in the IndefUnitId itself because we don't want to query -- DynFlags each time we pretty-print the IndefUnitId -- -mkIndefUnitId :: PackageState -> FastString -> IndefUnitId +mkIndefUnitId :: UnitState -> FastString -> IndefUnitId mkIndefUnitId pkgstate raw = let uid = UnitId raw in case lookupUnitId pkgstate uid of @@ -2087,11 +2087,11 @@ mkIndefUnitId pkgstate raw = Just c -> Indefinite uid $ Just $ mkUnitPprInfo c -- | Update component ID details from the database -updateIndefUnitId :: PackageState -> IndefUnitId -> IndefUnitId +updateIndefUnitId :: UnitState -> IndefUnitId -> IndefUnitId updateIndefUnitId pkgstate uid = mkIndefUnitId pkgstate (unitIdFS (indefUnit uid)) -displayUnitId :: PackageState -> UnitId -> Maybe String +displayUnitId :: UnitState -> UnitId -> Maybe String displayUnitId pkgstate uid = fmap unitPackageIdString (lookupUnitId pkgstate uid) @@ -2099,19 +2099,19 @@ displayUnitId pkgstate uid = -- Displaying packages -- | Show (very verbose) package info -pprPackages :: PackageState -> SDoc -pprPackages = pprPackagesWith pprUnitInfo +pprUnits :: UnitState -> SDoc +pprUnits = pprUnitsWith pprUnitInfo -pprPackagesWith :: (UnitInfo -> SDoc) -> PackageState -> SDoc -pprPackagesWith pprIPI pkgstate = +pprUnitsWith :: (UnitInfo -> SDoc) -> UnitState -> SDoc +pprUnitsWith pprIPI pkgstate = vcat (intersperse (text "---") (map pprIPI (listUnitInfo pkgstate))) --- | Show simplified package info. +-- | Show simplified unit info. -- -- The idea is to only print package id, and any information that might -- be different from the package databases (exposure, trust) -pprPackagesSimple :: PackageState -> SDoc -pprPackagesSimple = pprPackagesWith pprIPI +pprUnitsSimple :: UnitState -> SDoc +pprUnitsSimple = pprUnitsWith pprIPI where pprIPI ipi = let i = unitIdFS (unitId ipi) e = if unitIsExposed ipi then text "E" else text " " t = if unitIsTrusted ipi then text "T" else text " " @@ -2136,7 +2136,7 @@ fsPackageName info = fs -- | Given a fully instantiated 'InstantiatedUnit', improve it into a -- 'RealUnit' if we can find it in the package database. -improveUnit :: PackageState -> Unit -> Unit +improveUnit :: UnitState -> Unit -> Unit improveUnit state u = improveUnit' (unitInfoMap state) (preloadClosure state) u -- | Given a fully instantiated 'InstantiatedUnit', improve it into a @@ -2162,7 +2162,7 @@ improveUnit' pkg_map closure uid = -- references a matching installed unit. -- -- See Note [VirtUnit to RealUnit improvement] -instUnitToUnit :: PackageState -> InstantiatedUnit -> Unit +instUnitToUnit :: UnitState -> InstantiatedUnit -> Unit instUnitToUnit state iuid = -- NB: suppose that we want to compare the instantiated -- unit p[H=impl:H] against p+abcd (where p+abcd @@ -2181,14 +2181,14 @@ type ShHoleSubst = ModuleNameEnv Module -- directly on a 'nameModule', see Note [Representation of module/name variable]. -- @p[A=<A>]:B@ maps to @p[A=q():A]:B@ with @A=q():A@; -- similarly, @<A>@ maps to @q():A@. -renameHoleModule :: PackageState -> ShHoleSubst -> Module -> Module +renameHoleModule :: UnitState -> ShHoleSubst -> Module -> Module renameHoleModule state = renameHoleModule' (unitInfoMap state) (preloadClosure state) -- | Substitutes holes in a 'Unit', suitable for renaming when -- an include occurs; see Note [Representation of module/name variable]. -- -- @p[A=<A>]@ maps to @p[A=<B>]@ with @A=<B>@. -renameHoleUnit :: PackageState -> ShHoleSubst -> Unit -> Unit +renameHoleUnit :: UnitState -> ShHoleSubst -> Unit -> Unit renameHoleUnit state = renameHoleUnit' (unitInfoMap state) (preloadClosure state) -- | Like 'renameHoleModule', but requires only 'ClosureUnitInfoMap' @@ -2224,7 +2224,7 @@ renameHoleUnit' pkg_map closure env uid = -- | Injects an 'InstantiatedModule' to 'Module' (see also -- 'instUnitToUnit'. -instModuleToModule :: PackageState -> InstantiatedModule -> Module +instModuleToModule :: UnitState -> InstantiatedModule -> Module instModuleToModule pkgstate (Module iuid mod_name) = mkModule (instUnitToUnit pkgstate iuid) mod_name diff --git a/compiler/GHC/Unit/State.hs-boot b/compiler/GHC/Unit/State.hs-boot index 2f345cdf81..cc77d2b478 100644 --- a/compiler/GHC/Unit/State.hs-boot +++ b/compiler/GHC/Unit/State.hs-boot @@ -4,10 +4,10 @@ import GHC.Prelude import GHC.Data.FastString import {-# SOURCE #-} GHC.Unit.Types (IndefUnitId, UnitId) -data PackageState +data UnitState data UnitDatabase unit -emptyPackageState :: PackageState -mkIndefUnitId :: PackageState -> FastString -> IndefUnitId -displayUnitId :: PackageState -> UnitId -> Maybe String -updateIndefUnitId :: PackageState -> IndefUnitId -> IndefUnitId +emptyUnitState :: UnitState +mkIndefUnitId :: UnitState -> FastString -> IndefUnitId +displayUnitId :: UnitState -> UnitId -> Maybe String +updateIndefUnitId :: UnitState -> IndefUnitId -> IndefUnitId diff --git a/compiler/GHC/Unit/Types.hs b/compiler/GHC/Unit/Types.hs index 831dbac829..ffe9b38bf9 100644 --- a/compiler/GHC/Unit/Types.hs +++ b/compiler/GHC/Unit/Types.hs @@ -601,7 +601,7 @@ had used @-ignore-package@). The affected packages are compiled with, e.g., @-this-unit-id base@, so that the symbols in the object files have the unversioned unit id in their name. -Make sure you change 'GHC.Unit.State.findWiredInPackages' if you add an entry here. +Make sure you change 'GHC.Unit.State.findWiredInUnits' if you add an entry here. For `integer-gmp`/`integer-simple` we also change the base name to `integer-wired-in`, but this is fundamentally no different. |