dynamic loading with ghc api?

Hi all, I'd like to load a value from a .o file. I've got... import ObjLink main = do initObjLinker loadObj "Thing.o" resolveObjs Just ptr <- lookupSymbol "Thing_value_closure" Is that the correct symbol to load for the name "value" in module "Thing"? And if so, how to I get the haskell value out of the Ptr that I get from lookupSymbol? I found some code to do it and it works value :: Int, but it seg faults if value :: Integer, or something more complex like a function. {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} ... let !(Ptr addr) = ptr in case addrToHValue# addr of (# hval #) -> hval Is there some documentation for this that I'm missing? I'm looking at haddock with just type signatures, like this: http://www.haskell.org/ghc/docs/7.0.3/html/libraries/ghc-7.0.3/ObjLink.html (I'm a haskell beginner.) thank you, Rob

Perhaps look at the plugins package source?
-- Don
On Thu, Apr 7, 2011 at 12:20 PM, Rob Nikander
Hi all,
I'd like to load a value from a .o file. I've got...
import ObjLink main = do initObjLinker loadObj "Thing.o" resolveObjs Just ptr <- lookupSymbol "Thing_value_closure"
Is that the correct symbol to load for the name "value" in module "Thing"? And if so, how to I get the haskell value out of the Ptr that I get from lookupSymbol? I found some code to do it and it works value :: Int, but it seg faults if value :: Integer, or something more complex like a function.
{-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} ... let !(Ptr addr) = ptr in case addrToHValue# addr of (# hval #) -> hval
Is there some documentation for this that I'm missing? I'm looking at haddock with just type signatures, like this:
http://www.haskell.org/ghc/docs/7.0.3/html/libraries/ghc-7.0.3/ObjLink.html
(I'm a haskell beginner.)
thank you, Rob
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Is the 'plugins' package compatible with dynamic linking of the main
program? I ask because I wrote a test program using
System.Plugins.load and it works fine, but when I link it to the GHC
api using `ghc -dynamic ...' (which is nice cause it avoids the 50 MB
executable), it seg faults when it tries to call the function that it
loaded from the .o file. Maybe I need to compile the .o with
something more than `ghc -c MyPlugin.hs'?
Rob
On Thu, Apr 7, 2011 at 3:35 PM, Don Stewart
Perhaps look at the plugins package source?
-- Don
On Thu, Apr 7, 2011 at 12:20 PM, Rob Nikander
wrote: Hi all,
I'd like to load a value from a .o file. I've got...
import ObjLink main = do initObjLinker loadObj "Thing.o" resolveObjs Just ptr <- lookupSymbol "Thing_value_closure"
Is that the correct symbol to load for the name "value" in module "Thing"? And if so, how to I get the haskell value out of the Ptr that I get from lookupSymbol? I found some code to do it and it works value :: Int, but it seg faults if value :: Integer, or something more complex like a function.
{-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} ... let !(Ptr addr) = ptr in case addrToHValue# addr of (# hval #) -> hval
Is there some documentation for this that I'm missing? I'm looking at haddock with just type signatures, like this:
http://www.haskell.org/ghc/docs/7.0.3/html/libraries/ghc-7.0.3/ObjLink.html
(I'm a haskell beginner.)
thank you, Rob
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Using plugins with dynamic Haskell objects hasn't been tested in quite a while.
-- Don
On Thu, Apr 7, 2011 at 5:14 PM, Rob Nikander
Is the 'plugins' package compatible with dynamic linking of the main program? I ask because I wrote a test program using System.Plugins.load and it works fine, but when I link it to the GHC api using `ghc -dynamic ...' (which is nice cause it avoids the 50 MB executable), it seg faults when it tries to call the function that it loaded from the .o file. Maybe I need to compile the .o with something more than `ghc -c MyPlugin.hs'?
Rob
On Thu, Apr 7, 2011 at 3:35 PM, Don Stewart
wrote: Perhaps look at the plugins package source?
-- Don
On Thu, Apr 7, 2011 at 12:20 PM, Rob Nikander
wrote: Hi all,
I'd like to load a value from a .o file. I've got...
import ObjLink main = do initObjLinker loadObj "Thing.o" resolveObjs Just ptr <- lookupSymbol "Thing_value_closure"
Is that the correct symbol to load for the name "value" in module "Thing"? And if so, how to I get the haskell value out of the Ptr that I get from lookupSymbol? I found some code to do it and it works value :: Int, but it seg faults if value :: Integer, or something more complex like a function.
{-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} ... let !(Ptr addr) = ptr in case addrToHValue# addr of (# hval #) -> hval
Is there some documentation for this that I'm missing? I'm looking at haddock with just type signatures, like this:
http://www.haskell.org/ghc/docs/7.0.3/html/libraries/ghc-7.0.3/ObjLink.html
(I'm a haskell beginner.)
thank you, Rob
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
participants (2)
-
Don Stewart
-
Rob Nikander