Runtime importing of modules in GHC

Andre Pang ozone@algorithm.com.au
Mon, 27 May 2002 16:31:02 +1000


Hi all,

Manuel Chakravarty has helped me[1] with getting runtime
importing of modules (a.k.a. dynamic loading) working in GHC on
Linux.  It should work on Windows, too.

The concept: You want to have the equivalent of dlopen(); i.e. be
able to tell the Haskell runtime system to import a module and
call functions in that module.  As an example, say there's
a function called adder:

    module Adder1 where

    adder n = n + 2

which you want to call from another module, called, erm, "Main":

    module Main where

    main = do
             -- somehow import the Adder module
	     let foo = adder 5
	     putStr (show foo ++ "\n") -- should print out 7

We've managed to get the concept working, and the actual code
isn't all that complex.

We compile the Linker.lhs file (from the compiler/ghci/ directory
in the GHC source) so that we can get access to the functions in
the Haskell Runtime System's linker.  Then you can utilise the
FFI to runtime-import the module that you want.

Here's some example code (sorry to make this email so long):

    Adder1.hs:

	module Adder1 where

	foreign export adder :: (Int -> Int)

	adder n = n + 2

    Adder2.hs:

	module Adder2 where

	foreign export adder :: (Int -> Int)

	adder n = n + 3

    Main.hs:

	module Main where

	import Linker
	import Foreign
	import Maybe
	import System

	foreign import dynamic dynCallIntInt :: Ptr (Int -> Int) -> (Int -> Int)

	main :: IO ()
	main = do
		  -- initialise the runtime system linker
		  initLinker

		  -- Need to load these module so that resolveObjs later doesn't complain
		  loadObj "/usr/lib/ghc-5.02.2/HSstd.o"
		  loadObj "/usr/lib/ghc-5.02.2/HSstd_cbits.o"
		  
		  -- Load the module which we really want to load
		  argv <- getArgs
		  moduleName <- case argv of
		    [args] -> return args
		    _ -> do 
		      putStrLn "usage: ./a.out Foo,"
		      putStrLn "  where Foo is the module name which contains the adder function"
		      exitWith (ExitFailure 1)

		  loadObj (moduleName ++ ".o")
		  loadObj (moduleName ++ "_stub.o")
		  putStr ("Loaded " ++ moduleName ++ "\n")
		  
		  -- Tell the linker to resolve the symbols in the newly-loaded object file
		  resolvedObjs <- resolveObjs
		  putStr ("Resolved Object Symbols: " ++ show resolvedObjs ++ "\n")
		  
		  -- Look up the function name we want to call
		  foundSymbol <- lookupSymbol "adder"
		  let justFoundSymbol = fromJust foundSymbol
		  
		  -- Call the function with appropriate parameters
		  let result = dynCallIntInt justFoundSymbol 6
		  putStr (show result ++ "\n")
		  
		  -- Finished!
		  putStr "Yay!\n"

.. and the demonstration:

    16:25(0) .../project/runtime_import% make
    ghc -fglasgow-exts -package lang -c `ghc --print-libdir`/HSrts.o Linker.lhs
    ghc -fglasgow-exts -package lang -c `ghc --print-libdir`/HSrts.o Adder1.hs
    ghc -fglasgow-exts -package lang -c `ghc --print-libdir`/HSrts.o Adder2.hs
    ghc -ldl -package lang -fglasgow-exts -fvia-c Main.hs Linker.o
    nice make  6.29s user 0.65s system 94% cpu 7.359 total
    16:25(0) .../project/runtime_import% ./a.out Adder1 
    Loaded Adder1
    Resolved Object Symbols: True
    8
    Yay!
    16:25(0) .../project/runtime_import% ./a.out Adder2
    Loaded Adder2
    Resolved Object Symbols: True
    9
    Yay!
    16:25(0) .../project/runtime_import% 

So it looks like it all works nicely :).

The sample code's available at:

    http://www.algorithm.com.au/hacking/haskell/

if anybody wants to take a look at it.


1. Okay, he had about 95% of the insight, and I managed to piece
   the other 5% together :)


-- 
#ozone/algorithm <ozone@algorithm.com.au>          - trust.in.love.to.save