Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
-
d175aff8
by Sylvain Henry at 2025-08-12T10:01:31-04:00
3 changed files:
- + testsuite/tests/numeric/should_run/T18619.hs
- + testsuite/tests/numeric/should_run/T18619.stderr
- testsuite/tests/numeric/should_run/all.T
Changes:
1 | +module Main where
|
|
2 | + |
|
3 | +import Data.Bits
|
|
4 | + |
|
5 | +main :: IO ()
|
|
6 | +main = do
|
|
7 | + print $ Data.Bits.shiftL (1 :: Integer) ((-1) :: Int) |
1 | +T18619: Uncaught exception ghc-internal:GHC.Internal.Exception.Type.ArithException:
|
|
2 | + |
|
3 | +arithmetic overflow |
... | ... | @@ -87,3 +87,4 @@ test('T24066', normal, compile_and_run, ['']) |
87 | 87 | test('div01', normal, compile_and_run, [''])
|
88 | 88 | test('T24245', normal, compile_and_run, [''])
|
89 | 89 | test('T25653', normal, compile_and_run, [''])
|
90 | +test('T18619', exit_code(1), compile_and_run, ['']) |