| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
GHC.Unit.Home.Graph
Description
A HomeUnitGraph (HUG) collects information about all the home units.
Crucially, each node in a HomeUnitGraph includes a HomePackageTable.
Often, we don't want to query just a single HomePackageTable, but rather all
HomePackageTables of all home units.
This module is responsible for maintaining this bridge between querying all
home units vs querying the home package table directly. Think lookupHug vs
lookupHpt, hugAllInstances vs hptAllInstances, where the hug version
replies with information from all home units, and the hpt version with
information pertaining to a single home unit.
Meant to be imported qualified as HUG.
Example usage:
import GHC.Unit.Home.Graph (HomeUnitGraph, HomeUnitEnv) import qualified GHC.Unit.Home.Graph as HUG usage = ... HUG.insertHug hug uid modname modinfo ...
Synopsis
- type HomeUnitGraph = UnitEnvGraph HomeUnitEnv
- data HomeUnitEnv = HomeUnitEnv {}
- mkHomeUnitEnv :: UnitState -> Maybe [UnitDatabase UnitId] -> DynFlags -> HomePackageTable -> Maybe HomeUnit -> HomeUnitEnv
- addHomeModInfoToHug :: HomeModInfo -> HomeUnitGraph -> IO ()
- restrictHug :: [(UnitId, [HomeModInfo])] -> HomeUnitGraph -> IO ()
- renameUnitId :: UnitId -> UnitId -> HomeUnitGraph -> Maybe HomeUnitGraph
- allUnits :: HomeUnitGraph -> Set UnitId
- updateUnitFlags :: UnitId -> (DynFlags -> DynFlags) -> HomeUnitGraph -> HomeUnitGraph
- lookupHug :: HomeUnitGraph -> UnitId -> ModuleName -> IO (Maybe HomeModInfo)
- lookupHugByModule :: Module -> HomeUnitGraph -> IO (Maybe HomeModInfo)
- lookupHugUnit :: Unit -> HomeUnitGraph -> Maybe HomeUnitEnv
- lookupHugUnitId :: UnitId -> HomeUnitGraph -> Maybe HomeUnitEnv
- lookupAllHug :: HomeUnitGraph -> ModuleName -> IO [HomeModInfo]
- memberHugUnit :: Unit -> HomeUnitGraph -> Bool
- memberHugUnitId :: UnitId -> HomeUnitGraph -> Bool
- transitiveHomeDeps :: UnitId -> HomeUnitGraph -> Maybe [UnitId]
- allInstances :: HomeUnitGraph -> IO (InstEnv, [FamInst])
- allFamInstances :: HomeUnitGraph -> IO (ModuleEnv FamInstEnv)
- allAnns :: HomeUnitGraph -> IO AnnEnv
- allCompleteSigs :: HomeUnitGraph -> IO CompleteMatches
- hugSCCs :: HomeUnitGraph -> [SCC UnitId]
- hugFromList :: [(UnitId, HomeUnitEnv)] -> HomeUnitGraph
- pprHomeUnitGraph :: HomeUnitGraph -> IO SDoc
- pprHomeUnitEnv :: UnitId -> HomeUnitEnv -> IO SDoc
- newtype UnitEnvGraph v = UnitEnvGraph {
- unitEnv_graph :: Map UnitEnvGraphKey v
- unitEnv_lookup_maybe :: UnitEnvGraphKey -> UnitEnvGraph v -> Maybe v
- unitEnv_foldWithKey :: (b -> UnitEnvGraphKey -> a -> b) -> b -> UnitEnvGraph a -> b
- unitEnv_singleton :: UnitEnvGraphKey -> v -> UnitEnvGraph v
- unitEnv_adjust :: (v -> v) -> UnitEnvGraphKey -> UnitEnvGraph v -> UnitEnvGraph v
- unitEnv_keys :: UnitEnvGraph v -> Set UnitEnvGraphKey
- unitEnv_insert :: UnitEnvGraphKey -> v -> UnitEnvGraph v -> UnitEnvGraph v
- unitEnv_new :: Map UnitEnvGraphKey v -> UnitEnvGraph v
- unitEnv_lookup :: UnitEnvGraphKey -> UnitEnvGraph v -> v
- unitEnv_traverseWithKey :: Applicative f => (UnitEnvGraphKey -> a -> f b) -> UnitEnvGraph a -> f (UnitEnvGraph b)
- unitEnv_assocs :: UnitEnvGraph a -> [(UnitEnvGraphKey, a)]
Documentation
type HomeUnitGraph = UnitEnvGraph HomeUnitEnv Source #
data HomeUnitEnv Source #
Constructors
| HomeUnitEnv | |
Fields
| |
mkHomeUnitEnv :: UnitState -> Maybe [UnitDatabase UnitId] -> DynFlags -> HomePackageTable -> Maybe HomeUnit -> HomeUnitEnv Source #
Operations
addHomeModInfoToHug :: HomeModInfo -> HomeUnitGraph -> IO () Source #
Add an entry to the HomePackageTable under the unit of that entry.
restrictHug :: [(UnitId, [HomeModInfo])] -> HomeUnitGraph -> IO () Source #
Thin each HPT variable to only contain keys from the given dependencies. This is used at the end of upsweep to make sure that only completely successfully loaded modules are visible for subsequent operations.
renameUnitId :: UnitId -> UnitId -> HomeUnitGraph -> Maybe HomeUnitGraph Source #
Rename a unit id in the HomeUnitGraph
, if renameUnitId oldUnit newUnit hugoldUnit is not found in hug, returns Nothing.
If it exists, the result maps newUnit to the HomeUnitEnv of the
oldUnit (and oldUnit is removed from hug)
allUnits :: HomeUnitGraph -> Set UnitId Source #
Retrieve all UnitIds of units in the HomeUnitGraph.
updateUnitFlags :: UnitId -> (DynFlags -> DynFlags) -> HomeUnitGraph -> HomeUnitGraph Source #
Set the DynFlags of the HomeUnitEnv for unit in the HomeModuleGraph
Lookups
lookupHug :: HomeUnitGraph -> UnitId -> ModuleName -> IO (Maybe HomeModInfo) Source #
Lookup the HomeModInfo of a Module in the HomeUnitGraph given its
UnitId and ModuleName (via the HomePackageTable of the corresponding unit)
lookupHugByModule :: Module -> HomeUnitGraph -> IO (Maybe HomeModInfo) Source #
Lookup the HomeModInfo of a Module in the HomeUnitGraph (via the HomePackageTable of the corresponding unit)
lookupHugUnit :: Unit -> HomeUnitGraph -> Maybe HomeUnitEnv Source #
Lookup up the HomeUnitEnv by the Unit in the HomeUnitGraph.
If the Unit can be turned into a UnitId, we behave identical to lookupHugUnitId.
A HoleUnit is never part of the HomeUnitGraph, only instantiated Units
lookupHugUnitId :: UnitId -> HomeUnitGraph -> Maybe HomeUnitEnv Source #
Lookup a HomeUnitEnv by UnitId in a HomeUnitGraph
lookupAllHug :: HomeUnitGraph -> ModuleName -> IO [HomeModInfo] Source #
Lookup all HomeModInfo that have the same ModuleName as the given ModuleName.
ModuleNames are not unique in the case of multiple home units, so there can be
more than one possible HomeModInfo.
You should always prefer lookupHug and lookupHugByModule when possible.
memberHugUnit :: Unit -> HomeUnitGraph -> Bool Source #
Check whether the Unit is present in the HomeUnitGraph
A HoleUnit is never part of the HomeUnitGraph, only instantiated Units
memberHugUnitId :: UnitId -> HomeUnitGraph -> Bool Source #
Check whether the UnitId is present in the HomeUnitGraph
Reachability
transitiveHomeDeps :: UnitId -> HomeUnitGraph -> Maybe [UnitId] Source #
Compute the transitive closure of a unit in the HomeUnitGraph.
If the argument unit is not present in the graph returns Nothing.
Very important queries
allInstances :: HomeUnitGraph -> IO (InstEnv, [FamInst]) Source #
Find all the instance declarations (of classes and families) from
the Home Package Table filtered by the provided predicate function.
Used in tcRnImports, to select the instances that are in the
transitive closure of imports from the currently compiled module.
allFamInstances :: HomeUnitGraph -> IO (ModuleEnv FamInstEnv) Source #
allCompleteSigs :: HomeUnitGraph -> IO CompleteMatches Source #
Get all CompleteMatches (arising from COMPLETE pragmas) present across
all home units.
Utilities
hugFromList :: [(UnitId, HomeUnitEnv)] -> HomeUnitGraph Source #
Printing
pprHomeUnitGraph :: HomeUnitGraph -> IO SDoc Source #
pprHomeUnitEnv :: UnitId -> HomeUnitEnv -> IO SDoc Source #
Auxiliary internal structure
newtype UnitEnvGraph v Source #
Constructors
| UnitEnvGraph | |
Fields
| |
Instances
unitEnv_lookup_maybe :: UnitEnvGraphKey -> UnitEnvGraph v -> Maybe v Source #
unitEnv_foldWithKey :: (b -> UnitEnvGraphKey -> a -> b) -> b -> UnitEnvGraph a -> b Source #
unitEnv_singleton :: UnitEnvGraphKey -> v -> UnitEnvGraph v Source #
unitEnv_adjust :: (v -> v) -> UnitEnvGraphKey -> UnitEnvGraph v -> UnitEnvGraph v Source #
unitEnv_keys :: UnitEnvGraph v -> Set UnitEnvGraphKey Source #
unitEnv_insert :: UnitEnvGraphKey -> v -> UnitEnvGraph v -> UnitEnvGraph v Source #
unitEnv_new :: Map UnitEnvGraphKey v -> UnitEnvGraph v Source #
unitEnv_lookup :: UnitEnvGraphKey -> UnitEnvGraph v -> v Source #
unitEnv_traverseWithKey :: Applicative f => (UnitEnvGraphKey -> a -> f b) -> UnitEnvGraph a -> f (UnitEnvGraph b) Source #
unitEnv_assocs :: UnitEnvGraph a -> [(UnitEnvGraphKey, a)] Source #