[GHC] #10867: Primop types should not mention ()

#10867: Primop types should not mention () -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- I've just noticed that two primpops have types that mention tuples (see `compiler/prelude/primops.txt.pp`): {{{ primop FinalizeWeakOp "finalizeWeak#" GenPrimOp Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, (State# RealWorld -> (# State# RealWorld, () #)) #) primop Check "check#" GenPrimOp (State# RealWorld -> (# State# RealWorld, a #) ) -> (State# RealWorld -> (# State# RealWorld, () #) ) }}} But they really really shouldn't. The unit tuple is a type defined in Haskell, and it makes an awkward cycle if the supposedly-truly-primitive primpops refer to it. (Discovered during the saga of [Phab:D757].) Most primpops do not do this; eg {{{ primop WriteMutVarOp "writeMutVar#" GenPrimOp MutVar# s a -> a -> State# s -> State# s }}} Now `check#` and `finalizeWeak#` are pretty obscure primops and I don't think anyone will mind if I fix their type signatures. But in addition to doing that, I'll have to look at their implementations. '''But where ''are'' those implementations??''' I can't find anything in the RTS. While thinking about it * Both come with literally zero Haddock documentation which is terrible. The type of both is pretty obscure. * `check#` is a very short name for very specialised STM operation. Surely we should call it `addSTMInvariant` or something like that? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10867 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10867: Primop types should not mention () -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by fryguybob): The `check#` implementation is found here: https://ghc.haskell.org/trac/ghc/browser/ghc/rts/PrimOps.cmm#L1320 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10867#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10867: Primop types should not mention () -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Great. But what would need to change if we want the type of `check#` to be {{{ primop Check "check#" GenPrimOp (State# RealWorld -> (# State# RealWorld, a #) ) -> State# RealWorld -> State# RealWorld }}} more like other primops. Somehow it must be returning that unit tuple. (Or perhaps not and it's always been broken!!!) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10867#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10867: Primop types should not mention () -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by fryguybob): And `finalizeWeak#` is here: https://ghc.haskell.org/trac/ghc/browser/ghc/rts/PrimOps.cmm#L679 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10867#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10867: Primop types should not mention () -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by fryguybob): The `checkzh` primop ends with `return ()` which is syntax and turns into `mkReturn` with an empty list of `CmmActual`. Not sure if that helps. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10867#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10867: Primop types should not mention () -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by fryguybob): Other primops like `CopySmallArrayOp#` end with `return ()` in cmm and have a type `... -> State# s -> State# s`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10867#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10867: Primop types should not mention () -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by fryguybob): For the broader question of the STM data invariant feature, it is slightly broken (#7930) and may be a significant amount of work to keep around if we use an implementation that keeps an approximate read-set for performance gains. I have asked around before and never found any users of the feature or code in the wild that uses the feature. Its usefulness for discovering problems in user code is limited in highly concurrent settings. The implementation takes a lock on every `TVar` when the transaction has touched an invariant meaning it simply will not see some interleavings that might be the exact ones that violate the invariant. Perhaps a better approach in the space is to extend Déjà Fu from Michael Walker and Colin Runciman to cover the same territory but include all the most significant interleavings. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10867#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10867: Primop types should not mention () -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): I'd be ok with removing the STM data invariant feature altogether, if that seemed sensible. As you say, it is barely (never?) used. You are now the person closest to the metal, so please feel free to propose changes to GHC. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10867#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10867: Primop types should not mention () -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * cc: simonmar (added) Comment: Simon M: might you comment on what we need to do on the RTS side if we change the types of these to primops? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10867#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10867: Primop types should not mention () -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonmar): The RTS refers to lots of things that are defined in Haskell, incidentally, not just in primops. The full list is in `rts/Prelude.h`. But you can change these primops if necessary. You probably didn't find the implementations because they're Z-encoded; `finalizeWeak#` is `stg_finalizzeWeakzh` in `rts/PrimOps.h`. It returns the finalizer of a weak pointer, which has type `State# RealWorld -> (# State# RealWorld, () #)`, but you could always lie and give it a more general type. The wrapper in `GHC.Weak` will probably work unchanged. We already lie in the type of `mkWeak#` in a similar way, for reasons I forget. It looks like `check#` has the wrong type anyway, its implementation returns `()` (ie. zero return values in Cmm), so its Haskell type should have a return type of `State# RealWorld`. Feel free to change its name at the same time, I agree it's a silly name! When changing this you'll need to run the tests in the stm package, which I think aren't run by default. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10867#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10867: Primop types should not mention () -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * cc: core-libraries-committee (added) Comment: Simon, can you help a little more? I'm also copying the core libraries committee, since I propose an API change for weak-pointer primpops. The type `Weak#` and primop `mkWeak#`, are declared thus: {{{ primtype Weak# b primop MkWeakOp "mkWeak#" GenPrimOp o -> b -> c -> State# RealWorld -> (# State# RealWorld, Weak# b #) }}} I think `c` is the finalizer. This type suggests that you can put any old value in for the finalizer, which seems unlikely. '''In fact it can easily lead to a seg-fault (with no use of `unsafeCoerce` by building a weak pointer whose "finaliser" with the wrong type.''' Then the primop `finalizeWeak#` is declared thus: {{{ primop FinalizeWeakOp "finalizeWeak#" GenPrimOp Weak# a -> State# RealWorld -> (# State# RealWorld , Int# , State# RealWorld -> (# State# RealWorld, () #) #) }}} I believe the following: * The third argument to `mkWeak#` is returned as the third component of the result to `finalizeWeak#`, but is otherwise totally un-examined by the RTS. Is that true? In that case it would be far, far better to declare them like this: {{{ primtype Weak# value finalizer primop MkWeakOp "mkWeak#" GenPrimOp key -> value -> finalizer -> State# RealWorld -> (# State# RealWorld, Weak# payload finalizer #) }}} So `Weak#` gets two type parameters, the second recording the type of the "finaliser". All the RTS promises to do is to cough up the "finalizer" when the `key` dies. Now in `GHC.Weak` we can declare `Weak` thus: {{{ data Weak v = Weak (Weak# v) (IO ()) }}} That is `Weak` specialises the "any only value can be a finaliser" API offered by `Weak#` to "the finaliser is a vlaue of type `IO ()`" API for `Weak`. Doing this would eliminate an unpleasant potential source of seg-faults; and it would eliminate one of the two unpleasant uses of `()` in `primpops.txt.pp`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10867#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10867: Primop types should not mention () -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj):
It looks like `check#` has the wrong type anyway, its implementation returns () (ie. zero return values in Cmm), so its Haskell type should have a return type of `State# RealWorld`
Ben: could you do this and validate, pls? Fixes a bug and helps move this ticket along. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10867#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10867: Primop types should not mention () -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): OK, talked to Simon. My "I believe the following.." is false. In fact all those finalisers are packed into an array in `Weak.c` (function `scheduleFinalizers`) and handed off to the Haskell function `GHC.Weak.runFinalizerBatch`. So the latter certainly needs to know the type of the finaliser. With that in mind, I think we should not change the `Weak#` type (as I wrongly proposed above) but instead change the type of `mkWeak#` to {{{ primop MkWeakOp "mkWeak#" GenPrimOp key -> value -> (State# RealWorld -> State# RealWorld) -> (# State# RealWorld, Weak# b #) }}} and `GHC.Weak.runFinalizerBatch` to {{{ runFinalizerBatch :: Int -> Array# (State# RealWorld -> State# RealWorld) -> IO () }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10867#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10867: Primop types should not mention ()
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#10867: Primop types should not mention () -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: | Phab:D1276, Phab:D1272 -------------------------------------+------------------------------------- Changes (by bgamari): * differential: => Phab:D1276, Phab:D1272 Comment: Simon Marlow suggested that wrapping finalizers to peel off the return value from the returned unboxed tuple is unnecessary. fb4092642f057f258d07cd6979925f4e2579eda6 reverts changes the type from Simon PJ's suggestion of (implemented in Phab:D1271), {{{#!hs mkWeak# :: o -> b -> (State# RealWorld -> State# RealWorld) -> State# RealWorld -> (# State# RealWorld, Weak# b #) }}} to, {{{#!hs mkWeak# :: o -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) }}} This was done in Phab:D1276. Note that the return type `c` is now fully polymorphic. It is the user's responsibility to ignore this value. This is explained in a comment. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10867#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10867: Primop types should not mention () -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: | Phab:D1276, Phab:D1272 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10867#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC