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

GHC ghc-devs at haskell.org
Sat Aug 27 12:27:40 UTC 2016


#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


More information about the ghc-tickets mailing list