dynamic loading with ghc api?

Rob Nikander rob.nikander at gmail.com
Thu Apr 7 21:20:08 CEST 2011


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



More information about the Glasgow-haskell-users mailing list