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

GHC.Linker.Types

Synopsis

Documentation

newtype Loader Source #

Constructors

Loader 

data LoaderState Source #

Constructors

LoaderState 

Fields

  • closure_env :: ClosureEnv

    Current global mapping from Names to their true values

  • itbl_env :: !ItblEnv

    The current global mapping from RdrNames of DataCons to info table addresses. When a new Unlinked is linked into the running image, or an existing module in the image is replaced, the itbl_env must be updated appropriately.

  • bcos_loaded :: ![Linkable]

    The currently loaded interpreted modules (home package)

  • objs_loaded :: ![Linkable]

    And the currently-loaded compiled modules (home package)

  • pkgs_loaded :: ![UnitId]

    The currently-loaded packages; always object code Held, as usual, in dependency order; though I am not sure if that is really important

  • temp_sos :: ![(FilePath, String)]

    We need to remember the name of previous temporary DLL/.so libraries so we can link them (see #10322)

data Linkable Source #

Information we can use to dynamically link modules into the compiler

Constructors

LM 

Fields

  • linkableTime :: UTCTime

    Time at which this linkable was built (i.e. when the bytecodes were produced, or the mod date on the files)

  • linkableModule :: Module

    The linkable module itself

  • linkableUnlinked :: [Unlinked]

    Those files and chunks of code we have yet to link.

    INVARIANT: A valid linkable always has at least one Unlinked item. If this list is empty, the Linkable represents a fake linkable, which is generated with no backend is used to avoid recompiling modules.

    ToDo: Do items get removed from this list when they get linked?

Instances

Instances details
Outputable Linkable Source # 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: Linkable -> SDoc Source #

data Unlinked Source #

Objects which have yet to be linked by the compiler

Constructors

DotO FilePath

An object file (.o)

DotA FilePath

Static archive file (.a)

DotDLL FilePath

Dynamically linked library file (.so, .dll, .dylib)

BCOs CompiledByteCode [SptEntry]

A byte-code object, lives only in memory. Also carries some static pointer table entries which should be loaded along with the BCOs. See Note [Grant plan for static forms] in GHC.Iface.Tidy.StaticPtrTable.

Instances

Instances details
Outputable Unlinked Source # 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: Unlinked -> SDoc Source #

data SptEntry Source #

An entry to be inserted into a module's static pointer table. See Note [Grand plan for static forms] in GHC.Iface.Tidy.StaticPtrTable.

Constructors

SptEntry Id Fingerprint 

Instances

Instances details
Outputable SptEntry Source # 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: SptEntry -> SDoc Source #

isObject :: Unlinked -> Bool Source #

Is this an actual file on disk we can link in somehow?

nameOfObject :: Unlinked -> FilePath Source #

Retrieve the filename of the linkable if possible. Panic if it is a byte-code object

isInterpretable :: Unlinked -> Bool Source #

Is this a bytecode linkable with no file on disk?

byteCodeOfObject :: Unlinked -> CompiledByteCode Source #

Retrieve the compiled byte-code if possible. Panic if it is a file-based linkable