[GHC] #14561: Panic on levity polymorphic very unsafe coerce

#14561: Panic on levity polymorphic very unsafe coerce -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Keywords: | Operating System: Unknown/Multiple LevityPolymorphism | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE TypeInType #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE MagicHash #-} module LevityId where import GHC.Types import GHC.Prim levityPolymorphicId :: forall (a :: TYPE r). a -> a levityPolymorphicId = unsafeCoerce# }}} {{{ (GHC version 8.3.20170928 for x86_64-apple-darwin): runtimeRepPrimRep typePrimRep (a_aW0 :: TYPE r_aVZ) r_aVZ Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1144:37 in ghc:Outputable pprPanic, called at compiler/simplStg/RepType.hs:358:5 in ghc:RepType runtimeRepPrimRep, called at compiler/simplStg/RepType.hs:344:5 in ghc:RepType kindPrimRep, called at compiler/simplStg/RepType.hs:307:18 in ghc:RepType typePrimRep, called at compiler/simplStg/UnariseStg.hs:666:8 in ghc:UnariseStg Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} As originally mentioned [https://github.com/ghc-proposals/ghc- proposals/pull/98#issuecomment-349727273 here]. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14561 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14561: Panic on levity polymorphic very unsafe coerce -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: | LevityPolymorphism 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 simonpj): Ah, hum. Lint rejects the program thus {{{ *** Core Lint errors : in result of Desugar (after optimization) *** <no location info>: warning: [in body of lambda with binder v_B1 :: a_aVG] Levity-polymorphic binder: v_B1 :: (a_aVG :: TYPE r_aVF) *** Offending Program *** levityPolymorphicId :: forall (a :: TYPE r). a -> a [LclIdX] levityPolymorphicId = \ (@ (r_aVF :: RuntimeRep)) (@ (a_aVG :: TYPE r_aVF)) (v_B1 :: a_aVG) -> v_B1 }}} This happens because we want to allow {{{ unsafeCoerce# (x::Int#) }}} and expand it to {{{ x |> (UnsafeCo ...) }}} So we give `unsafeCoerce#` the extremely dodgy unfolding {{{ /\r1 r2 (a:Type r1) (b:Type r2) (x:a). x |> UnsafeCo ... }}} It's dodgy because it has a bad lambda: we can't lambda-bind a levity- polymorphic variable `x`. It only works when `unsafeCoerce#` is saturated. This is tiresome. The only paths forward I can see are * Do not allow `unsafeCoerce` on unboxed values. I don't know how much it is used. * Check that all uses are saturated. Perhaps in the desugarer. The latter would be least destabilising. Any thoughts? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14561#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14561: Panic on levity polymorphic very unsafe coerce -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: | LevityPolymorphism 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): I strongly prefer the latter. It makes me nervous not to have a true back- door to the type system (which we would lose if we dropped the levity- polymorphism from `unsafeCoerce#`). It should be easy enough to check for saturation in the desugarer. But, actually, there's a third option: * Allow silly uses of `unsafeCoerce#` to cause a panic. The user is clearly taking on the risk of a runtime crash with `unsafeCoerce#`. We could just say they also risk taking on a compile-time crash. In this case, I think the fix (the saturation check) is easy enough, but I don't feel strongly committed to eradicating a hard-to-fix panic if the user abuses the type system with such a low-level operation. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14561#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14561: Panic on levity polymorphic very unsafe coerce -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: | LevityPolymorphism 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 andrewthad): * cc: andrewthad (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14561#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14561: Panic on levity polymorphic very unsafe coerce -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: | LevityPolymorphism 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): There are lots of `unsafeCoerce#` in the GHCi debugger (`RtClosureInspect`) where we need to coerce unknown but pointed types into unpointed types like `MutVar#`. There's another instance of this kind of coercion in `newStablePtrPrimMVar` in base. I don't know of any places where we legitimately coerce between boxed and unboxed types, but I think it would be nice if we could retain the ability to do so, for debugging (e.g. printing out pointer values) & general hacking purposes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14561#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14561: Panic on levity polymorphic very unsafe coerce -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: | LevityPolymorphism 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 simonpj): I don't want "silly uses" of `unsafeCoerce#` to cause a panic. GHC should never panic. This ticket is about an un-saturated use of `unsafeCoerce#`; we can easily check for that. Simon M raises the question of coercing between boxed and unboxed types. That seems very dodgy: the GC now won't see that pointer. But I suppose if you want to print an address there is no other way to do so. Regardless, it's a separate point to the saturation one, which is the point of this ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14561#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14561: Panic on levity polymorphic very unsafe coerce
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.3
Resolution: | Keywords:
| LevityPolymorphism
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 Simon Peyton Jones

#14561: Panic on levity polymorphic very unsafe coerce
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.3
Resolution: | Keywords:
| LevityPolymorphism
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 Simon Peyton Jones

#14561: Panic on levity polymorphic very unsafe coerce -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: fixed | Keywords: | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | polykinds/T14561 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => polykinds/T14561 * resolution: => fixed Comment: The fix was easier than I thought: see comment:6 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14561#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14561: Panic on levity polymorphic very unsafe coerce
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner: (none)
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 8.3
Resolution: fixed | Keywords:
| LevityPolymorphism
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| polykinds/T14561
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones
participants (1)
-
GHC