Skip to content
Snippets Groups Projects
Commit 9f9fab15 authored by Ben Gamari's avatar Ben Gamari Committed by Marge Bot
Browse files

testsuite: Add test for #19645

parent 721ea018
No related branches found
No related tags found
No related merge requests found
{-# 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 #)
7.0
......@@ -26,3 +26,4 @@ test('T12711', only_ways(['ghci']), ghci_script, ['T12711.script'])
test('UbxSumLevPoly', normal, compile, ['-Wno-overlapping-patterns'])
test('T14051', normal, multi_compile, ['T14051.hs', [('T14051a.hs', '')], '-O2 -v0'])
test('T19645', normal, compile_and_run, [''])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment