Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Hsc a = Hsc (HscEnv -> WarningMessages -> IO (a, WarningMessages))
- data HscEnv = HscEnv {
- hsc_dflags :: DynFlags
- hsc_targets :: [Target]
- hsc_mod_graph :: ModuleGraph
- hsc_IC :: InteractiveContext
- hsc_HPT :: HomePackageTable
- hsc_EPS :: !(IORef ExternalPackageState)
- hsc_NC :: !(IORef NameCache)
- hsc_FC :: !(IORef FinderCache)
- hsc_type_env_var :: Maybe (Module, IORef TypeEnv)
- hsc_interp :: Maybe Interp
- hsc_plugins :: ![LoadedPlugin]
- hsc_static_plugins :: ![StaticPlugin]
- hsc_unit_dbs :: !(Maybe [UnitDatabase UnitId])
- hsc_unit_env :: UnitEnv
- hsc_logger :: !Logger
- hsc_hooks :: !Hooks
- hsc_tmpfs :: !TmpFs
- hsc_home_unit :: HscEnv -> HomeUnit
- hsc_units :: HscEnv -> UnitState
- runHsc :: HscEnv -> Hsc a -> IO a
- mkInteractiveHscEnv :: HscEnv -> HscEnv
- runInteractiveHsc :: HscEnv -> Hsc a -> IO a
- hscEPS :: HscEnv -> IO ExternalPackageState
- hptCompleteSigs :: HscEnv -> [CompleteMatch]
- hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [FamInst])
- hptAnns :: HscEnv -> Maybe [ModuleNameWithIsBoot] -> [Annotation]
- hptAllThings :: (HomeModInfo -> [a]) -> HscEnv -> [a]
- hptSomeThingsBelowUs :: (HomeModInfo -> [a]) -> Bool -> HscEnv -> [ModuleNameWithIsBoot] -> [a]
- hptRules :: HscEnv -> [ModuleNameWithIsBoot] -> [CoreRule]
- prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv
- lookupType :: HscEnv -> Name -> IO (Maybe TyThing)
- lookupIfaceByModule :: HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
- mainModIs :: HscEnv -> Module
Documentation
The Hsc monad: Passing an environment and warning state
Hsc (HscEnv -> WarningMessages -> IO (a, WarningMessages)) |
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 | |
|
hsc_home_unit :: HscEnv -> HomeUnit 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.
hptCompleteSigs :: HscEnv -> [CompleteMatch] Source #
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