plugins-1.0ContentsIndex
System.Plugins.Load
Contents
The LoadStatus type
High-level interface
Low-level interface
Description
An interface to the GHC runtime's dynamic linker, providing runtime loading and linking of Haskell object files, commonly known as plugins.
Synopsis
data LoadStatus a
= LoadSuccess Module a
| LoadFailure Errors
load :: FilePath -> [FilePath] -> [PackageConf] -> Symbol -> IO (LoadStatus a)
load_ :: FilePath -> [FilePath] -> Symbol -> IO (LoadStatus a)
dynload :: Typeable a => FilePath -> [FilePath] -> [PackageConf] -> Symbol -> IO (LoadStatus a)
pdynload :: FilePath -> [FilePath] -> [PackageConf] -> Type -> Symbol -> IO (LoadStatus a)
pdynload_ :: FilePath -> [FilePath] -> [PackageConf] -> [Arg] -> Type -> Symbol -> IO (LoadStatus a)
unload :: Module -> IO ()
unloadAll :: Module -> IO ()
reload :: Module -> Symbol -> IO (LoadStatus a)
data Module = Module {
path :: !FilePath
mname :: !String
kind :: !ObjType
iface :: Iface
key :: Key
}
initLinker :: IO ()
loadModule :: FilePath -> IO Module
loadFunction :: Module -> String -> IO (Maybe a)
loadFunction_ :: String -> String -> IO (Maybe a)
loadPackage :: String -> IO ()
unloadPackage :: String -> IO ()
loadPackageWith :: String -> [PackageConf] -> IO ()
loadShared :: FilePath -> IO Module
resolveObjs :: IO a -> IO ()
loadRawObject :: FilePath -> IO Module
type Symbol = String
getImports :: String -> IO [String]
The LoadStatus type
data LoadStatus a
The LoadStatus type encodes the return status of functions that perform dynamic loading in a type isomorphic to Either. Failure returns a list of error strings, success returns a reference to a loaded module, and the Haskell value corresponding to the symbol that was indexed.
Constructors
LoadSuccess Module a
LoadFailure Errors
High-level interface
load
:: FilePathobject file
-> [FilePath]any include paths
-> [PackageConf]list of package.conf paths
-> Symbolsymbol to find
-> IO (LoadStatus a)

load is the basic interface to the dynamic loader. A call to load imports a single object file into the caller's address space, returning the value associated with the symbol requested. Libraries and modules that the requested module depends upon are loaded and linked in turn.

The first argument is the path to the object file to load, the second argument is a list of directories to search for dependent modules. The third argument is a list of paths to user-defined, but unregistered, package.conf files. The Symbol argument is the symbol name of the value you with to retrieve.

The value returned must be given an explicit type signature, or provided with appropriate type constraints such that Haskell compiler can determine the expected type returned by load, as the return type is notionally polymorphic.

Example:

 do mv <- load "Plugin.o" ["api"] [] "resource"
    case mv of
        LoadFailure msg -> print msg
        LoadSuccess _ v -> return v
load_ :: FilePath -> [FilePath] -> Symbol -> IO (LoadStatus a)
Like load, but doesn't want a package.conf arg (they are rarely used)
dynload :: Typeable a => FilePath -> [FilePath] -> [PackageConf] -> Symbol -> IO (LoadStatus a)
pdynload
:: FilePathobject to load
-> [FilePath]include paths
-> [PackageConf]package confs
-> TypeAPI type
-> Symbolsymbol
-> IO (LoadStatus a)
pdynload_
:: FilePathobject to load
-> [FilePath]include paths for loading
-> [PackageConf]any extra package.conf files
-> [Arg]extra arguments to ghc, when typechecking
-> Typeexpected type
-> Symbolsymbol to load
-> IO (LoadStatus a)
Like pdynload, but you can specify extra arguments to the typechecker.
unload :: Module -> IO ()

unload a module (not its dependencies) we have the dependencies, so cascaded unloading is possible

once you unload it, you can't load it again, you have to reload it. Cause we don't unload all the dependencies

unloadAll :: Module -> IO ()
unload a module and its dependencies we have the dependencies, so cascaded unloading is possible
reload :: Module -> Symbol -> IO (LoadStatus a)

this will be nice for panTHeon, needs thinking about the interface reload a single object file. don't care about depends, assume they are loaded. (should use state to store all this)

assumes you've already done a load

should factor the code

data Module
Constructors
Module
path :: !FilePath
mname :: !String
kind :: !ObjType
iface :: Iface
key :: Key
show/hide Instances
Low-level interface
initLinker :: IO ()
loadModule :: FilePath -> IO Module
loadFunction
:: ModuleThe module the value is in
-> StringSymbol name of value
-> IO (Maybe a)The value you want

Call the initLinker function first, before calling any of the other functions in this module - otherwise you'll get unresolved symbols.

Load a function from a module (which must be loaded and resolved first).

loadFunction_ :: String -> String -> IO (Maybe a)
loadPackage :: String -> IO ()
unloadPackage :: String -> IO ()
loadPackageWith :: String -> [PackageConf] -> IO ()
loadShared :: FilePath -> IO Module

from ghci/ObjLinker.c

Load a .so type object file.

resolveObjs :: IO a -> IO ()
Resolve (link) the modules loaded by the loadObject function.
loadRawObject :: FilePath -> IO Module
Load a generic .o file, good for loading C objects. You should know what you're doing.. Returns a fairly meaningless iface value.
type Symbol = String
getImports :: String -> IO [String]
Produced by Haddock version 0.8