| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Development.IDE.GHC.Compat.Env
Description
Synopsis
- data HscEnv
- 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
 
- 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
- type TmpFs = ()
- hscHomeUnit :: HscEnv -> HomeUnit
- type HomeUnit = UnitId
- setHomeUnitId_ :: UnitId -> DynFlags -> DynFlags
- mkHomeModule :: HomeUnit -> ModuleName -> Module
- newtype Logger = Logger {}
- type 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 = [Way]
- data Way
- hostFullWays :: Ways
- setWays :: Ways -> DynFlags -> DynFlags
- wayGeneralFlags :: Platform -> Way -> [GeneralFlag]
- wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag]
- type Backend = HscTarget
- setBackend :: Backend -> DynFlags -> DynFlags
- 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.
data InteractiveContext #
Interactive context, recording information about the state of the context in which statements are executed in a GHCi session.
Constructors
| InteractiveContext | |
| Fields 
 | |
setInteractiveDynFlags :: GhcMonad m => DynFlags -> m () #
Set the DynFlags used to evaluate interactive expressions.
 Note: this cannot be used for changes to packages.  Use
 setSessionDynFlags, or setProgramDynFlags and then copy the
 pkgState 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 Source #
hsc_unit_env :: HscEnv -> UnitEnv Source #
HomeUnit
hscHomeUnit :: HscEnv -> HomeUnit Source #
mkHomeModule :: HomeUnit -> ModuleName -> Module Source #
Provide backwards Compatible
Home Unit
homeUnitId_ :: DynFlags -> UnitId Source #
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 Source #
Ways
hostFullWays :: Ways Source #
wayGeneralFlags :: Platform -> Way -> [GeneralFlag] #
wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag] #