8.5. Using the FFI with GHC

The following sections also give some hints and tips on the use of the foreign function interface in GHC.

8.5.1. Using foreign export with GHC

When GHC compiles a module (say M.hs) which uses foreign export or foreign export dynamic, it generates two additional files, M_stub.c and M_stub.h. GHC will automatically compile M_stub.c to generate M_stub.o at the same time.

For a plain foreign export, the file M_stub.h contains a C prototype for the foreign exported function, and M_stub.c contains its definition. For example, if we compile the following module:

module Foo where

foreign export foo :: Int -> IO Int

foo :: Int -> IO Int
foo n = return (length (f n))

f :: Int -> [Int]
f 0 = []
f n = n:(f (n-1))

Then Foo_stub.h will contain something like this:

#include "HsFFI.h"
extern HsInt foo(HsInt a0);

and Foo_stub.c contains the compiler-generated definition of foo(). To invoke foo() from C, just #include "Foo_stub.h" and call foo().

8.5.1.1. Using your own main()

Normally, GHC's runtime system provides a main(), which arranges to invoke Main.main in the Haskell program. However, you might want to link some Haskell code into a program which has a main function written in another languagem, say C. In order to do this, you have to initialize the Haskell runtime system explicitly.

Let's take the example from above, and invoke it from a standalone C program. Here's the C code:

#include <stdio.h>
#include "foo_stub.h"

#include "RtsAPI.h"

extern void __stginit_Foo ( void );

int main(int argc, char *argv[])
{
  int i;

  startupHaskell(argc, argv, __stginit_Foo);

  for (i = 0; i < 5; i++) {
    printf("%d\n", foo(2500));
  }

  shutdownHaskell();

  return 0;
}

The call to startupHaskell() initializes GHC's runtime system. Do NOT try to invoke any Haskell functions before calling startupHaskell(): strange things will undoubtedly happen.

We pass argc and argv to startupHaskell() so that it can separate out any arguments for the RTS (i.e. those arguments between +RTS...-RTS).

The third argument to startupHaskell() is used for initializing the Haskell modules in the program. It must be the name of the initialization function for the "top" module in the program/library - in other words, the module which directly or indirectly imports all the other Haskell modules in the program. In a standalone Haskell program this would be module Main, but when you are only using the Haskell code as a library it may not be. If your library doesn't have such a module, then it is straightforward to create one, purely for this initialization process. The name of the initialization function for module M is __stginit_M, and it may be declared as an external function symbol as in the code above.

After we've finished invoking our Haskell functions, we can call shutdownHaskell(), which terminates the RTS. It runs any outstanding finalizers and generates any profiling or stats output that might have been requested.

The functions startupHaskell() and shutdownHaskell() may be called only once each, and only in that order.

8.5.1.2. Using foreign export dynamic with GHC

When foreign export dynamic is used in a Haskell module, The C stub file M_stub.c generated by GHC contains small helper functions used by the code generated for the foreign export dynamic, so it must be linked in to the final program. When linking the program, remember to include M_stub.o in the final link command line, or you'll get link errors for the missing function(s) (this isn't necessary when building your program with ghc --make, as GHC will automatically link in the correct bits).

8.5.2. Using function headers

When generating C (using the -fvia-C directive), one can assist the C compiler in detecting type errors by using the -#include directive (Section 4.12.4) to provide .h files containing function headers.

For example,

#include "HsFFI.h"

void         initialiseEFS (HsInt size);
HsInt        terminateEFS (void);
HsForeignObj emptyEFS(void);
HsForeignObj updateEFS (HsForeignObj a, HsInt i, HsInt x);
HsInt        lookupEFS (HsForeignObj a, HsInt i);

The types HsInt, HsForeignObj etc. are described in Table 8-1.

Note that this approach is only essential for returning floats (or if sizeof(int) != sizeof(int *) on your architecture) but is a Good Thing for anyone who cares about writing solid code. You're crazy not to do it.