Linking to Haskell code from an external program

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

Embarassing - I simply forgot to include Fib.o in the link. So it links now (program crashes, but I can try to sort that out). I'm still intereted in knowing how to automatically get the list of required libraries.
"Colin" == Colin Paul Adams
writes:
Colin> I am trying to call a Haskell function from an Eiffel
Colin> program, using C as an intermediary.
Colin> For starters, I compiled and ran a variation of the program
Colin> shown in
Colin> http://haskell.org/haskellwiki/Calling_Haskell_from_C, to
Colin> make sure I had the C-code right.
Colin> I then attempted to move it into Eiffel. I can compile the
Colin> C code OK, but I'm running into problems with linking.
Colin> I solved most of the problems by adding the -v flag to the
Colin> call to ghc which I used to link the original (haskell + c
Colin> only) program, and cut-and-paste the linker options from
Colin> their into the Eiffel configuration file. This isn't really
Colin> satisfactory - I would like some automatic way to determine
Colin> what the flags should be.
Colin> The remaining problem has me stumped. I am getting the
Colin> following messages:
Colin> big_file_C4_c.c:(.text+0x9f4f): undefined reference to
Colin> `__stginit_Fib' /home/colin/fib/Fib_stub.o: In function
Colin> `stginit_export_Fib_zdffibonaccizuhszuaQO':
Colin> Fib_stub.c:(.text+0x5): undefined reference to
Colin> `Fib_zdffibonaccizuhszuaQO_closure'
Colin> /home/colin/fib/Fib_stub.o: In function `fibonacci_hs':
Colin> Fib_stub.c:(.text+0x32): undefined reference to
Colin> `Fib_zdffibonaccizuhszuaQO_closure'
Colin> 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
Colin> And the C code (in an Eiffel wrapper) looks like this:
Colin> haskell_fib (n: INTEGER): POINTER is -- String
Colin> representation of `n'th Fibonacci number as a string
Colin> external "C inline use

Colin Paul Adams wrote:
Embarassing - I simply forgot to include Fib.o in the link. So it links now (program crashes, but I can try to sort that out).
I'm still intereted in knowing how to automatically get the list of required libraries.
"Colin" == Colin Paul Adams
writes: Colin> I am trying to call a Haskell function from an Eiffel Colin> program, using C as an intermediary.
Colin> For starters, I compiled and ran a variation of the program Colin> shown in Colin> http://haskell.org/haskellwiki/Calling_Haskell_from_C, to Colin> make sure I had the C-code right.
Colin> I then attempted to move it into Eiffel. I can compile the Colin> C code OK, but I'm running into problems with linking.
Colin> I solved most of the problems by adding the -v flag to the Colin> call to ghc which I used to link the original (haskell + c Colin> only) program, and cut-and-paste the linker options from Colin> their into the Eiffel configuration file. This isn't really Colin> satisfactory - I would like some automatic way to determine Colin> what the flags should be.
The only other way I can think of is to construct the arguments yourself by querying the package database, e.g. "ghc-pkg field ld-options rts", but you'll have to combine the information from several different fields of the packages you use, and basically reproduce what GHC does to construct the ld command line. Cheers, Simon

"Simon" == Simon Marlow
writes:
Colin> I then attempted to move it into Eiffel. I can compile the Colin> C code OK, but I'm running into problems with linking. >> Colin> I solved most of the problems by adding the -v flag to the Colin> call to ghc which I used to link the original (haskell + c Colin> only) program, and cut-and-paste the linker options from Colin> their into the Eiffel configuration file. This isn't really Colin> satisfactory - I would like some automatic way to determine Colin> what the flags should be. Simon> The only other way I can think of is to construct the Simon> arguments yourself by querying the package database, Simon> e.g. "ghc-pkg field ld-options rts", but you'll have to Simon> combine the information from several different fields of Simon> the packages you use, and basically reproduce what GHC does Simon> to construct the ld command line. Can you point me at where it does this? Thanks. -- Colin Adams Preston Lancashire

"Colin" == Colin Paul Adams
writes:
"Simon" == Simon Marlow
writes: Colin> I then attempted to move it into Eiffel. I can compile the Colin> C code OK, but I'm running into problems with linking. >>> Colin> I solved most of the problems by adding the -v flag to the Colin> call to ghc which I used to link the original (haskell + c Colin> only) program, and cut-and-paste the linker options from Colin> their into the Eiffel configuration file. This isn't really Colin> satisfactory - I would like some automatic way to determine Colin> what the flags should be.
Simon> The only other way I can think of is to construct the
Simon> arguments yourself by querying the package database,
Simon> e.g. "ghc-pkg field ld-options rts", but you'll have to
Simon> combine the information from several different fields of
Simon> the packages you use, and basically reproduce what GHC does
Simon> to construct the ld command line.
I have upgraded to ghc 6.10.1 by compiling from source.
Now I can't get it to link, either using my previous method of linking
a standalone C program via ghc -v, and copying the -u options, or by
running:
ghc-pkg field rts ld-options
(I found out by trial-and error that the syntax you gave above was
inverted).
In both cases, I get errors:
/home/colin/fib/Fib.o: In function `r131_info':
(.text+0x79): undefined reference to `base_GHCziBase_ZC_con_info'
/home/colin/fib/Fib.o: In function `r131_info':
(.text+0x10f): undefined reference to `base_GHCziBase_ZMZN_closure'
/home/colin/fib/Fib.o: In function `s13p_info':
(.text+0x157): undefined reference to `base_GHCziBase_ZMZN_closure'
/home/colin/fib/Fib.o: In function `s13F_info':
(.text+0x2cf): undefined reference to `base_GHCziBase_ZMZN_closure'
/home/colin/fib/Fib.o: In function `s13c_info':
(.text+0x32): undefined reference to `base_GHCziNum_plusInteger_info'
/home/colin/fib/Fib.o: In function `r131_info':
(.text+0x124): undefined reference to `base_GHCziList_foldr21_info'
/home/colin/fib/Fib.o:(.data+0x0): undefined reference to `base_GHCziNum_Szh_static_info'
/home/colin/fib/Fib.o:(.data+0x10): undefined reference to `base_GHCziNum_Szh_static_info'
/home/colin/fib/Fib.o: In function `r131_closure':
(.data+0x38): undefined reference to `base_GHCziBase_ZC_static_info'
/home/colin/fib/Fib.o: In function `r131_closure':
(.data+0x58): undefined reference to `base_GHCziBase_ZC_static_info'
collect2: ld returned 1 exit status
I tried in desperation to add -u flag for each of the undefined
symbols above, but it makes no difference.
I'm quite lost now.
My C code looks like this:
static char * program_name = "Eiffel program";
static char * terminator = (char *) 0;
int argc;
char **argv[2];
argc = 1;
argv [0] = &program_name;
argv [1] = &terminator;
hs_init(&argc, argv);
#ifdef __GLASGOW_HASKELL__
#include "Fib_stub.h"
extern void __stginit_Fib ( void );
hs_add_root(__stginit_Fib);
#endif
return (fibonacci_hs($n));
hs_exit();
(and in addition there are includes for

It looks as if you are somehow failing to link your binary with package 'base'. (Are you using 'ghc' as your linker; you should be.) But others are better than I at this kind of stuff.
Simon
| -----Original Message-----
| From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users-
| bounces@haskell.org] On Behalf Of Colin Paul Adams
| Sent: 23 November 2008 15:20
| To: Simon Marlow
| Cc: glasgow-haskell-users@haskell.org
| Subject: Re: Linking to Haskell code from an external program
|
| >>>>> "Colin" == Colin Paul Adams

"Simon" == Simon Peyton-Jones
writes:
Simon> It looks as if you are somehow failing to link your binary Simon> with package 'base'. (Are you using 'ghc' as your linker; Simon> you should be.) But others are better than I at this kind Simon> of stuff. I have base-4.0.0.0 specified. No, I am not using ghc as the linker. Since I am calling the Haskell routine from an Eiffel program, I don't see how I could do that with any sort of ease. -- Colin Adams Preston Lancashire

Colin Paul Adams wrote:
"Simon" == Simon Peyton-Jones
writes: Simon> It looks as if you are somehow failing to link your binary Simon> with package 'base'. (Are you using 'ghc' as your linker; Simon> you should be.) But others are better than I at this kind Simon> of stuff.
I have base-4.0.0.0 specified.
No, I am not using ghc as the linker. Since I am calling the Haskell routine from an Eiffel program, I don't see how I could do that with any sort of ease.
I think you'll have to post complete instructions to reproduce the problem you're having; it's hard to piece it together from the information you've given. The problem will be in the details somewhere. Cheers, Simon

"Simon" == Simon Marlow
writes:
Simon> Colin Paul Adams wrote:
>>>>>>> "Simon" == Simon Peyton-Jones

Colin Paul Adams wrote:
"Simon" == Simon Marlow
writes: Simon> Colin Paul Adams wrote: >>>>>>> "Simon" == Simon Peyton-Jones
>>>>>>> writes: >> Simon> It looks as if you are somehow failing to link your binary Simon> with package 'base'. (Are you using 'ghc' as your linker; Simon> you should be.) But others are better than I at this kind Simon> of stuff. >> >> I have base-4.0.0.0 specified. >> >> No, I am not using ghc as the linker. Since I am calling the >> Haskell routine from an Eiffel program, I don't see how I could >> do that with any sort of ease. Simon> I think you'll have to post complete instructions to Simon> reproduce the problem you're having; it's hard to piece it Simon> together from the information you've given. The problem Simon> will be in the details somewhere.
It seems it was some complication when switching from 6.8 to 6.10. I didn't clean up properly.
Links now, but I'm still getting the crash in the garbage collector. :-(
Perhaps try reducing the example until the problem goes away, so we can see at which stage it gets introduced? Or can you boil down your example to something we can reproduce? Cheers, Simon

"Simon" == Simon Marlow
writes:
>> Links now, but I'm still getting the crash in the garbage >> collector. :-( Simon> Perhaps try reducing the example until the problem goes Simon> away, so we can see at which stage it gets introduced? Or Simon> can you boil down your example to something we can Simon> reproduce? I've managed to solve it this morning. It was the way I was setting up argc and argv (badly) for the call to hs_init. Doing it properly means there are no longer any crashes with either Eiffel compliler. -- Colin Adams Preston Lancashire

Colin Paul Adams
I've managed to solve it this morning. It was the way I was setting up argc and argv (badly) for the call to hs_init. Doing it properly means there are no longer any crashes with either Eiffel compliler.
What is the "bad" way to set them up? -- _jsn

"Jason" == Jason Dusek
writes:
Jason> Colin Paul Adams
participants (4)
-
Colin Paul Adams
-
Jason Dusek
-
Simon Marlow
-
Simon Peyton-Jones