[GHC] #15128: emitPrimOp: can't translate PrimOp

#15128: emitPrimOp: can't translate PrimOp -------------------------------------+------------------------------------- Reporter: tianxiaogu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 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: -------------------------------------+------------------------------------- Affected HEAD (GHC version 8.5.20180506) Reproduce: {{{ ghc -O bug.hs }}} Log: {{{ [1 of 1] Compiling Main ( bug.hs, bug.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.5.20180506 for x86_64-unknown-linux): emitPrimOp: can't translate PrimOp byteArrayContents# Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1162:37 in ghc:Outputable pprPanic, called at compiler/codeGen/StgCmmPrim.hs:943:12 in ghc:StgCmmPrim Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15128 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15128: emitPrimOp: can't translate PrimOp -------------------------------------+------------------------------------- Reporter: tianxiaogu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 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 tianxiaogu): * Attachment "bug.hs" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15128 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15128: emitPrimOp: can't translate PrimOp -------------------------------------+------------------------------------- Reporter: tianxiaogu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 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 osa1): Smaller reproducer: {{{#!haskell {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} module Lib where import GHC.Exts (Int (..), MutableByteArray#, byteArrayContents#, newPinnedByteArray#, unsafeCoerce#) import GHC.Ptr (Ptr (..)) import GHC.ST (ST (..)) data MByteArray s = MByteArray { unMBA :: MutableByteArray# s } newPinnedByteArray :: Int -> ST s (Ptr a, MByteArray s) newPinnedByteArray (I# n#) = ST $ \s# -> case newPinnedByteArray# n# s# of (# s2#, marr# #) -> (# s2#, ( Ptr (byteArrayContents# (unsafeCoerce# s#)), MByteArray marr# ) #) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15128#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15128: emitPrimOp: can't translate PrimOp -------------------------------------+------------------------------------- Reporter: tianxiaogu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 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 simonpj):
You're trying to coerce a state token to ByteArray#.
Which is certainly a bad thing to do. I wonder if we can produce a more civilised error, from Core Lint, perhaps? We should not unsafely coerce between types with different representations, and that might not be too hard to spot. Just by looking at the kind of the two types. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15128#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15128: emitPrimOp: can't translate PrimOp -------------------------------------+------------------------------------- Reporter: tianxiaogu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 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 osa1): Core Lint already catches this: {{{ From: State# s_a143 To: ByteArray# *** Core Lint warnings : in result of Simplifier *** <no location info>: warning: In the expression: byteArrayContents# (s#_a13D `cast` (UnsafeCo representational (State# s_a143) ByteArray# :: (State# s_a143 :: TYPE ('TupleRep '[])) ~R# (ByteArray# :: TYPE 'UnliftedRep))) Unsafe coercion: between values with different # of reps From: State# s_a143 To: ByteArray# *** Core Lint warnings : in result of Simplifier *** <no location info>: warning: In the expression: byteArrayContents# (eta_B1 `cast` (UnsafeCo representational (State# s_a143) ByteArray# :: (State# s_a143 :: TYPE ('TupleRep '[])) ~R# (ByteArray# :: TYPE 'UnliftedRep))) Unsafe coercion: between values with different # of reps From: State# s_a143 To: ByteArray# *** Core Lint warnings : in result of Simplifier *** <no location info>: warning: In the expression: byteArrayContents# (eta_B1 `cast` (UnsafeCo representational (State# s_a143) ByteArray# :: (State# s_a143 :: TYPE ('TupleRep '[])) ~R# (ByteArray# :: TYPE 'UnliftedRep))) Unsafe coercion: between values with different # of reps From: State# s_a143 To: ByteArray# *** Core Lint warnings : in result of Tidy Core *** <no location info>: warning: In the expression: byteArrayContents# (eta_B1 `cast` (UnsafeCo representational (State# s_a143) ByteArray# :: (State# s_a143 :: TYPE ('TupleRep '[])) ~R# (ByteArray# :: TYPE 'UnliftedRep))) Unsafe coercion: between values with different # of reps From: State# s_a143 To: ByteArray# *** Core Lint warnings : in result of CorePrep *** <no location info>: warning: In the expression: byteArrayContents# (eta_s1gf `cast` (UnsafeCo representational (State# s_a143) ByteArray# :: (State# s_a143 :: TYPE ('TupleRep '[])) ~R# (ByteArray# :: TYPE 'UnliftedRep))) Unsafe coercion: between values with different # of reps From: State# s_a143 To: ByteArray# ghc: panic! (the 'impossible' happened) (GHC version 8.4.2 for x86_64-unknown-linux): emitPrimOp: can't translate PrimOp byteArrayContents# Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in ghc:Outputable pprPanic, called at compiler/codeGen/StgCmmPrim.hs:882:12 in ghc:StgCmmPrim Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} So perhaps we can close this ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15128#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15128: emitPrimOp: can't translate PrimOp -------------------------------------+------------------------------------- Reporter: tianxiaogu | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 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 simonpj):
Core Lint already catches this:
Fine. That seems great. Yes, let's close as invalid. Mind you, complaining about `different # of reps` s a bit obscure. Perhaps `different runtime representations`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15128#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15128: emitPrimOp: can't translate PrimOp -------------------------------------+------------------------------------- Reporter: tianxiaogu | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: invalid | 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 osa1): * status: new => closed * resolution: => invalid -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15128#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC