FFI Tutorial / Examples

Daan Leijen daanleijen@xs4all.nl
Mon, 10 Mar 2003 09:11:31 +0100


On Sun, 09 Mar 2003 22:13:35 -0500, Matthew Donadio <m.p.donadio@ieee.org> wrote:

> I may be being a bit dense about this, but I am having some trouble
> understanding how to use FFI, especially with respect to interfacing
> Haskell lists/arrays to C arrays.
>
> For example, say I have the C functions
>
> void foo (double *input, double *output, int N);

Hi Donadio,

I do this from the top of my head, but it should get you started.
The easiest way to marshal this is to use lists:

foo :: [Double] -> [Double]
foo xs  = unsafePerformIO (fooIO xs)

fooIO :: [Double] -> IO [Double]
fooIO []
  = return []		         -- I guess a null array is not supported in foo?
fooIO xs
  = withArray xs $ \cxs ->       -- array of the list (auto deallocated)
    allocaArray n $ \cys ->      -- fresh array of size n (auto deallocated)
    do fooC cxs cys n            -- call "foo" in C land
       peekArray n cys           -- unmarshal the values in cys back to a list of doubles
  where
    n = length xs

foreign import ccall "foo" fooC :: Ptr Double -> Ptr Double -> Int -> IO ()


If you really want to use Array's, you can convert the lists to arrays
in "foo". Note though that it almost never pays to use Array's in Haskell
unless you really need random access (which is rarely needed in practice).

Hope this helps,
  -- Daan.


btw. If you have the header file of the "foo", you should include it. Say:

  foreign import ccall "Foo.h foo" fooC :: Ptr Double -> Ptr Double -> Int -> IO ()

and use on top of the Haskell file:

  {-# OPTIONS -fvia-C -#include Foo.h #-}

This will check your foreign import signature against the C declaration.

(of course, we should update H/Direct to GHC 5.04 and let it work
better with C header files, and none of this would be needed --
but life is never perfect :-)