
Hello Cafe, I am trying to use a Haskell shared library with foreign exports from Haskell again via dlopen/dlsym. Sadly it segfaults, and the segfaults happen on dlclose during garbage collection points (as figured out by monochrom in #haskell). So right now I can only open a library once and may not dlclose it. Can someone point me to a mistake I made, or is this rather a ghc (7.8.3) bug? Please see attached minimal example. Regards, Tobias test.hs: module Main where import qualified System.Posix.DynamicLinker as DL import Foreign foreign import ccall "dynamic" mkTest :: FunPtr Int -> Int main = do DL.withDL ("./libtest.so") [DL.RTLD_NOW] $ \dl -> do dimPtr <- DL.dlsym dl "test" let test = mkTest dimPtr print test libtest.hs: module Test() where import Foreign foreign export ccall test :: Int test :: Int test = 124 build with: ghc --make -shared -dynamic -fPIC libtest.hs -o libtest.so ghc --make -dynamic test.hs