| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | GHC2021 | 
Development.IDE.GHC.Compat.Env
Description
Synopsis
- data HscEnv
- hsc_HPT :: HscEnv -> HomePackageTable
- data InteractiveContext = InteractiveContext {- ic_dflags :: DynFlags
- ic_mod_index :: Int
- ic_imports :: [InteractiveImport]
- ic_tythings :: [TyThing]
- ic_gre_cache :: IcGlobalRdrEnv
- ic_instances :: (InstEnv, [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 :: !Plugins
 
- setInteractivePrintName :: InteractiveContext -> Name -> InteractiveContext
- setInteractiveDynFlags :: GhcMonad m => DynFlags -> m ()
- hsc_dflags :: HscEnv -> DynFlags
- hsc_EPS :: HscEnv -> UnitEnv
- 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
- workingDirectory :: DynFlags -> Maybe FilePath
- setWorkingDirectory :: FilePath -> DynFlags -> DynFlags
- hscSetActiveUnitId :: HasDebugCallStack => UnitId -> HscEnv -> HscEnv
- reexportedModules :: DynFlags -> Set ModuleName
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.
Instances
| ContainsDynFlags HscEnv | |
| Defined in GHC.Driver.Env.Types Methods extractDynFlags :: HscEnv -> DynFlags # | |
hsc_HPT :: HscEnv -> HomePackageTable #
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.
 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_logger :: HscEnv -> Logger #
Logger with its flags.
Don't forget to update the logger flags if the logging related DynFlags change. Or better, use hscSetFlags setter which does it.
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 is 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
Backend, backwards compatible
A value of type Backend represents one of GHC's back ends.
 The set of back ends cannot be extended except by modifying the
 definition of Backend in this module.
The Backend type is abstract; that is, its value constructors are
 not exported.  It's crucial that they not be exported, because a
 value of type Backend carries only the back end's name, not its
 behavior or properties.  If Backend were not abstract, then code
 elsewhere in the compiler could depend directly on the name, not on
 the semantics, which would make it challenging to create a new back end.
 Because Backend is abstract, all the obligations of a new back
 end are enumerated in this module, in the form of functions that
 take Backend as an argument.
The issue of abstraction is discussed at great length in #20927 and !7442.
workingDirectory :: DynFlags -> Maybe FilePath #
hscSetActiveUnitId :: HasDebugCallStack => UnitId -> HscEnv -> HscEnv #
reexportedModules :: DynFlags -> Set ModuleName #