[Haskell-cafe] help with FFI

José Prous hiena03 at gmail.com
Thu Sep 17 19:10:51 EDT 2009


Hello

Lets say I have a library in C with a header like this:

#include <stdio.h>

/*really big structure*/
typedef struct {
int *a;
int *b;
/*lots of stuff
...
*/
int *z;
} foo;

/*this function allocate memory and fill the structure, reading from a
file*/
int create_foo(foo *f,FILE *file,int x,int y);

/*some functions that use the structure*/
int use_foo(foo *f,int w);

/*a funtion that releases the memory*/
int destroy_foo(foo *f);

And I want to use it in haskell using FFI. I can create a .hsc file like
this:

{-# LANGUAGE CPP, ForeignFunctionInterface #-}

import Foreign
import Foreign.C.Types

#include "foo.h"

newtype Foo = Foo ()

foreign import ccall "static foo.h create_foo"
c_create_foo :: Ptr (Foo) -> Ptr (CFile) -> CInt -> CInt -> IO CInt

foreign import ccall "static foo.h use_foo"
c_use_foo :: Ptr (Foo) -> CInt -> IO CInt

foreign import ccall "static foo.h destroy_foo"
c_destroy_foo :: Ptr (Foo) -> IO CInt

It compiles but I have no idea how to call c_create_foo and get back Foo
Any suggestions?

thanks
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090917/88a9333a/attachment.html


More information about the Haskell-Cafe mailing list