[Haskell-cafe] Newbie Question: Using Haskell Functions in a C Program

Don Stewart dons at galois.com
Thu May 8 18:33:16 EDT 2008


mail:
> Is there a way to write some of the functions in Haskell and then use 
> them in my C code via some kind of interface?

Using C just for IO is a bit weird -- perhaps you could illustrate
the kind of IO you're doing?  Learning how to do IO in Haskell is 
a much safer solution that linking the Haskell runtime into your
C program.

That said, this is done by using 'foreign export' declarations
in your Haskell code, then linking the compiled Haskell objects 
into your C code, as follows:


We define the fibonacci function in Haskell:


    {-# LANGUAGE ForeignFunctionInterface #-}

    module Safe where

    import Foreign.C.Types

    fibonacci :: Int -> Int
    fibonacci n = fibs !! n
        where fibs = 0 : 1 : zipWith (+) fibs (tail fibs)

    fibonacci_hs :: CInt -> CInt
    fibonacci_hs = fromIntegral . fibonacci . fromIntegral

    foreign export ccall fibonacci_hs :: CInt -> CInt


And call it from C:

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

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

       i = fibonacci_hs(42);
       printf("Fibonacci: %d\n", i);

       hs_exit();
       return 0;
    }

Now, first compile the Haskell file:

    $ ghc -c -O A.hs

Which creates some *.c and *.h headers, which you import into
your C program. Now compile your C code with ghc (!), passing
the Haskell objects on the command line:

    $ ghc -optc-O test.c A.o A_stub.o -o test

How run your C code:

    $ ./test 
    Fibonacci: 267914296

And that's it.

-- Don

P.S. Its easier to learn how to do IO in Haskell :)


More information about the Haskell-Cafe mailing list