Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Hsc a = Hsc (HscEnv -> Messages GhcMessage -> IO (a, Messages GhcMessage))
- data HscEnv = HscEnv {
- hsc_dflags :: DynFlags
- hsc_targets :: [Target]
- hsc_mod_graph :: ModuleGraph
- hsc_IC :: InteractiveContext
- hsc_NC :: !NameCache
- hsc_FC :: !FinderCache
- hsc_type_env_vars :: KnotVars (IORef TypeEnv)
- hsc_interp :: Maybe Interp
- hsc_plugins :: !Plugins
- hsc_unit_env :: UnitEnv
- hsc_logger :: !Logger
- hsc_hooks :: !Hooks
- hsc_tmpfs :: !TmpFs
- hsc_llvm_config :: !LlvmConfigCache
- hscUpdateFlags :: (DynFlags -> DynFlags) -> HscEnv -> HscEnv
- hscSetFlags :: HasDebugCallStack => DynFlags -> HscEnv -> HscEnv
- hsc_home_unit :: HscEnv -> HomeUnit
- hsc_home_unit_maybe :: HscEnv -> Maybe HomeUnit
- hsc_units :: HasDebugCallStack => HscEnv -> UnitState
- hsc_HPT :: HscEnv -> HomePackageTable
- hsc_HUE :: HscEnv -> HomeUnitEnv
- hsc_HUG :: HscEnv -> HomeUnitGraph
- hsc_all_home_unit_ids :: HscEnv -> Set UnitId
- hscUpdateLoggerFlags :: HscEnv -> HscEnv
- hscUpdateHUG :: (HomeUnitGraph -> HomeUnitGraph) -> HscEnv -> HscEnv
- hscUpdateHPT_lazy :: (HomePackageTable -> HomePackageTable) -> HscEnv -> HscEnv
- hscUpdateHPT :: (HomePackageTable -> HomePackageTable) -> HscEnv -> HscEnv
- hscSetActiveHomeUnit :: HasDebugCallStack => HomeUnit -> HscEnv -> HscEnv
- hscSetActiveUnitId :: HasDebugCallStack => UnitId -> HscEnv -> HscEnv
- hscActiveUnitId :: HscEnv -> UnitId
- runHsc :: HscEnv -> Hsc a -> IO a
- runHsc' :: HscEnv -> Hsc a -> IO (a, Messages GhcMessage)
- mkInteractiveHscEnv :: HscEnv -> HscEnv
- runInteractiveHsc :: HscEnv -> Hsc a -> IO a
- hscEPS :: HscEnv -> IO ExternalPackageState
- hscInterp :: HscEnv -> Interp
- hptCompleteSigs :: HscEnv -> [CompleteMatch]
- hptAllInstances :: HscEnv -> (InstEnv, [FamInst])
- hptInstancesBelow :: HscEnv -> UnitId -> ModuleNameWithIsBoot -> (InstEnv, [FamInst])
- hptAnns :: HscEnv -> Maybe (UnitId, ModuleNameWithIsBoot) -> [Annotation]
- hptAllThings :: (HomeModInfo -> [a]) -> HscEnv -> [a]
- hptSomeThingsBelowUs :: (HomeModInfo -> [a]) -> Bool -> HscEnv -> UnitId -> ModuleNameWithIsBoot -> [a]
- hptRules :: HscEnv -> UnitId -> ModuleNameWithIsBoot -> [CoreRule]
- prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv
- discardIC :: HscEnv -> HscEnv
- lookupType :: HscEnv -> Name -> IO (Maybe TyThing)
- lookupIfaceByModule :: HomeUnitGraph -> PackageIfaceTable -> Module -> Maybe ModIface
- mainModIs :: HomeUnitEnv -> Module
Documentation
The Hsc monad: Passing an environment and diagnostic state
Hsc (HscEnv -> Messages GhcMessage -> IO (a, Messages GhcMessage)) |
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.
HscEnv | |
|
Instances
ContainsDynFlags HscEnv Source # | |
Defined in GHC.Driver.Env.Types extractDynFlags :: HscEnv -> DynFlags Source # |
hscSetFlags :: HasDebugCallStack => DynFlags -> HscEnv -> HscEnv Source #
Set Flags
hsc_home_unit :: HscEnv -> HomeUnit Source #
hsc_HPT :: HscEnv -> HomePackageTable Source #
hsc_HUE :: HscEnv -> HomeUnitEnv Source #
hsc_HUG :: HscEnv -> HomeUnitGraph Source #
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.
hscUpdateHUG :: (HomeUnitGraph -> HomeUnitGraph) -> HscEnv -> HscEnv Source #
hscUpdateHPT_lazy :: (HomePackageTable -> HomePackageTable) -> HscEnv -> HscEnv Source #
hscUpdateHPT :: (HomePackageTable -> HomePackageTable) -> HscEnv -> HscEnv Source #
hscSetActiveHomeUnit :: HasDebugCallStack => HomeUnit -> HscEnv -> HscEnv Source #
hscSetActiveUnitId :: HasDebugCallStack => UnitId -> HscEnv -> HscEnv Source #
hscActiveUnitId :: HscEnv -> UnitId 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.
hscInterp :: HscEnv -> Interp Source #
Retrieve the target code interpreter
Fails if no target code interpreter is available
hptCompleteSigs :: HscEnv -> [CompleteMatch] Source #
hptAllInstances :: HscEnv -> (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.
hptInstancesBelow :: HscEnv -> UnitId -> ModuleNameWithIsBoot -> (InstEnv, [FamInst]) Source #
Find instances visible from the given set of imports
hptAnns :: HscEnv -> Maybe (UnitId, 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 -> UnitId -> ModuleNameWithIsBoot -> [a] Source #
Get things from modules "below" this one (in the dependency sense) C.f Inst.hptInstances
hptRules :: HscEnv -> UnitId -> 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
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 -> Maybe ModIface Source #
mainModIs :: HomeUnitEnv -> Module Source #