ghc-9.13: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Driver.Env

Contents

Synopsis

Documentation

newtype Hsc a Source #

The Hsc monad: Passing an environment and diagnostic state

Constructors

Hsc (HscEnv -> Messages GhcMessage -> IO (a, Messages GhcMessage)) 

Instances

Instances details
HasDynFlags Hsc Source # 
Instance details

Defined in GHC.Driver.Env.Types

HasLogger Hsc Source # 
Instance details

Defined in GHC.Driver.Env.Types

Applicative Hsc Source # 
Instance details

Defined in GHC.Driver.Env.Types

Methods

pure :: a -> Hsc a #

(<*>) :: Hsc (a -> b) -> Hsc a -> Hsc b #

liftA2 :: (a -> b -> c) -> Hsc a -> Hsc b -> Hsc c #

(*>) :: Hsc a -> Hsc b -> Hsc b #

(<*) :: Hsc a -> Hsc b -> Hsc a #

Functor Hsc Source # 
Instance details

Defined in GHC.Driver.Env.Types

Methods

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

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

Monad Hsc Source # 
Instance details

Defined in GHC.Driver.Env.Types

Methods

(>>=) :: Hsc a -> (a -> Hsc b) -> Hsc b #

(>>) :: Hsc a -> Hsc b -> Hsc b #

return :: a -> Hsc a #

MonadIO Hsc Source # 
Instance details

Defined in GHC.Driver.Env.Types

Methods

liftIO :: IO a -> Hsc a #

data HscEnv Source #

HscEnv is like Session, except that some of the fields are immutable. An HscEnv is used to compile a single module from plain Haskell source code (after preprocessing) to either C, assembly or C--. It's also used to store the dynamic linker state to allow for multiple linkers in the same address space. Things like the module graph don't change during a single compilation.

Historical note: "hsc" used to be the name of the compiler binary, when there was a separate driver and compiler. To compile a single module, the driver would invoke hsc on the source code... so nowadays we think of hsc as the layer of the compiler that deals with compiling a single module.

Constructors

HscEnv 

Fields

Instances

Instances details
ContainsDynFlags HscEnv Source # 
Instance details

Defined in GHC.Driver.Env.Types

hscUpdateLoggerFlags :: HscEnv -> HscEnv Source #

Update the LogFlags of the Log in hsc_logger from the DynFlags in hsc_dflags. You need to call this when DynFlags are modified.

runHsc :: HscEnv -> Hsc a -> IO a Source #

mkInteractiveHscEnv :: HscEnv -> HscEnv Source #

Switches in the DynFlags and Plugins from the InteractiveContext

runInteractiveHsc :: HscEnv -> Hsc a -> IO a Source #

A variant of runHsc that switches in the DynFlags and Plugins from the InteractiveContext before running the Hsc computation.

hscEPS :: HscEnv -> IO ExternalPackageState Source #

Retrieve the ExternalPackageState cache.

hscInterp :: HscEnv -> Interp Source #

Retrieve the target code interpreter

Fails if no target code interpreter is available

prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv Source #

Deal with gathering annotations in from all possible places and combining them into a single AnnEnv

discardIC :: HscEnv -> HscEnv Source #

Discard the contents of the InteractiveContext, but keep the DynFlags and the loaded plugins. It will also keep ic_int_print and ic_monad if their names are from external packages.

lookupType :: HscEnv -> Name -> IO (Maybe TyThing) Source #

Find the TyThing for the given Name by using all the resources at our disposal: the compiled modules in the HomePackageTable and the compiled modules in other packages that live in PackageTypeEnv. Note that this does NOT look up the TyThing in the module being compiled: you have to do that yourself, if desired

lookupIfaceByModule :: HomeUnitGraph -> PackageIfaceTable -> Module -> IO (Maybe ModIface) Source #

Find the ModIface for a Module, searching in both the loaded home and external package module information

hugRulesBelow :: HscEnv -> UnitId -> ModuleNameWithIsBoot -> IO RuleBase Source #

Find all rules in modules that are in the transitive closure of the given module.

hugInstancesBelow :: HscEnv -> UnitId -> ModuleNameWithIsBoot -> IO (InstEnv, [FamInst]) Source #

Find instances visible from the given set of imports

hugAnnsBelow :: HscEnv -> UnitId -> ModuleNameWithIsBoot -> IO AnnEnv Source #

Get annotations from all modules "below" this one (in the dependency sense) within the home units. If the module is Nothing, returns all annotations in the home units.

Legacy API

hscUpdateHPT :: (HomePackageTable -> HomePackageTable) -> HscEnv -> HscEnv Source #

Deprecated: Updating the HPT directly is no longer a supported operation. Instead, the HPT is an insert-only data structure. If you want to overwrite an existing entry, just use hscInsertHPT to insert it again (it will override the existing entry if there is one). See PackageTable for more details.