[Haskell-cafe] Attach a finalizer to a FunPtr
Roman Cheplyaka
roman.cheplyaka at tweag.io
Tue Sep 17 07:16:44 UTC 2019
Hi all,
I'd like to attach a finalizer to FunPtrs (which point to JIT-compiled functions that need to be deallocated).
However, the act of running the finalizer (no matter what it does) results in a segfault.
Here's a minimal example:
{-# LANGUAGE UnboxedTuples, MagicHash #-}
import GHC.Exts (FunPtr(..))
import GHC.Base
import Foreign.Ptr
import System.Mem
attachFinalizer :: FunPtr a -> IO () -> IO ()
attachFinalizer fptr@(FunPtr addr) (IO fin) = IO $ \s0 ->
case mkWeak# addr fptr fin s0 of
(# s1, _ #) -> (# s1, () #)
foreign import ccall "wrapper"
mkIO :: IO () -> IO (FunPtr (IO ()))
main = do
fptr <- mkIO $ return ()
attachFinalizer fptr $ do
-- The exact contents of the finalizer doesn't seem to matter
putStrLn "+++ finalizer ran"
freeHaskellFunPtr fptr
putStrLn "+++ attached successfully"
performGC
Is there a proper way to do this? (GHC 8.6.5)
Roman
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20190917/f8f85ba9/attachment.html>
More information about the Haskell-Cafe
mailing list