Internal error: ARR_WORDS object entered on ByteArray# & Unboxed Sum
Summary
The compiled program crashes at runtime. Either I am doing something terribly wrong with primops or there is a bug in GHC.
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedSums #-}
{-# LANGUAGE UnboxedTuples #-}
module Main (main) where
import GHC.Base
data MyArray t = MyArray (# t | ByteArray# #)
getBytes :: MyArray t -> ByteArray#
-- This would work on GHC versions < 9.0 when uncommented, but not on 9.0.1!
-- getBytes (MyArray (# | arr #)) = case runRW# (\s -> (# touch# arr s, arr #)) of (# _, r #) -> r
getBytes (MyArray (# | arr #)) = arr
getBytes _ = mkByteArray 13
-- Commenting out this NOINLINE pragma also makes it work successfully
{-# NOINLINE getBytes #-}
mkByteArray :: Double -> ByteArray#
mkByteArray (D# x) = case runRW#
( \s0 -> case newByteArray# 8# s0 of
(# s1, mba #) -> unsafeFreezeByteArray# mba ( writeDoubleArray# mba 0# x s1)
) of (# _, ba #) -> ba
main :: IO ()
main = print $ case getBytes x of a -> D# (indexDoubleArray# a 0#)
where
x :: MyArray Double
x = MyArray (# | mkByteArray 7 #)
Here is what I get:
$ cabal v2-run enter-words
Resolving dependencies...
Build profile: -w ghc-9.0.1 -O1
In order, the following will be built (use -v for more details):
- enter-words-0.1.0.0 (exe:enter-words) (configuration changed)
Configuring executable 'enter-words' for enter-words-0.1.0.0..
Preprocessing executable 'enter-words' for enter-words-0.1.0.0..
Building executable 'enter-words' for enter-words-0.1.0.0..
enter-words: internal error: ARR_WORDS object (0x42001060b8) entered!
(GHC version 9.0.1 for x86_64_unknown_linux)
Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug
Aborted (core dumped)
Maybe it's just me using incorrectly runRW#/newByteArray#/unsafeFreezeByteArray#
or unboxed sums?
I am sorry that I spotted it in my project two years ago,
but failed to write a small example program to report. Now this is more critical, because the workaround does not work anymore.
Steps to reproduce
Compile and run the program with GHC 8.4+
Expected behavior
The program is expected to output a single line "7.0
" and finish successfully.
Environment
- GHC version used: 8.4.4, 8.6.5, 8.8.4, 8.10.4, 9.0.1
Optional:
- Operating System: Ubuntu 20.04.2 LTS
- System Architecture: x86_64
Edited by Artem Chirkin