GHCi can't see 'atexit', can't load module
Maurício CA
mauricio.antunes at gmail.com
Tue Aug 25 22:20:17 EDT 2009
(I left this in cafe, but I think it is actually ghc related.)
I just checked it seems not to be possible to load any module in
GHCi that uses FFI to wrap the standard C function 'atexit'. When
trying that, we get a message saying the symbol 'atexit' can't be
found. (This is not a problem when building an executable with
ghc, though.)
It's easy to reproduce the problem. Just try something like this:
-----
module XXX where
import Foreign
import Foreign.C
foreign import ccall atexit :: FunPtr (IO ()) -> IO CInt
-----
Load it in ghci (after ':set -XForeignFunctionInterface' to get
FFI) and you will get the error. If we replace the line below for
the above we don't get any error message:
foreign import ccall exit :: CInt -> IO ()
Here, we just replaced 'atexit' by 'exit', which, according to
'nm' tool, is at the same 'libc' library that 'atexit' belongs to.
Thanks,
Maurício
More information about the Glasgow-haskell-users
mailing list