[GHC] #13611: Segfault due to levity polymorphism of mkWeak#

#13611: Segfault due to levity polymorphism of mkWeak# -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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: -------------------------------------+------------------------------------- This code segfaults: {{{ {-# LANGUAGE MagicHash, UnboxedTuples #-} import GHC.Prim import GHC.Types main = do let local = () let null = 0## :: Word# let triple = (# local, null, null #) IO (\s -> case mkWeakNoFinalizer# triple () s of (# s, r #) -> (# s, () #)) }}} The problem is that `mkWeakNoFinalizer#` has a levity polymorphic type for its first argument, but the implementation really requires the first argument to be a pointer. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13611 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13611: Segfault due to levity polymorphism of mkWeak# -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 RyanGlScott): Is this addressed by Phab:D3490? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13611#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13611: Segfault due to levity polymorphism of mkWeak# -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 nomeata): I don’t think so. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13611#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13611: Segfault due to levity polymorphism of mkWeak# -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 goldfire): Neither do I. Though what guarantees do we provide when a user writes the `IO` constructor explicitly? This is tantamount to `unsafePerformIO`, is it not? While I conjecture that the segfault is possible without unsafe features, this test case isn't terribly convincing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13611#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13611: Segfault due to levity polymorphism of mkWeak# -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.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 nomeata):
This is tantamount to unsafePerformIO, is it not?
Not quite, I am not producing a `RealWorld#` token out of thin air. Normal user code calls `mkWeak#` via `mkWeak` in `GHC.Weak`, which is not levity polymorphic. But there is one use of `mkWeak#` in the libraries that seems to use a different `TypeRep`: {{{ addForeignPtrConcFinalizer_ :: ForeignPtrContents -> IO () -> IO () addForeignPtrConcFinalizer_ (PlainForeignPtr r) finalizer = do noFinalizers <- insertHaskellFinalizer r finalizer if noFinalizers then IO $ \s -> case r of { IORef (STRef r#) -> case mkWeak# r# () (unIO $ foreignPtrFinalizer r) s of { (# s1, _ #) -> (# s1, () #) }} else return () }}} The `r#` here is of type `MutVar# s a`, which is `UnliftedRep`; there are similar calls in the modules for for `MVar` and `IORef`. So this is a use case where we want levity polymorphism that allows any *boxed* type, whether lifted or not. Or, the easy way out, is to have two copies of the `mkWeak#` primop, one for `LiftedRep` and one for `UnliftedRep`. They could use the same code and info-pointer. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13611#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13611: Segfault due to levity polymorphism of mkWeak# -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.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 bgamari): * milestone: => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13611#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13611: Segfault due to levity polymorphism of mkWeak# -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.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 simonpj): * cc: simonmar (added) Comment:
Though what guarantees do we provide when a user writes the IO constructor explicitly? This is tantamount to unsafePerformIO, is it not?
You might get sequencing or concurrency errors, but not seg-faults.
But there is one use of mkWeak# in the libraries that seems to use a different TypeRep
Actually ''all'' the uses in `base` are on `UnliftedRep` except the single use in `GHC.Weak.mkWeak`.
Or, the easy way out, is to have two copies of the mkWeak# primop, one for LiftedRep and one for UnliftedRep.
Yes, let's do that. In principle we could further structure `RuntimeRep` to have {{{ data RuntimeRep = IntRep | WordRep | PtrRep Liftedness data Liftedness = Lifted | Unlifted }}} and now we could have polymorphism over liftedness, but I just don't think it's worth it. BTW I think that (like `dataToTag#`) `mkWeak#` probably requires its argument to be evaluated. (I don't think it does and eval itself, though perhaps it should.) Reason: `mkWeak#` should not make a weak pointer to a thunk. I think. So I am pretty suspicious of this `GHC.Weak.mkWeak`: {{{ mkWeak key val (Just (IO finalizer)) = IO $ \s -> case mkWeak# key val finalizer s of { (# s1, w #) -> (# s1, Weak w #) } }}} Looks wrong to me; e.g. `mkWeak# (head xs)`? Copying Simon M. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13611#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

and now we could have polymorphism over liftedness, but I just don't
#13611: Segfault due to levity polymorphism of mkWeak# -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.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 Iceland_jack): Replying to [comment:6 simonpj]: think it's worth it. Can it be added in the future if deemed useful? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13611#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13611: Segfault due to levity polymorphism of mkWeak# -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.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 simonmar): Duplicating the primop is an ugly solution to something that isn't really a problem IMO. There are lots of ways to segfault using primops! We should just document how to use them safely. If we could fix the type system to give an accurate type to this then fine, but otherwise I suggest we just improve the documentation. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13611#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13611: Segfault due to levity polymorphism of mkWeak# -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.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): Phab:D3498 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D3498 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13611#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13611: Segfault due to levity polymorphism of mkWeak#
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.2.1
Component: Compiler | Version: 8.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): Phab:D3498
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13611: Segfault due to levity polymorphism of mkWeak# -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.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): Phab:D3498 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13611#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13611: Segfault due to levity polymorphism of mkWeak# -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3498 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged as 933fb440ad4adba542975fc5d8b46c1f666ff2ce. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13611#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC