| Safe Haskell | None |
|---|---|
| Language | GHC2024 |
GHC.Linker.Types
Contents
Synopsis
- newtype Loader = Loader {
- loader_state :: MVar (Maybe LoaderState)
- data LoaderState = LoaderState {
- bco_loader_state :: !BytecodeLoaderState
- bcos_loaded :: !LinkableSet
- objs_loaded :: !LinkableSet
- pkgs_loaded :: !PkgsLoaded
- temp_sos :: ![(FilePath, String)]
- uninitializedLoader :: IO Loader
- data BytecodeLoaderState = BytecodeLoaderState {}
- data BytecodeState = BytecodeState {}
- emptyBytecodeLoaderState :: BytecodeLoaderState
- emptyBytecodeState :: BytecodeState
- modifyHomePackageBytecodeState :: BytecodeLoaderState -> (BytecodeState -> BytecodeState) -> BytecodeLoaderState
- modifyExternalPackageBytecodeState :: BytecodeLoaderState -> (BytecodeState -> BytecodeState) -> BytecodeLoaderState
- modifyBytecodeLoaderState :: BytecodeLoaderStateModifier -> LoaderState -> (BytecodeState -> BytecodeState) -> LoaderState
- lookupNameBytecodeState :: BytecodeLoaderState -> Name -> Maybe (Name, ForeignHValue)
- lookupBreakArrayBytecodeState :: BytecodeLoaderState -> Module -> Maybe (ForeignRef BreakArray)
- lookupInfoTableBytecodeState :: BytecodeLoaderState -> Name -> Maybe (Name, ItblPtr)
- lookupAddressBytecodeState :: BytecodeLoaderState -> Name -> Maybe (Name, AddrPtr)
- lookupCCSBytecodeState :: BytecodeLoaderState -> Module -> Maybe (Array BreakTickIndex (RemotePtr CostCentre))
- type BytecodeLoaderStateModifier = BytecodeLoaderState -> (BytecodeState -> BytecodeState) -> BytecodeLoaderState
- type BytecodeLoaderStateTraverser (m :: Type -> Type) = BytecodeLoaderState -> (BytecodeState -> m BytecodeState) -> m BytecodeLoaderState
- traverseHomePackageBytecodeState :: Monad m => BytecodeLoaderState -> (BytecodeState -> m BytecodeState) -> m BytecodeLoaderState
- traverseExternalPackageBytecodeState :: Monad m => BytecodeLoaderState -> (BytecodeState -> m BytecodeState) -> m BytecodeLoaderState
- modifyClosureEnv :: BytecodeState -> (ClosureEnv -> ClosureEnv) -> BytecodeState
- data LinkerEnv = LinkerEnv {
- closure_env :: !ClosureEnv
- itbl_env :: !ItblEnv
- addr_env :: !AddrEnv
- emptyLinkerEnv :: LinkerEnv
- type ClosureEnv = NameEnv (Name, ForeignHValue)
- emptyClosureEnv :: ClosureEnv
- extendClosureEnv :: ClosureEnv -> [(Name, ForeignHValue)] -> ClosureEnv
- data LinkedBreaks = LinkedBreaks {
- breakarray_env :: !(ModuleEnv (ForeignRef BreakArray))
- ccs_env :: !(ModuleEnv (Array BreakTickIndex (RemotePtr CostCentre)))
- emptyLinkedBreaks :: LinkedBreaks
- type LinkableSet = ModuleEnv Linkable
- mkLinkableSet :: [Linkable] -> LinkableSet
- unionLinkableSet :: LinkableSet -> LinkableSet -> LinkableSet
- type ObjFile = FilePath
- data SptEntry = SptEntry !Name !Fingerprint
- data LibrarySpec
- data LoadedPkgInfo = LoadedPkgInfo {}
- type PkgsLoaded = UniqDFM UnitId LoadedPkgInfo
- type Linkable = LinkableWith (NonEmpty LinkablePart)
- type WholeCoreBindingsLinkable = LinkableWith WholeCoreBindings
- data LinkableWith parts = Linkable {
- linkableTime :: !UTCTime
- linkableModule :: !Module
- linkableParts :: parts
- mkModuleByteCodeLinkable :: UTCTime -> ModuleByteCode -> Linkable
- data LinkablePart
- data LinkableObjectSort
- linkableIsNativeCodeOnly :: Linkable -> Bool
- linkableObjs :: Linkable -> [FilePath]
- linkableLibs :: Linkable -> [LinkablePart]
- linkableFiles :: Linkable -> [FilePath]
- linkableBCOs :: Linkable -> [CompiledByteCode]
- linkablePartBCOs :: LinkablePart -> [CompiledByteCode]
- linkableModuleByteCodes :: Linkable -> [ModuleByteCode]
- linkableNativeParts :: Linkable -> [LinkablePart]
- linkablePartitionParts :: Linkable -> ([LinkablePart], [LinkablePart])
- linkablePartPath :: LinkablePart -> Maybe FilePath
- isNativeCode :: LinkablePart -> Bool
- isNativeLib :: LinkablePart -> Bool
- linkableFilterByteCode :: Linkable -> Maybe Linkable
- linkableFilterNative :: Linkable -> Maybe Linkable
- partitionLinkables :: [Linkable] -> ([Linkable], [Linkable])
- data ModuleByteCode = ModuleByteCode {}
Documentation
Constructors
| Loader | |
Fields
| |
data LoaderState Source #
Constructors
| LoaderState | |
Fields
| |
Bytecode Loader State
data BytecodeLoaderState Source #
The BytecodeLoaderState captures all the information about bytecode loaded
into the interpreter.
It is separated into two parts. One for bytecode objects loaded by the home package and
one for bytecode objects loaded from bytecode libraries for external packages.
Much like the HPT/EPS split, the home package state can be unloaded by calling unload.
Constructors
| BytecodeLoaderState | |
Fields
| |
data BytecodeState Source #
Constructors
| BytecodeState | |
Fields
| |
modifyHomePackageBytecodeState :: BytecodeLoaderState -> (BytecodeState -> BytecodeState) -> BytecodeLoaderState Source #
Only update the home package bytecode state.
modifyExternalPackageBytecodeState :: BytecodeLoaderState -> (BytecodeState -> BytecodeState) -> BytecodeLoaderState Source #
Only update the external package bytecode state.
modifyBytecodeLoaderState :: BytecodeLoaderStateModifier -> LoaderState -> (BytecodeState -> BytecodeState) -> LoaderState Source #
lookupNameBytecodeState :: BytecodeLoaderState -> Name -> Maybe (Name, ForeignHValue) Source #
Find a name loaded from bytecode
lookupBreakArrayBytecodeState :: BytecodeLoaderState -> Module -> Maybe (ForeignRef BreakArray) Source #
Look up a break array in the bytecode loader state.
lookupInfoTableBytecodeState :: BytecodeLoaderState -> Name -> Maybe (Name, ItblPtr) Source #
Look up an info table in the bytecode loader state.
lookupAddressBytecodeState :: BytecodeLoaderState -> Name -> Maybe (Name, AddrPtr) Source #
Look up an address in the bytecode loader state.
lookupCCSBytecodeState :: BytecodeLoaderState -> Module -> Maybe (Array BreakTickIndex (RemotePtr CostCentre)) Source #
Look up a cost centre stack in the bytecode loader state.
type BytecodeLoaderStateModifier = BytecodeLoaderState -> (BytecodeState -> BytecodeState) -> BytecodeLoaderState Source #
type BytecodeLoaderStateTraverser (m :: Type -> Type) = BytecodeLoaderState -> (BytecodeState -> m BytecodeState) -> m BytecodeLoaderState Source #
traverseHomePackageBytecodeState :: Monad m => BytecodeLoaderState -> (BytecodeState -> m BytecodeState) -> m BytecodeLoaderState Source #
Effectfully update the home package bytecode state.
traverseExternalPackageBytecodeState :: Monad m => BytecodeLoaderState -> (BytecodeState -> m BytecodeState) -> m BytecodeLoaderState Source #
Effectfully update the external package bytecode state.
modifyClosureEnv :: BytecodeState -> (ClosureEnv -> ClosureEnv) -> BytecodeState Source #
Information about loaded bytecode
Constructors
| LinkerEnv | |
Fields
| |
type ClosureEnv = NameEnv (Name, ForeignHValue) Source #
extendClosureEnv :: ClosureEnv -> [(Name, ForeignHValue)] -> ClosureEnv Source #
data LinkedBreaks Source #
BreakArrays and CCSs are allocated per-module at link-time.
Specifically, a module's BreakArray is allocated either:
- When a BCO for that module is linked
- When :break is used on a given module *before* the BCO has been linked.
We keep this structure in the LoaderState
Constructors
| LinkedBreaks | |
Fields
| |
type LinkableSet = ModuleEnv Linkable Source #
mkLinkableSet :: [Linkable] -> LinkableSet Source #
unionLinkableSet :: LinkableSet -> LinkableSet -> LinkableSet Source #
Union of LinkableSets.
In case of conflict, keep the most recent Linkable (as per linkableTime)
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 !Name !Fingerprint |
data LibrarySpec Source #
Constructors
| Objects [FilePath] | |
| Archive FilePath | |
| DLL String | |
| DLLPath FilePath | |
| Framework String | |
| BytecodeLibrary FilePath | A bytecode library file (.bytecodelib) |
Instances
| Outputable LibrarySpec Source # | |
Defined in GHC.Linker.Types Methods ppr :: LibrarySpec -> SDoc Source # | |
data LoadedPkgInfo Source #
Constructors
| LoadedPkgInfo | |
Fields
| |
Instances
| Outputable LoadedPkgInfo Source # | |
Defined in GHC.Linker.Types Methods ppr :: LoadedPkgInfo -> SDoc Source # | |
type PkgsLoaded = UniqDFM UnitId LoadedPkgInfo Source #
Linkable
type Linkable = LinkableWith (NonEmpty LinkablePart) Source #
data LinkableWith parts Source #
Information we can use to dynamically link modules into the compiler
Constructors
| Linkable | |
Fields
| |
Instances
data LinkablePart Source #
Objects which have yet to be linked by the compiler
Constructors
| DotO | |
Fields
| |
| DotA FilePath | Static archive file (.a) |
| DotDLL FilePath | Dynamically linked library file (.so, .dll, .dylib) |
| DotGBC ModuleByteCode | A byte-code object, lives only in memory. |
Instances
| Outputable LinkablePart Source # | |
Defined in GHC.Linker.Types Methods ppr :: LinkablePart -> SDoc Source # | |
data LinkableObjectSort Source #
Classify the provenance of .o products.
Constructors
| ModuleObject | The object is the final product for a module. When linking splices, its file extension will be adapted to the interpreter's way if needed. |
| ForeignObject | The object was created from generated code for foreign stubs or foreign sources added by the user. Its file extension must be preserved, since there are no objects for alternative ways available. |
linkableIsNativeCodeOnly :: Linkable -> Bool Source #
Return true if the linkable only consists of native code (no BCO)
linkableObjs :: Linkable -> [FilePath] Source #
List the native objects (.o) of a linkable
linkableLibs :: Linkable -> [LinkablePart] Source #
List the native libraries (.so/.dll) of a linkable
linkableFiles :: Linkable -> [FilePath] Source #
List the paths of the native objects and libraries (.o.so.dll)
linkableBCOs :: Linkable -> [CompiledByteCode] Source #
List the BCOs parts of a linkable.
This excludes the CoreBindings parts
linkablePartBCOs :: LinkablePart -> [CompiledByteCode] Source #
Retrieve the compiled byte-code from the linkable part.
Contrary to linkableBCOs, this includes byte-code from LazyBCOs.
linkableNativeParts :: Linkable -> [LinkablePart] Source #
List the native linkable parts (.o.so.dll) of a linkable
linkablePartitionParts :: Linkable -> ([LinkablePart], [LinkablePart]) Source #
Split linkable parts into (native code parts, BCOs parts)
linkablePartPath :: LinkablePart -> Maybe FilePath Source #
Get the FilePath of linkable part (if applicable)
isNativeCode :: LinkablePart -> Bool Source #
Is the part a native object or library? (.o.so.dll)
isNativeLib :: LinkablePart -> Bool Source #
Is the part a native library? (.so/.dll)
linkableFilterByteCode :: Linkable -> Maybe Linkable Source #
Transform the LinkablePart list in this Linkable to contain only byte
code
If no LinkablePart remains, return Nothing.
linkableFilterNative :: Linkable -> Maybe Linkable Source #
Transform the LinkablePart list in this Linkable to contain only
object code files (.o, .a, .so) without BCOs.
If no LinkablePart remains, return Nothing.
partitionLinkables :: [Linkable] -> ([Linkable], [Linkable]) Source #
Split the LinkablePart lists in each Linkable into only object code
files (.o, .a, .so) and only byte code, and return two
lists containing the nonempty Linkables for each.
data ModuleByteCode Source #
The in-memory representation of a bytecode object These are stored on-disk as .gbc files.
Constructors
| ModuleByteCode | |
Fields
| |
Instances
| Outputable ModuleByteCode Source # | |
Defined in GHC.Linker.Types Methods ppr :: ModuleByteCode -> SDoc Source # | |