pdynload-0.0.2: pdynload is polymorphic dynamic linking library.

System.Plugin

Contents

Synopsis

Methods

pdynloadSource

Arguments

:: (String, String)

A tuple (symbolModule, symbol), specifying a symbol in module

symbolModule is a fully-qualified module name, ie "Data.List"

symbol is an unqualified symbol name, ie "reverse".

-> (String, String)

A tuple (typModule, typ), specifying a type in module

typModule is a fully-qualified module name, ie "Prelude" , you can empty this string if type define in Prelude.

typ is an unqualified type name, ie "String -> String".

-> IO (Maybe a)

If the specified symbol is found, Just its value. Otherwise, Nothing.

Polymorphic dynamic loading.

Resolves the specified symbol to any given type. This means linking the package containing it if it is not already linked, extracting the value of that symbol, and returning that value.

Here has simplest demo for test:

 module Main where
 
 import System.Plugin
 import Unsafe.Coerce
 
 main = do
   val <- pdynload ("Prelude", "reverse") ("", "String -> String")
   let str = case val of
               Just v  -> (unsafeCoerce v :: String -> String) "hello"
               Nothing -> "Load failed."
   print str

Because pdynload check type at runtime, so don't afraid unsafeCoerce, it is perfect safety.