
Hi, I'm trying to use a shared lib written in Haskell to overload C functions via LD_PRELOAD. You might think this is a bit silly, but hey, why not? I want to overload connect() from sys/socket.h. I'll document what I've written so far; unfortunately there doesn't seem to be a lot of documentation about this topic. This is my haskell code (in testffi.hs):
module Socks where
import Foreign.C.Types import Foreign.Ptr
newtype S_sockaddr = S_sockaddr ()
foreign export ccall "connect" connect :: CInt -> Ptr (S_sockaddr) -> CUInt -> IO CInt
connect :: CInt -> Ptr (S_sockaddr) -> CUInt -> IO CInt connect _ _ _ = return (-1::CInt)
Here's how I compile it: ghc -Wall -c -fffi testffi.hs ghc -Wall -optl "-shared" -optl "-Wl,-soname,libtestffi.so" \ -o libtestffi.so testffi.o testffi_stub.o I'm not at all sure about these compiler and linker options, but this is the best I could come up with (i.e., no errors or warnings) Then I run a test program which calls connect(). I won't include the C source of that program, but it basically connects to the IP address given as the first argument (at port given by third argument) and sends a string. Basic error checking is done, i.e. the program does test the return value of connect(): LD_PRELOAD=./libtestffi.so ./conntest 127.0.0.1 "HELO" 1234 This aborts with a segfault in scheduleWaitThread() from ./libtestffi.so The test program doesn't use threads, so I'm wondering what I did wrong? Any help is appreciated. Greetings, Stephan Walter

On 9/23/06, Stephan Walter
I'm trying to use a shared lib written in Haskell to overload C functions via LD_PRELOAD. [snip] This aborts with a segfault in scheduleWaitThread() from ./libtestffi.so
The test program doesn't use threads, so I'm wondering what I did wrong?
From http://www.haskell.org/ghc/docs/latest/html/users_guide/sec-ffi-ghc.html#usi...: The call to hs_init() initializes GHC's runtime system. Do NOT try to invoke any Haskell functions before calling hs_init(): strange things will undoubtedly happen.
If you are using gcc you can add something like this when linking libtestffi.so:
#include

On Sun, 24 Sep 2006 20:20:55 +0300, Anatoly Zaretsky wrote:
#include
extern void __stginit_Socks(void);
static void __attribute__ ((constructor)) my_init(void) { int argc = 1; char *argv[] = {"Haskell shared object"}; char **argvp = argv; hs_init(&argc, &argvp); hs_add_root(__stginit_Socks); }
static void __attribute__ ((destructor)) my_fini(void) { hs_exit(); }
That solved it! If anyone wants to do the same: I put the code you gave above in hsinit.c, and compiled everything with: ghc -Wall -c -fffi testffi.hs gcc -g -Wall -I/usr/lib/ghc-6.4.2/include -c -o hsinit.o hsinit.c ghc -Wall -optl "-shared" -o libtestffi.so \ hsinit.o testffi.o testffi_stub.o Then, using LD_PRELOAD with the test program worked fine. Thanks a lot! -Stephan

On 9/24/06, Stephan Walter
gcc -g -Wall -I/usr/lib/ghc-6.4.2/include -c -o hsinit.o hsinit.c
or ghc -c hsinit.c or even ghc -Wall -optl "-shared" -o libtestffi.so \ hsinit.c testffi.o testffi_stub.o Could anybody familiar with ghc linking details comment on this constructor/destructor thing so that we can add a wiki about building shared objects? -- Tolik

On Sun, 24 Sep 2006 21:37:32 +0300, Anatoly Zaretsky wrote:
ghc -Wall -optl "-shared" -o libtestffi.so \ hsinit.c testffi.o testffi_stub.o
Ok, that is even shorter. And it seems you don't have to call
hs_add_root() or hs_exit(). At least for me it works with this hsinit.c:
#include
participants (2)
-
Anatoly Zaretsky
-
Stephan Walter