[Haskell-cafe] FFI and LD_PRELOAD -> segfault

Stephan Walter news at stephan.walter.name
Sat Sep 23 13:13:54 EDT 2006


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



More information about the Haskell-Cafe mailing list