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

GHC.Driver.Env

Synopsis

Documentation

newtype Hsc a Source #

The Hsc monad: Passing an environment and warning state

Constructors

Hsc (HscEnv -> WarningMessages -> IO (a, WarningMessages)) 

Instances

Instances details
MonadIO Hsc Source # 
Instance details

Defined in GHC.Driver.Env.Types

Methods

liftIO :: IO a -> Hsc a Source #

Applicative Hsc Source # 
Instance details

Defined in GHC.Driver.Env.Types

Methods

pure :: a -> Hsc a Source #

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

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

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

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

Functor Hsc Source # 
Instance details

Defined in GHC.Driver.Env.Types

Methods

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

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

Monad Hsc Source # 
Instance details

Defined in GHC.Driver.Env.Types

Methods

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

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

return :: a -> Hsc a Source #

HasDynFlags Hsc Source # 
Instance details

Defined in GHC.Driver.Env.Types

HasLogger Hsc Source # 
Instance details

Defined in GHC.Driver.Env.Types

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

  • hsc_dflags :: DynFlags

    The dynamic flag settings

  • hsc_targets :: [Target]

    The targets (or roots) of the current session

  • hsc_mod_graph :: ModuleGraph

    The module graph of the current session

  • hsc_IC :: InteractiveContext

    The context for evaluating interactive statements

  • hsc_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 hsc_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.)

    hsc_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.)

  • hsc_EPS :: !(IORef ExternalPackageState)

    Information about the currently loaded external packages. This is mutable because packages will be demand-loaded during a compilation run as required.

  • hsc_NC :: !(IORef NameCache)

    As with hsc_EPS, this is side-effected by compiling to reflect sucking in interface files. They cache the state of external interface files, in effect.

  • hsc_FC :: !(IORef FinderCache)

    The cached result of performing finding in the file system

  • hsc_type_env_var :: Maybe (Module, IORef TypeEnv)

    Used for one-shot compilation only, to initialise the IfGblEnv. See tcg_type_env_var for TcGblEnv. See also Note [hsc_type_env_var hack]

  • hsc_interp :: Maybe Interp

    target code interpreter (if any) to use for TH and GHCi. See Note [Target code interpreter]

  • hsc_plugins :: ![LoadedPlugin]

    plugins dynamically loaded after processing arguments. What will be loaded here is directed by DynFlags.pluginModNames. Arguments are loaded from DynFlags.pluginModNameOpts.

    The purpose of this field is to cache the plugins so they don't have to be loaded each time they are needed. See initializePlugins.

  • hsc_static_plugins :: ![StaticPlugin]

    static plugins which do not need dynamic loading. These plugins are intended to be added by GHC API users directly to this list.

    To add dynamically loaded plugins through the GHC API see addPluginModuleName instead.

  • hsc_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!

  • hsc_unit_env :: UnitEnv

    Unit environment (unit state, home unit, etc.).

    Initialized from the databases cached in hsc_unit_dbs and from the DynFlags.

  • hsc_logger :: !Logger

    Logger

  • hsc_hooks :: !Hooks

    Hooks

  • hsc_tmpfs :: !TmpFs

    Temporary files

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.

hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [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.

hptAnns :: HscEnv -> Maybe [ModuleNameWithIsBoot] -> [Annotation] Source #

Get annotations from modules "below" this one (in the dependency sense)

hptAllThings :: (HomeModInfo -> [a]) -> HscEnv -> [a] Source #

hptSomeThingsBelowUs :: (HomeModInfo -> [a]) -> Bool -> HscEnv -> [ModuleNameWithIsBoot] -> [a] Source #

Get things from modules "below" this one (in the dependency sense) C.f Inst.hptInstances

hptRules :: HscEnv -> [ModuleNameWithIsBoot] -> [CoreRule] Source #

Get rules from modules "below" this one (in the dependency sense)

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

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

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 :: HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface Source #

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