Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
-
0959d4bc
by Andreas Klebinger at 2025-09-10T10:44:12-04:00
2 changed files:
Changes:
1 | +module M where
|
|
2 | + |
|
3 | +import GHC.Exts ( Any )
|
|
4 | +import Unsafe.Coerce ( unsafeCoerce )
|
|
5 | + |
|
6 | +data Sigma = MkT Any
|
|
7 | + |
|
8 | +testSubList :: Maybe Bool -> Sigma -> Sigma
|
|
9 | +testSubList (Just x) final = {-# SCC "y" #-} (
|
|
10 | + let x' = seq x ()
|
|
11 | + in case testSubList Nothing final of
|
|
12 | + MkT w -> {-# SCC "x" #-}
|
|
13 | + (unsafeCoerce MkT (konst x' myHead (unsafeCoerce w))))
|
|
14 | +testSubList Nothing final = final
|
|
15 | + |
|
16 | +myHead :: [a] -> a
|
|
17 | +myHead (x:_) = x
|
|
18 | + |
|
19 | +konst :: () -> ([a] -> a) -> [a] -> a
|
|
20 | +konst _ x = x
|
|
21 | +{-# OPAQUE konst #-} |
... | ... | @@ -20,3 +20,4 @@ test('T14931', [test_opts, unless(have_dynamic(), skip)], |
20 | 20 | test('T15108', [test_opts], compile, ['-O -prof -fprof-auto'])
|
21 | 21 | test('T19894', [test_opts, extra_files(['T19894'])], multimod_compile, ['Main', '-v0 -O2 -prof -fprof-auto -iT19894'])
|
22 | 22 | test('T20938', [test_opts], compile, ['-O -prof'])
|
23 | +test('T26056', [test_opts], compile, ['-O -prof']) |