ghcide-2.7.0.0: The core of an IDE
Safe HaskellSafe-Inferred
LanguageGHC2021

Development.IDE.GHC.Compat.Env

Description

Compat module for the main Driver types, such as HscEnv, UnitEnv and some DynFlags compat functions.

Synopsis

Documentation

data HscEnv #

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

Instances details
ContainsDynFlags HscEnv 
Instance details

Defined in GHC.Driver.Env.Types

data InteractiveContext #

Interactive context, recording information about the state of the context in which statements are executed in a GHCi session.

Constructors

InteractiveContext 

Fields

  • ic_dflags :: DynFlags

    The DynFlags used to evaluate interactive expressions and statements.

  • ic_mod_index :: Int

    Each GHCi stmt or declaration brings some new things into scope. We give them names like interactive:Ghci9.T, where the ic_index is the '9'. The ic_mod_index is incremented whenever we add something to ic_tythings See Note [The interactive package]

  • ic_imports :: [InteractiveImport]

    The GHCi top-level scope (icReaderEnv) is extended with these imports

    This field is only stored here so that the client can retrieve it with GHC.getContext. GHC itself doesn't use it, but does reset it to empty sometimes (such as before a GHC.load). The context is set with GHC.setContext.

  • ic_tythings :: [TyThing]

    TyThings defined by the user, in reverse order of definition (ie most recent at the front). Also used in GHC.Tc.Module.runTcInteractive to fill the type checker environment. See Note [ic_tythings]

  • ic_gre_cache :: IcGlobalRdrEnv

    Essentially the cached GlobalRdrEnv.

    The GlobalRdrEnv contains everything in scope at the command line, both imported and everything in ic_tythings, with the correct shadowing.

    The IcGlobalRdrEnv contains extra data to allow efficient recalculation when the set of imports change. See Note [icReaderEnv recalculation]

  • ic_instances :: (InstEnv, [FamInst])

    All instances and family instances created during this session. These are grabbed en masse after each update to be sure that proper overlapping is retained. That is, rather than re-check the overlapping each time we update the context, we just take the results from the instance code that already does that.

  • ic_fix_env :: FixityEnv

    Fixities declared in let statements

  • ic_default :: Maybe [Type]

    The current default types, set by a 'default' declaration

  • ic_resume :: [Resume]

    The stack of breakpoint contexts

  • ic_monad :: Name

    The monad that GHCi is executing in

  • ic_int_print :: Name

    The function that is used for printing results of expressions in ghci and -e mode.

  • ic_cwd :: Maybe FilePath

    virtual CWD of the program

  • ic_plugins :: !Plugins

    Cache of loaded plugins. We store them here to avoid having to load them every time we switch to the interactive context.

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_tmpfs :: HscEnv -> TmpFs #

Temporary files

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.

hsc_hooks :: HscEnv -> Hooks #

Hooks

data TmpFs #

Temporary file-system

HomeUnit

mkHomeModule :: HomeUnit -> ModuleName -> Module #

Make a module in home unit

Provide backwards Compatible

data Logger #

data UnitEnv #

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

type Ways = Set Way #

data Way #

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).

Instances

Instances details
Read Way 
Instance details

Defined in GHC.Platform.Ways

Show Way 
Instance details

Defined in GHC.Platform.Ways

Methods

showsPrec :: Int -> Way -> ShowS #

show :: Way -> String #

showList :: [Way] -> ShowS #

Eq Way 
Instance details

Defined in GHC.Platform.Ways

Methods

(==) :: Way -> Way -> Bool #

(/=) :: Way -> Way -> Bool #

Ord Way 
Instance details

Defined in GHC.Platform.Ways

Methods

compare :: Way -> Way -> Ordering #

(<) :: Way -> Way -> Bool #

(<=) :: Way -> Way -> Bool #

(>) :: Way -> Way -> Bool #

(>=) :: Way -> Way -> Bool #

max :: Way -> Way -> Way #

min :: Way -> Way -> Way #

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

data Backend #

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.

Instances

Instances details
Show Backend

The Show instance is for messages only. If code depends on what's in the string, you deserve what happens to you.

Instance details

Defined in GHC.Driver.Backend