ghc-9.13: The GHC API
Safe HaskellNone
LanguageGHC2021

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

Documentation

data HomeUnitEnv Source #

Constructors

HomeUnitEnv 

Fields

  • homeUnitEnv_units :: !UnitState

    External units

  • homeUnitEnv_unit_dbs :: !(Maybe [UnitDatabase UnitId])

    Stack of unit databases for the target platform.

    This field is populated with the result of initUnits.

    Nothing means the databases have never been read from disk.

    Usually we don't reload the databases from disk if they are cached, even if the database flags changed!

  • homeUnitEnv_dflags :: DynFlags

    The dynamic flag settings

  • homeUnitEnv_hpt :: HomePackageTable

    The home package table describes already-compiled home-package modules, excluding the module we are compiling right now. (In one-shot mode the current module is the only home-package module, so homeUnitEnv_hpt is empty. All other modules count as "external-package" modules. However, even in GHCi mode, hi-boot interfaces are demand-loaded into the external-package table.)

    homeUnitEnv_hpt is not mutable because we only demand-load external packages; the home package is eagerly loaded, module by module, by the compilation manager.

    The HPT may contain modules compiled earlier by --make but not actually below the current module in the dependency graph.

    (This changes a previous invariant: changed Jan 05.)

  • homeUnitEnv_home_unit :: !(Maybe HomeUnit)

    Home-unit

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

renameUnitId oldUnit newUnit hug, if oldUnit 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)

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.

allCompleteSigs :: HomeUnitGraph -> IO CompleteMatches Source #

Get all CompleteMatches (arising from COMPLETE pragmas) present across all home units.

Utilities

Printing

Auxiliary internal structure

newtype UnitEnvGraph v Source #

Constructors

UnitEnvGraph 

Fields

Instances

Instances details
Functor UnitEnvGraph Source # 
Instance details

Defined in GHC.Unit.Home.Graph

Methods

fmap :: (a -> b) -> UnitEnvGraph a -> UnitEnvGraph b #

(<$) :: a -> UnitEnvGraph b -> UnitEnvGraph a #

Foldable UnitEnvGraph Source # 
Instance details

Defined in GHC.Unit.Home.Graph

Methods

fold :: Monoid m => UnitEnvGraph m -> m #

foldMap :: Monoid m => (a -> m) -> UnitEnvGraph a -> m #

foldMap' :: Monoid m => (a -> m) -> UnitEnvGraph a -> m #

foldr :: (a -> b -> b) -> b -> UnitEnvGraph a -> b #

foldr' :: (a -> b -> b) -> b -> UnitEnvGraph a -> b #

foldl :: (b -> a -> b) -> b -> UnitEnvGraph a -> b #

foldl' :: (b -> a -> b) -> b -> UnitEnvGraph a -> b #

foldr1 :: (a -> a -> a) -> UnitEnvGraph a -> a #

foldl1 :: (a -> a -> a) -> UnitEnvGraph a -> a #

toList :: UnitEnvGraph a -> [a] #

null :: UnitEnvGraph a -> Bool #

length :: UnitEnvGraph a -> Int #

elem :: Eq a => a -> UnitEnvGraph a -> Bool #

maximum :: Ord a => UnitEnvGraph a -> a #

minimum :: Ord a => UnitEnvGraph a -> a #

sum :: Num a => UnitEnvGraph a -> a #

product :: Num a => UnitEnvGraph a -> a #

Traversable UnitEnvGraph Source # 
Instance details

Defined in GHC.Unit.Home.Graph

Methods

traverse :: Applicative f => (a -> f b) -> UnitEnvGraph a -> f (UnitEnvGraph b) #

sequenceA :: Applicative f => UnitEnvGraph (f a) -> f (UnitEnvGraph a) #

mapM :: Monad m => (a -> m b) -> UnitEnvGraph a -> m (UnitEnvGraph b) #

sequence :: Monad m => UnitEnvGraph (m a) -> m (UnitEnvGraph a) #

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 #