[GHC] #13148: Adding weak pointers to non-mutable unboxed values segfaults

GHC ghc-devs at haskell.org
Wed Jan 18 11:38:46 UTC 2017


#13148: Adding weak pointers to non-mutable unboxed values segfaults
-------------------------------------+-------------------------------------
           Reporter:  mboes          |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           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:
-------------------------------------+-------------------------------------
 Consider the following program:

 {{{#!hs
 {-# LANGUAGE MagicHash #-}
 {-# LANGUAGE UnboxedTuples #-}

 module Main where

 import Foreign
 import GHC.Base
 import GHC.IORef
 import GHC.Ptr
 import GHC.STRef
 import System.Mem

 main = do
     p@(Ptr p#) <- mallocBytes 10
     r@(IORef (STRef r#)) <- newIORef True
     IO $ \s -> case mkWeakNoFinalizer# r# () s of (# s1, w #) -> (# s1, ()
 #)
     performGC
 }}}

 This program works fine. But if I `mkWeakNoFinalizer#` to `#p` instead of
 `#r` then it '''segfaults'''. That is, I can attach a weak pointer to a
 `MutVar#`, as well as to a `MVar#`, but not any other unboxed type,
 including pointer addresses.

 The documentation says "Finalizers ''can'' be used reliably for types that
 are created explicitly and have identity, such as IORef and MVar". But a)
 I don't know that "types that have identity" is defined anywhere, b) this
 doesn't say that weak pointers ''cannot'' be used for anything else.

 Should I be able to create weak pointers to any unboxed value? If not, I
 guess this is mostly a documentation bug.

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


More information about the ghc-tickets mailing list