
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