ghc-9.6.1: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Unit.Env

Synopsis

Documentation

data UnitEnv Source #

Constructors

UnitEnv 

Fields

unsafeGetHomeUnit :: UnitEnv -> HomeUnit Source #

Get home-unit

Unsafe because the home-unit may not be set

Unit Env helper functions

ue_renameUnitId :: HasDebugCallStack => UnitId -> UnitId -> UnitEnv -> UnitEnv Source #

Rename a unit id in the internal unit env.

ue_renameUnitId oldUnit newUnit UnitEnv, it is assumed that the oldUnit exists in the map, otherwise we panic. The DynFlags associated with the home unit will have its field homeUnitId set to newUnit.

HomeUnitEnv

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

Instances

Instances details
Outputable HomeUnitEnv Source # 
Instance details

Defined in GHC.Unit.Env

Methods

ppr :: HomeUnitEnv -> SDoc Source #

Outputable (UnitEnvGraph HomeUnitEnv) Source # 
Instance details

Defined in GHC.Unit.Env

UnitEnvGraph

newtype UnitEnvGraph v Source #

Constructors

UnitEnvGraph 

Instances

Instances details
Foldable UnitEnvGraph Source # 
Instance details

Defined in GHC.Unit.Env

Methods

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

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

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

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

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

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

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

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

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

toList :: UnitEnvGraph a -> [a] Source #

null :: UnitEnvGraph a -> Bool Source #

length :: UnitEnvGraph a -> Int Source #

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

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

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

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

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

Traversable UnitEnvGraph Source # 
Instance details

Defined in GHC.Unit.Env

Methods

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

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

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

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

Functor UnitEnvGraph Source # 
Instance details

Defined in GHC.Unit.Env

Methods

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

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

Outputable (UnitEnvGraph HomeUnitEnv) Source # 
Instance details

Defined in GHC.Unit.Env

unitEnv_foldWithKey :: (b -> UnitEnvGraphKey -> a -> b) -> b -> UnitEnvGraph a -> b Source #

Invariants

Preload units info

preloadUnitsInfo :: UnitEnv -> MaybeErr UnitErr [UnitInfo] Source #

Lookup UnitInfo for every preload unit from the UnitState and for every unit used to instantiate the home unit.

preloadUnitsInfo' :: UnitEnv -> [UnitId] -> MaybeErr UnitErr [UnitInfo] Source #

Lookup UnitInfo for every preload unit from the UnitState, for every unit used to instantiate the home unit, and for every unit explicitly passed in the given list of UnitId.

Home Module functions

isUnitEnvInstalledModule :: UnitEnv -> InstalledModule -> Bool Source #

Test if the module comes from the home unit