[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:StgCmmPrimPlease report this as a GHC bug: http://www.haskell.org/ghc/reportabug
Trac metadata
Trac field
Value
Version
8.5
Type
Bug
TypeOfFailure
OtherFailure
Priority
normal
Resolution
Unresolved
Component
Compiler
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Child items
...
Show closed items
Linked items
0
Link issues together to show that they're related or that one is blocking others.
Learn more.
{-# LANGUAGE MagicHash #-}{-# LANGUAGE UnboxedTuples #-}moduleLibwhereimportGHC.Exts(Int(..),byteArrayContents#,newPinnedByteArray#,unsafeCoerce#)importGHC.Ptr(Ptr(..))importGHC.ST(ST(..))newPinnedByteArray::Int->STs(Ptra)newPinnedByteArray(I#n#)=ST$\s#->casenewPinnedByteArray#n#s#of(#s2#,marr##)->(#s2#,Ptr(byteArrayContents#(unsafeCoerce#s#))#)
You're trying to coerce a state token to ByteArray#.
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.
[1 of 1] Compiling Lib ( Lib.hs, Lib.o )*** Core Lint warnings : in result of Desugar (after optimization) ***<no location info>: warning: In the expression: (# s2#_a13E, case case s#_a13D `cast` (UnsafeCo representational (State# s_a143) ByteArray# :: (State# s_a143 :: TYPE ('TupleRep '[])) ~R# (ByteArray# :: TYPE 'UnliftedRep)) of wild_Xb { __DEFAULT -> byteArrayContents# wild_Xb } of wild_Xb { __DEFAULT -> Ptr @ a_a144 wild_Xb } #) 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# (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:StgCmmPrimPlease report this as a GHC bug: http://www.haskell.org/ghc/reportabug