ghc-6.12.2: The GHC APISource codeContentsIndex
Linker
Description

The dynamic linker for GHCi.

This module deals with the top-level issues of dynamic linking, calling the object-code linker and the byte-code linker where necessary.

Synopsis
data HValue
getHValue :: HscEnv -> Name -> IO HValue
showLinkerState :: IO ()
linkExpr :: HscEnv -> SrcSpan -> UnlinkedBCO -> IO HValue
unload :: DynFlags -> [Linkable] -> IO ()
withExtendedLinkEnv :: (MonadIO m, ExceptionMonad m) => [(Name, HValue)] -> m a -> m a
extendLinkEnv :: [(Name, HValue)] -> IO ()
deleteFromLinkEnv :: [Name] -> IO ()
extendLoadedPkgs :: [PackageId] -> IO ()
linkPackages :: DynFlags -> [PackageId] -> IO ()
initDynLinker :: DynFlags -> IO ()
dataConInfoPtrToName :: Ptr () -> TcM (Either String Name)
Documentation
data HValue Source
getHValue :: HscEnv -> Name -> IO HValueSource

Get the HValue associated with the given name.

May cause loading the module that contains the name.

Throws a ProgramError if loading fails or the name cannot be found.

showLinkerState :: IO ()Source
Display the persistent linker state.
linkExpr :: HscEnv -> SrcSpan -> UnlinkedBCO -> IO HValueSource

Link a single expression, including first linking packages and modules that this expression depends on.

Raises an IO exception (ProgramError) if it can't find a compiled version of the dependents to link.

unloadSource
:: DynFlags
-> [Linkable]The linkables to *keep*.
-> IO ()

Unloading old objects ready for a new compilation sweep.

The compilation manager provides us with a list of linkables that it considers "stable", i.e. won't be recompiled this time around. For each of the modules current linked in memory,

  • if the linkable is stable (and it's the same one -- the user may have recompiled the module on the side), we keep it,
  • otherwise, we unload it.
  • we also implicitly unload all temporary bindings at this point.
withExtendedLinkEnv :: (MonadIO m, ExceptionMonad m) => [(Name, HValue)] -> m a -> m aSource
Temporarily extend the linker state.
extendLinkEnv :: [(Name, HValue)] -> IO ()Source
deleteFromLinkEnv :: [Name] -> IO ()Source
extendLoadedPkgs :: [PackageId] -> IO ()Source
linkPackages :: DynFlags -> [PackageId] -> IO ()Source
Link exactly the specified packages, and their dependents (unless of course they are already linked). The dependents are linked automatically, and it doesn't matter what order you specify the input packages.
initDynLinker :: DynFlags -> IO ()Source

Initialise the dynamic linker. This entails

a) Calling the C initialisation procedure,

b) Loading any packages specified on the command line,

c) Loading any packages specified on the command line, now held in the -l options in v_Opt_l,

d) Loading any .o/.dll files specified on the command line, now held in v_Ld_inputs,

e) Loading any MacOS frameworks.

NOTE: This function is idempotent; if called more than once, it does nothing. This is useful in Template Haskell, where we call it before trying to link.

dataConInfoPtrToName :: Ptr () -> TcM (Either String Name)Source

Given a data constructor in the heap, find its Name. The info tables for data constructors have a field which records the source name of the constructor as a Ptr Word8 (UTF-8 encoded string). The format is:

 Package:Module.Name

We use this string to lookup the interpreter's internal representation of the name using the lookupOrig.

Produced by Haddock version 2.6.1