I want to be able to take a simple C program and
access a function from it in Haskell. A simple example

The attachement is a file where the Haskell program first creates the C-source, compiles it to an shared object file, loads the object using the dynamic linker and uses the just constructed function.

Regards,

--
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---
module Main where

import System.Posix.DynamicLinker as DL
import System.Process ( runInteractiveProcess , waitForProcess )
import Foreign.C ( CString , withCString )
import Foreign ( FunPtr )
import Directory ( removeFile )

-------------------------------------------------------------------------------

fun_name = "fun"

mod_contents = 
   unlines 
   [ "#include <string.h>"
   , "#include <stdio.h>"
   , ""
   , "int " , fun_name , " ( int n , char * msg )"
   , "{"
   , "  static int count = 1 ; "
   , "  int l = strlen ( msg ) ;"
   , "  printf ( \"[call %d] %s (%d) - %d\\n\" , count ++ , msg , l , n ) ; "
   , "  return ( l * n ) ; "
   , "}"
   ]

cc = "gcc"
cc_opts = [ "-shared" ,"-fpic" ]
mod_name = "./dl.o"
mod_src = "./dl.c"

create_mod = do 
    writeFile mod_src mod_contents
    (_,_,_,pid) <- 
	runInteractiveProcess cc ( cc_opts ++ [ mod_src , "-o" , mod_name ] )
			         Nothing Nothing
    waitForProcess pid
    removeFile mod_src

remove_mod = removeFile mod_name

with_mod f = create_mod >> f >> remove_mod

-------------------------------------------------------------------------------

type Fun = Int -> CString -> IO Int

foreign import ccall "dynamic" fun__ :: FunPtr Fun -> Fun

-------------------------------------------------------------------------------

use_fun f (msg,n) = withCString msg (f n)

use_once x =
    DL.withDL mod_name [DL.RTLD_NOW] $ \ dl -> do
    fun_ptr <- DL.dlsym dl fun_name
    use_fun (fun__ fun_ptr) x

use_often xs = do
    dl <- DL.dlopen mod_name [DL.RTLD_NOW]
    fun_ptr <- DL.dlsym dl fun_name
    res <- mapM (use_fun (fun__ fun_ptr)) xs
    DL.dlclose dl
    return res

inp = [("Foo",3),("Bar",4),("FooBar",2)]

main = with_mod $ do
       mapM use_once inp >>= print
       use_often inp >>= print

{-
[EMAIL PROTECTED]:~/dl$ ls
DL.hs
[EMAIL PROTECTED]:~/dl$ ghc --make -fffi DL.hs -o DL
[1 of 1] Compiling Main             ( DL.hs, DL.o )
Linking DL ...
[EMAIL PROTECTED]:~/dl$ ./DL
[call 1] Foo (3) - 3
[call 1] Bar (3) - 4
[call 1] FooBar (6) - 2
[9,12,12]
[call 1] Foo (3) - 3
[call 2] Bar (3) - 4
[call 3] FooBar (6) - 2
[9,12,12]
[EMAIL PROTECTED]:~/dl$ ls
DL  DL.hi  DL.hs  DL.o
-}
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to