Linking to Haskell code from an external program
Colin Paul Adams
colin at colina.demon.co.uk
Sat Nov 15 07:10:12 EST 2008
I am trying to call a Haskell function from an Eiffel program, using C
as an intermediary.
For starters, I compiled and ran a variation of the program shown in
http://haskell.org/haskellwiki/Calling_Haskell_from_C, to make sure I
had the C-code right.
I then attempted to move it into Eiffel. I can compile the C code OK,
but I'm running into problems with linking.
I solved most of the problems by adding the -v flag to the call to ghc
which I used to link the original (haskell + c only) program, and
cut-and-paste the linker options from their into the Eiffel
configuration file. This isn't really satisfactory - I would like some
automatic way to determine what the flags should be.
The remaining problem has me stumped. I am getting the following
messages:
big_file_C4_c.c:(.text+0x9f4f): undefined reference to `__stginit_Fib'
/home/colin/fib/Fib_stub.o: In function `stginit_export_Fib_zdffibonaccizuhszuaQO':
Fib_stub.c:(.text+0x5): undefined reference to `Fib_zdffibonaccizuhszuaQO_closure'
/home/colin/fib/Fib_stub.o: In function `fibonacci_hs':
Fib_stub.c:(.text+0x32): undefined reference to `Fib_zdffibonaccizuhszuaQO_closure'
The Haskell code looks like this:
>{-# LANGUAGE ForeignFunctionInterface #-}
>
> module Fib where
>
> import Foreign.C.Types
> import CString
>
> fibonacci :: Int -> String
> fibonacci n = show (fibs !! n)
> where fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
>
> fibonacci_hs :: CInt -> IO CString
> fibonacci_hs = newCString . fibonacci . fromIntegral
>
> foreign export ccall fibonacci_hs :: CInt -> IO CString
And the C code (in an Eiffel wrapper) looks like this:
haskell_fib (n: INTEGER): POINTER is
-- String representation of `n'th Fibonacci number as a string
external "C inline use <stdio.h>,%"HsFFI.h%""
alias "[
#ifdef __GLASGOW_HASKELL__
#include "Fib_stub.h"
extern void __stginit_Fib ( void );
#endif
int argc;
char *argv[0];
argc = 0;
hs_init(&argc, &argv);
#ifdef __GLASGOW_HASKELL__
hs_add_root(__stginit_Fib);
#endif
return (fibonacci_hs($n));
hs_exit();
]"
end
I can't find any mention of the word "fibonacci" in the output from
the ghc run, and I don't know where this _closure stuff is coming
from. Can you help?
--
Colin Adams
Preston Lancashire
More information about the Glasgow-haskell-users
mailing list