[GHC] #12547: Concurrent.ForeignPtr needs to access a C-ForeignPtr, but this is already gone

#12547: Concurrent.ForeignPtr needs to access a C-ForeignPtr, but this is already gone -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime | Version: 8.0.1 System | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I have a `ForeignPtr` `fptr32` with a C finalizer and a `Concurrent.ForeignPtr` with a finalizer that needs to access `fptr32`. Unfortunately, accessing `fptr32` from the concurrent finalizer does not assert that `fptr32` is still alive. Consider the following program: {{{#!hs {-# LANGUAGE ForeignFunctionInterface #-} module Main where import qualified Foreign.Concurrent as FC import Foreign.Storable (peek) import Foreign.ForeignPtr (ForeignPtr, withForeignPtr, newForeignPtr) import Foreign.Ptr (Ptr, FunPtr, nullPtr) import Control.Monad (void) import Data.Word (Word32) import System.Mem (performGC) foreign import ccall safe "create" create :: IO (Ptr Word32) foreign import ccall safe "&delete" delete :: FunPtr (Ptr Word32 -> IO ()) makeForeignPtr :: IO () -> IO (ForeignPtr ()) makeForeignPtr final = FC.newForeignPtr nullPtr final finalizer :: ForeignPtr Word32 -> IO () finalizer fptr = do withForeignPtr fptr $ \ptr -> print =<< peek ptr main :: IO () main = do fptr32 <- newForeignPtr delete =<< create void $ makeForeignPtr (finalizer fptr32) performGC }}} and {{{#!c #include "stdio.h" #include "stdlib.h" #include "stdint.h" uint32_t *create () { uint32_t *ptr = malloc(sizeof(uint32_t)); printf ("create %lx\n", (unsigned long int)ptr); *ptr = 23; return ptr; } void delete (uint32_t *ptr) { printf ("delete %lx\n", (unsigned long int)ptr); *ptr = 42; free(ptr); } }}} It emits: {{{ create 2685dc0 delete 2685dc0 0 }}} If it would be correct, it would print `23` instead of `0` and it would print the number before `delete`. Is this a bug or a feature? If it is a feature, how do I get what I need? I know that the documentation says that we must not use `touchForeignPtr` for enforcing a particular order of running finalizers, but I thought that `withForeignPtr`/`touchForeignPtr` pretty clearly state that the `ForeignPtr` must be alive in `finalizer`. I cannot see an abuse here. Actually, this is a simplified version from an example that is even worse: In the original code, `create` is the LLVM-JIT creating code for a finalizer, `delete` frees the function code and `finalizer` runs the LLVM generated finalizer code. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12547 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12547: Concurrent.ForeignPtr needs to access a C-ForeignPtr, but this is already gone -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Lemming): * Attachment "GarbageCollection.hs" added. main Haskell program -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12547 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12547: Concurrent.ForeignPtr needs to access a C-ForeignPtr, but this is already gone -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Lemming): * Attachment "GarbageCollectionC.c" added. additional C code -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12547 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12547: Concurrent.ForeignPtr needs to access a C-ForeignPtr, but this is already gone -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * type: bug => feature request Comment: Currently all `ForeignPtrs` that are unreachable get finalized at the same time. This is how it's intended to work. We *could* refine it so that a finalizer from a `Concurrent.ForeignPtr` can keep a C `ForeignPtr` alive. It would mean processing the two kinds of weak pointers in separate batches (and possibly keeping them in separate lists, I'm not sure). Note that this is a special case, and is different from saying that a finalizer from any dead `ForeignPtr` can keep any other `ForeignPtr` alive. It's not clear to me how you'd define a sensible semantics in that case (consider a `ForeignPtr` that refers to itself from its finalizer, or two `ForeignPtr`s that refer to each other from their finalizers). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12547#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12547: Concurrent.ForeignPtr needs to access a C-ForeignPtr, but this is already gone -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Lemming): I have to add that I do not really need `Concurrent.ForeignPtr`. It allowed me to call `touchForeignPtr` and I hoped that this would solve my problem. Since it does not work we may forget about `Concurrent.ForeignPtr` and look for a solution using entirely C `ForeignPtr`s. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12547#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12547: Concurrent.ForeignPtr needs to access a C-ForeignPtr, but this is already gone -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Lemming): Replying to [comment:1 simonmar]:
Currently all `ForeignPtrs` that are unreachable get finalized at the same time. This is how it's intended to work.
We *could* refine it so that a finalizer from a `Concurrent.ForeignPtr` can keep a C `ForeignPtr` alive. It would mean processing the two kinds of weak pointers in separate batches (and possibly keeping them in separate lists, I'm not sure).
You gave me privately the tip to use `StablePtr`. So I added a `freeStablePtr` after `withForeignPtr`. This works nicely! Thus I think it is enough to add a warning to `touchForeignPtr` and `withForeignPtr` that they have no effect in a concurrent finalizer and that you should consider `StablePtr` instead. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12547#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12547: Concurrent.ForeignPtr needs to access a C-ForeignPtr, but this is already
gone
-------------------------------------+-------------------------------------
Reporter: Lemming | Owner:
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Runtime System | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Marlow
participants (1)
-
GHC