Safe Haskell | None |
---|---|
Language | Haskell98 |
An interface to the GHC runtime's dynamic linker, providing runtime loading and linking of Haskell object files, commonly known as plugins.
- data LoadStatus a
- 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 {}
- initLinker :: IO ()
- loadModule :: FilePath -> IO Module
- loadFunction :: Module -> String -> IO (Maybe a)
- loadFunction_ :: String -> String -> IO (Maybe a)
- loadPackageFunction :: String -> 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 Source #
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.
High-level interface
:: FilePath | object file |
-> [FilePath] | any include paths |
-> [PackageConf] | list of package.conf paths |
-> Symbol | symbol 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
:: FilePath | object file |
-> [FilePath] | any include paths |
-> Symbol | symbol to find |
-> 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) Source #
A work-around for Dynamics. The keys used to compare two TypeReps are somehow not equal for the same type in hs-plugin's loaded objects. Solution: implement our own dynamics...
The problem with dynload is that it requires the plugin to export a value that is a Dynamic (in our case a (TypeRep,a) pair). If this is not the case, we core dump. Use pdynload if you don't trust the user to supply you with a Dynamic
:: FilePath | object to load |
-> [FilePath] | include paths |
-> [PackageConf] | package confs |
-> Type | API type |
-> Symbol | symbol |
-> IO (LoadStatus a) |
The super-replacement for dynload
Use GHC at runtime so we get staged type inference, providing full power dynamics, *on module interfaces only*. This is quite suitable for plugins, of coures :)
TODO where does the .hc file go in the call to build() ?
:: FilePath | object to load |
-> [FilePath] | include paths for loading |
-> [PackageConf] | any extra package.conf files |
-> [Arg] | extra arguments to ghc, when typechecking |
-> Type | expected type |
-> Symbol | symbol to load |
-> IO (LoadStatus a) |
Like pdynload, but you can specify extra arguments to the typechecker.
unloadAll :: Module -> IO () Source #
unload a module and its dependencies we have the dependencies, so cascaded unloading is possible
reload :: Module -> Symbol -> IO (LoadStatus a) Source #
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
Low-level interface
initLinker :: IO () Source #
Call the initLinker function first, before calling any of the other functions in this module - otherwise you'll get unresolved symbols.
loadModule :: FilePath -> IO Module Source #
load a single object. no dependencies. You should know what you're doing.
Load a function from a module (which must be loaded and resolved first).
:: String | Package name, including version number. |
-> String | Module name |
-> String | Symbol to lookup in the module |
-> IO (Maybe a) |
Loads a function from a package module, given the package name, module name and symbol name.
loadPackage :: String -> IO () Source #
Load a -package that we might need, implicitly loading the cbits too The argument is the name of package (e.g. "concurrent")
How to find a package is determined by the package.conf info we store in the environment. It is just a matter of looking it up.
Not printing names of dependent pkgs
unloadPackage :: String -> IO () Source #
Unload a -package, that has already been loaded. Unload the cbits too. The argument is the name of the package.
May need to check if it exists.
Note that we currently need to unload everything. grumble grumble.
We need to add the version number to the package name with 6.4 and over. "yi-0.1" for example. This is a bug really.
loadPackageWith :: String -> [PackageConf] -> IO () Source #
load a package using the given package.conf to help TODO should report if it doesn't actually load the package, instead of mapM_ doing nothing like above.
resolveObjs :: IO a -> IO () Source #
Resolve (link) the modules loaded by the loadObject
function.