
Hi, I have a blogpost which demonstrates this https://purelyfunctional.org/posts/2016-05-20-dynamic-loading-haskell-module... Basically you need to unwrap the address and then use addrToAny. Obviously this is not typesafe so use it carefully. Cheers, Moritz On 07/27/2017 04:20 PM, Saurabh Nanda wrote:
Hi,
I'm playing around with https://www.stackage.org/haddock/lts-9.0/ghci-8.0.2/GHCi-ObjLink.html to see if I can come up with some sort of hot-loading/plugin system in Haskell.
I've managed to load a shared object (compiled from a Haskell source via -rdynamic) with the following code:
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE MagicHash, UnboxedTuples #-}
module Main where
import GHC.Exts ( addrToAny# ) import GHC.Ptr ( Ptr(..) ) import System.Info ( os, arch ) import Encoding import GHCi.ObjLink import Debug.Trace
main :: IO () main = do traceM "before initObjLinker" initObjLinker traceM "before loadObj" loadObj "/Users/saurabhnanda/projects/test-plugins/test-plugins/app/PluginMarkup.o" traceM "after loadObj"
-- NOTE: I've hardcoded the symbol name that I obtained from running `symbols PluginMarkup.o` sym <- lookupSymbol "PluginMarkup_foliage_info" traceM "after lookupsymbol" traceM (show sym)
I'm getting the following output, which mean that I'm probably getting the Ptr to the function.
before initObjLinker before loadObj after loadObj after lookupsymbol Just 0x0000000104be49a8
Question is, how do I run the function in the same Haskell environment/runtime? The underlying function is actually `foliage :: UtcTime -> Html`
The code is available at https://github.com/vacationlabs/hint-test/blob/dll/app/Main.hs and the DLL is available at https://github.com/vacationlabs/hint-test/blob/dll/app/PluginMarkup.o
-- Saurabh.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.