Difference between revisions of "Calling Haskell from C"

From HaskellWiki
Jump to navigation Jump to search
(fix filenames; one more standard #include; update to a GHC need (hs_add_root); another compile command)
(2 intermediate revisions by 2 users not shown)
Line 5: Line 5:
   
 
<haskell>
 
<haskell>
{-# LANGUAGE ForeignFunctionInterface #-}
+
{-# LANGUAGE ForeignFunctionInterface #-}
   
module Safe where
+
module Safe where
   
import Foreign.C.Types
+
import Foreign.C.Types
   
fibonacci :: Int -> Int
+
fibonacci :: Int -> Int
fibonacci n = fibs !! n
+
fibonacci n = fibs !! n
where fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
+
where fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
   
fibonacci_hs :: CInt -> CInt
+
fibonacci_hs :: CInt -> CInt
fibonacci_hs = fromIntegral . fibonacci . fromIntegral
+
fibonacci_hs = fromIntegral . fibonacci . fromIntegral
   
foreign export ccall fibonacci_hs :: CInt -> CInt
+
foreign export ccall fibonacci_hs :: CInt -> CInt
 
</haskell>
 
</haskell>
   
Line 26: Line 26:
 
And call it from C:
 
And call it from C:
   
 
#include <HsFFI.h>
<haskell>
 
 
#ifdef __GLASGOW_HASKELL__
#include <HsFFI.h>
 
 
#include "Safe_stub.h"
#ifdef __GLASGOW_HASKELL__
 
 
extern void __stginit_Safe(void);
#include "Safe_stub.h"
 
 
#endif
extern void __stginit_Safe(void);
 
 
#include <stdio.h>
#endif
 
  +
#include <stdio.h>
 
 
int main(int argc, char *argv[])
 
  +
{
int main(int argc, char *argv[]) {
 
int i;
+
int i;
hs_init(&argc, &argv);
+
hs_init(&argc, &argv);
#ifdef __GLASGOW_HASKELL__
+
#ifdef __GLASGOW_HASKELL__
hs_add_root(__stginit_Safe);
+
hs_add_root(__stginit_Safe);
#endif
+
#endif
  +
 
i = fibonacci_hs(42);
+
i = fibonacci_hs(42);
printf("Fibonacci: %d\n", i);
+
printf("Fibonacci: %d\n", i);
  +
 
hs_exit();
+
hs_exit();
return 0;
+
return 0;
  +
}
}
 
</haskell>
 
   
 
Now, first compile the Haskell file:
 
Now, first compile the Haskell file:
   
$ ghc -c -O Safe.hs
+
$ ghc -c -O Safe.hs
   
 
Which creates Safe_stub.c, Safe_stub.o, Safe_stub.h, which you import into
 
Which creates Safe_stub.c, Safe_stub.o, Safe_stub.h, which you import into
Line 57: Line 56:
 
the Haskell objects on the command line:
 
the Haskell objects on the command line:
   
$ ghc -optc-O test.c Safe.o Safe_stub.o -o test
+
$ ghc -optc-O test.c Safe.o Safe_stub.o -o test
   
  +
Note, this will not work for ghc >= 7.2 due to ghc not generating Safe_stub.o file (thanks to Daniel Fischer for pointing this out), use the following command instead:
(Alternatively, fewer files to enumerate:
 
   
$ ghc --make -no-hs-main -optc-O test.c Safe -o test
+
$ ghc --make -no-hs-main -optc-O test.c Safe -o test
)
 
   
 
Then run your C code:
 
Then run your C code:
   
$ ./test
+
$ ./test
Fibonacci: 267914296
+
Fibonacci: 267914296
   
 
And that's it.
 
And that's it.

Revision as of 19:43, 11 June 2012

It is not uncommon to want to call a Haskell function from C code. Here's how to do that.

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

Note the foreign export. When GHC sees this, it will generate stubs for C, to help it work out the Haskell types.

And call it from C:

#include <HsFFI.h>
#ifdef __GLASGOW_HASKELL__
#include "Safe_stub.h"
extern void __stginit_Safe(void);
#endif
#include <stdio.h>

int main(int argc, char *argv[])
{
    int i;
    hs_init(&argc, &argv);
#ifdef __GLASGOW_HASKELL__
    hs_add_root(__stginit_Safe);
#endif

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

    hs_exit();
    return 0;
}

Now, first compile the Haskell file:

$ ghc -c -O Safe.hs

Which creates Safe_stub.c, Safe_stub.o, Safe_stub.h, 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 Safe.o Safe_stub.o -o test

Note, this will not work for ghc >= 7.2 due to ghc not generating Safe_stub.o file (thanks to Daniel Fischer for pointing this out), use the following command instead:

$ ghc --make -no-hs-main -optc-O test.c Safe -o test

Then run your C code:

$ ./test 
Fibonacci: 267914296

And that's it.