#7170: Foreign.Concurrent finalizer called twice in some cases
------------------------------+---------------------------------------------
 Reporter:  joeyadams         |          Owner:                  
     Type:  bug               |         Status:  new             
 Priority:  normal            |      Component:  Runtime System  
  Version:  7.4.2             |       Keywords:                  
       Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  Runtime crash     |       Testcase:                  
Blockedby:                    |       Blocking:                  
  Related:                    |  
------------------------------+---------------------------------------------
 When [http://hackage.haskell.org/packages/archive/base/latest/doc/html
 /Foreign-Concurrent.html#v:newForeignPtr Foreign.Concurrent.newForeignPtr]
 is used, here's a case where the finalizer is called twice:

 {{{
 {-# LANGUAGE ForeignFunctionInterface #-}
 import Control.Concurrent
 import Control.Exception    (bracket)
 import Foreign.Ptr          (Ptr, intPtrToPtr)
 import Foreign.ForeignPtr   (ForeignPtr)
 import qualified Foreign.Concurrent as FC
 import qualified Foreign.ForeignPtr as FP

 testForeignPtr_Concurrent :: Ptr a -> IO (ForeignPtr a)
 testForeignPtr_Concurrent ptr = FC.newForeignPtr ptr (fin ptr)

 fin :: Ptr a -> IO ()
 fin ptr = putStrLn $ "finalizing " ++ show ptr

 main :: IO ()
 main = do
     mv <- newEmptyMVar
     bracket (testForeignPtr_Concurrent $ intPtrToPtr 1)
             FP.finalizeForeignPtr $ \_ ->
         -- hang, so the thread and foreign pointer get GCed
         takeMVar mv
 }}}

 This produces the following output:

 {{{
 finalizing 0x0000000000000001
 finalizing 0x0000000000000001
 foreignptr: thread blocked indefinitely in an MVar operation
 }}}

 This happens on GHC 7.4.2 and 7.6.0.20120810, with and without -threaded.

 This can easily lead to segfaults when you have an FFI library that does
 this:

 {{{
 create :: IO Object
 create = do
     ptr <- c_create
     CObject <$> newForeignPtr ptr (finalize ptr)

 finalize :: Ptr CObject -> IO ()
 finalize ptr = do
     ...

 destroy :: Object -> IO ()
 destroy (Object fptr) =
     finalizeForeignPtr fptr
 }}}

 And application code does this:

 {{{
 bracket create destroy $ \obj -> do
     ...
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7170>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to