Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data HscEnv
- hsc_HPT :: HscEnv -> HomePackageTable
- data InteractiveContext = InteractiveContext {
- ic_dflags :: DynFlags
- ic_mod_index :: Int
- ic_imports :: [InteractiveImport]
- ic_tythings :: [TyThing]
- ic_rn_gbl_env :: GlobalRdrEnv
- ic_instances :: ([ClsInst], [FamInst])
- ic_fix_env :: FixityEnv
- ic_default :: Maybe [Type]
- ic_resume :: [Resume]
- ic_monad :: Name
- ic_int_print :: Name
- ic_cwd :: Maybe FilePath
- ic_plugins :: ![LoadedPlugin]
- setInteractivePrintName :: InteractiveContext -> Name -> InteractiveContext
- setInteractiveDynFlags :: GhcMonad m => DynFlags -> m ()
- hsc_dflags :: HscEnv -> DynFlags
- hsc_EPS :: HscEnv -> IORef ExternalPackageState
- hsc_logger :: HscEnv -> Logger
- hsc_tmpfs :: HscEnv -> TmpFs
- hsc_unit_env :: HscEnv -> UnitEnv
- hsc_hooks :: HscEnv -> Hooks
- hscSetHooks :: Hooks -> HscEnv -> HscEnv
- data TmpFs
- hscHomeUnit :: HscEnv -> HomeUnit
- type HomeUnit = GenHomeUnit UnitId
- setHomeUnitId_ :: UnitId -> DynFlags -> DynFlags
- mkHomeModule :: HomeUnit -> ModuleName -> Module
- data Logger
- data UnitEnv
- hscSetUnitEnv :: UnitEnv -> HscEnv -> HscEnv
- hscSetFlags :: DynFlags -> HscEnv -> HscEnv
- initTempFs :: HscEnv -> IO HscEnv
- homeUnitId_ :: DynFlags -> UnitId
- setBytecodeLinkerOptions :: DynFlags -> DynFlags
- setInterpreterLinkerOptions :: DynFlags -> DynFlags
- safeImportsOn :: DynFlags -> Bool
- type Ways = Set Way
- data Way
- hostFullWays :: Ways
- setWays :: Ways -> DynFlags -> DynFlags
- wayGeneralFlags :: Platform -> Way -> [GeneralFlag]
- wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag]
- data Backend
- setBackend :: Backend -> DynFlags -> DynFlags
- ghciBackend :: Backend
- platformDefaultBackend :: DynFlags -> Backend
Documentation
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.
hsc_HPT :: HscEnv -> 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.)
data InteractiveContext #
Interactive context, recording information about the state of the context in which statements are executed in a GHCi session.
InteractiveContext | |
|
setInteractiveDynFlags :: GhcMonad m => DynFlags -> m () #
Set the DynFlags
used to evaluate interactive expressions.
Also initialise (load) plugins.
Note: this cannot be used for changes to packages. Use
setSessionDynFlags
, or setProgramDynFlags
and then copy the
unitState
into the interactive DynFlags
.
hsc_dflags :: HscEnv -> DynFlags #
The dynamic flag settings
hsc_EPS :: HscEnv -> 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_logger :: HscEnv -> Logger #
Logger
hsc_unit_env :: HscEnv -> UnitEnv #
Unit environment (unit state, home unit, etc.).
Initialized from the databases cached in hsc_unit_dbs
and
from the DynFlags.
HomeUnit
hscHomeUnit :: HscEnv -> HomeUnit Source #
type HomeUnit = GenHomeUnit UnitId #
mkHomeModule :: HomeUnit -> ModuleName -> Module #
Make a module in home unit
Provide backwards Compatible
Home Unit
homeUnitId_ :: DynFlags -> UnitId #
Target home unit-id
DynFlags Helper
setBytecodeLinkerOptions :: DynFlags -> DynFlags Source #
We don't want to generate object code so we compile to bytecode (HscInterpreted) which implies LinkInMemory HscInterpreted
safeImportsOn :: DynFlags -> Bool #
Test if Safe Imports are on in some form
Ways
A way
Don't change the constructor order as it us used by waysTag
to create a
unique tag (e.g. thr_debug_p) which is expected by other tools (e.g. Cabal).
hostFullWays :: Ways #
Host "full" ways (i.e. ways that have an impact on the compilation, not RTS only ways).
These ways must be used when compiling codes targeting the internal interpreter.
wayGeneralFlags :: Platform -> Way -> [GeneralFlag] #
Turn these flags on when enabling this way
wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag] #
Turn these flags off when enabling this way