ghc-9.4.4: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Runtime.Context

Synopsis

Documentation

data InteractiveContext Source #

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 everytime we switch to the interctive context.

data InteractiveImport Source #

Constructors

IIDecl (ImportDecl GhcPs)

Bring the exports of a particular module (filtered by an import decl) into scope

IIModule ModuleName

Bring into scope the entire top-level envt of of this module, including the things imported into it.

Instances

Instances details
Outputable InteractiveImport Source # 
Instance details

Defined in GHC.Runtime.Context

emptyInteractiveContext :: DynFlags -> InteractiveContext Source #

Constructs an empty InteractiveContext.

extendInteractiveContext :: InteractiveContext -> [TyThing] -> InstEnv -> [FamInst] -> Maybe [Type] -> FixityEnv -> InteractiveContext Source #

extendInteractiveContext is called with new TyThings recently defined to update the InteractiveContext to include them. By putting new things first, unqualified use will pick the most recently defined thing with a given name, while still keeping the old names in scope in their qualified form (Ghci1.foo).

icInScopeTTs :: InteractiveContext -> [TyThing] Source #

This function returns the list of visible TyThings (useful for e.g. showBindings).

It picks only those TyThings that are not shadowed by later definitions on the interpreter, to not clutter :showBindings with shadowed ids, which would show up as Ghci9.foo.

Some TyThings define many names; we include them if _any_ name is still available unqualified.

icPrintUnqual :: UnitEnv -> InteractiveContext -> PrintUnqualified Source #

Get the PrintUnqualified function based on the flags and this InteractiveContext