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

#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

#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 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 rwbarton): I don't know exactly how `mkWeakNoFinalizer#` works but surely it can only possibly attach a finalizer to a value of ''boxed'' type, that is, a value that is stored as a closure on the Haskell heap. After all the meaning of a finalizer is that it's an action that runs when the object is no longer live after GC. `MutVar#` and `MVar#` are boxed (but unlifted) types, but `Addr#` is unboxed, really just a synonym for `Int#`. It doesn't make any more sense to attach a finalizer to `p#` than it does to attach one to `7#`. See https://ghc.haskell.org/trac/ghc/wiki/Commentary/Rts/Storage/HeapObjects for the difference between unboxed and unlifted. The segfault happened because the weak finalizer code interpreted the bit pattern of `p#` as a pointer into the Haskell heap, while it was actually a pointer into the C heap (produced by `malloc`); and chaos ensued. (Based on this program snippet, it looks like you might just want `mallocForeignPtr`.) But morally the problem isn't really with C vs. Haskell heap but with trying to attach a finalizer to an unboxed value. The documentation you refer to is the documentation for the user-facing System.Mem.Weak module. We could add documentation to `mkWeakNoFinalizer#`, even though the primops are really only intended to be used to implement the base libraries. What would have been helpful? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13148#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 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 mboes): OK that makes sense. I was surprised that things worked with `MutVar#` because I assumed it was also unboxed, but I see now that's not the case. The types in `System.Mem.Weak` already preclude creating a weak pointer to an unboxed value. But that of `mkWeakNoFinalizer#` is not precise enough to rule that out. Is the rule that the first argument to this function is valid iff it is of unlifted (primitive) type? If so, I think it would be useful to document that there. This exploration arose from the need to retrofit a single finalizer to a codebase that makes extensive use of `Ptr` without having to switch to `ForeignPtr` everywhere. The latter being more inconvenient, since it can't appear in the type signature of foreign imports. I assume attaching a finalizer to a `Ptr` runs the risk that the finalizer might fire too early. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13148#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 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 rwbarton): A `Ptr` is a wrapper around `Addr#` in the same way that `Int` is a wrapper around `Int#`. The `Ptr` itself has no meaningful lifetime or identity (unlike the underlying memory pointed to by the pointer). So yes, attaching a finalizer to a `Ptr` will not be useful. Using `Ptr` is entirely equivalent to programming in C with manual memory management; the Haskell GC can't help you here. `Ptr` really might just as well be `Int` as far as Haskell is concerned. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13148#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 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 rwbarton):
Is the rule that the first argument to this function is valid iff it is of unlifted (primitive) type? If so, I think it would be useful to document that there.
I think the rule is probably that the argument must be of boxed type. Surely it must be necessary; not sure whether it is also sufficient. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13148#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC