some progress on the plugin system
This commit is contained in:
parent
c07bc5eda0
commit
cc6c634c82
@ -1,15 +1,23 @@
|
||||
{-# LANGUAGE MagicHash #-}
|
||||
{-# LANGUAGE UnboxedTuples #-}
|
||||
|
||||
module IRC.Plugins.Loader where
|
||||
module IRC.Plugins.Loader ( load ) where
|
||||
|
||||
import GHC.Exts ( addrToAny# )
|
||||
import GHC.Ptr ( Ptr(..) )
|
||||
import System.Info ( os, arch )
|
||||
import qualified Data.HashMap.Lazy as M
|
||||
|
||||
import Control.Exception ( catch, ErrorCall )
|
||||
import GHC.Exts ( addrToAny# )
|
||||
import GHC.Ptr ( Ptr(..) )
|
||||
import System.Info ( os, arch )
|
||||
import GHCi.ObjLink
|
||||
import Encoding
|
||||
|
||||
load :: IO (Either String (IO ()))
|
||||
type PluginSet = M.HashMap String Plugin
|
||||
|
||||
data Plugin = Plugin { wew :: Int,
|
||||
lad :: Int }
|
||||
|
||||
load :: PluginSet -> IO (Either String (IO PluginSet))
|
||||
load = do initObjLinker RetainCAFs
|
||||
loadObj "Plugin.o"
|
||||
_ret <- resolveObjs
|
||||
@ -19,6 +27,12 @@ load = do initObjLinker RetainCAFs
|
||||
Just (Ptr addr) -> case addrToAny# addr of
|
||||
(# f #) -> return $ Right f
|
||||
|
||||
unload :: String -> IO PluginSet
|
||||
unload plugin = catch (unloadObj $ plugin <> ".o") exceptionHandler
|
||||
|
||||
exceptionHandler :: ErrorCall -> IO PluginSet
|
||||
exceptionHandler _ = return ()
|
||||
|
||||
mangleSymbol :: Maybe String -> String -> String -> String
|
||||
mangleSymbol pkg module' valsym =
|
||||
prefixUnderscore <>
|
||||
|
Loading…
Reference in New Issue
Block a user