diff --git a/compiler/deSugar/DsExpr.hs b/compiler/deSugar/DsExpr.hs index 28254c93b4a93af8089e2f30268ff75f1689ddbf..faf562e4284fcfc9a07202fd7f8c98b97f8986f3 100644 --- a/compiler/deSugar/DsExpr.hs +++ b/compiler/deSugar/DsExpr.hs @@ -271,6 +271,15 @@ dsExpr (HsWrap co_fn e) ; warnAboutIdentities dflags e' (exprType wrapped_e) ; return wrapped_e } +dsExpr (NegApp (L loc (HsOverLit lit@(OverLit { ol_val = HsIntegral src i }))) + neg_expr) + = do { expr' <- putSrcSpanDs loc $ do + { dflags <- getDynFlags + ; warnAboutOverflowedLiterals dflags + (lit { ol_val = HsIntegral src (-i) }) + ; dsOverLit' dflags lit } + ; dsSyntaxExpr neg_expr [expr'] } + dsExpr (NegApp expr neg_expr) = do { expr' <- dsLExpr expr ; dsSyntaxExpr neg_expr [expr'] } diff --git a/compiler/deSugar/MatchLit.hs b/compiler/deSugar/MatchLit.hs index 2e9a5235bf40e9635d3fcd29746b5bc76f1771fb..6ed34f42db3cb25518ea4da31b7f0ce917b97fa1 100644 --- a/compiler/deSugar/MatchLit.hs +++ b/compiler/deSugar/MatchLit.hs @@ -8,10 +8,11 @@ Pattern-matching literal patterns {-# LANGUAGE CPP, ScopedTypeVariables #-} -module MatchLit ( dsLit, dsOverLit, hsLitKey +module MatchLit ( dsLit, dsOverLit, dsOverLit', hsLitKey , tidyLitPat, tidyNPat , matchLiterals, matchNPlusKPats, matchNPats - , warnAboutIdentities, warnAboutEmptyEnumerations + , warnAboutIdentities, warnAboutOverflowedLiterals + , warnAboutEmptyEnumerations ) where #include "HsVersions.h" diff --git a/testsuite/tests/deSugar/should_compile/T13257.hs b/testsuite/tests/deSugar/should_compile/T13257.hs new file mode 100644 index 0000000000000000000000000000000000000000..b9188dfe3b6c6cc9b3a8193b3a36f4b6b88b301a --- /dev/null +++ b/testsuite/tests/deSugar/should_compile/T13257.hs @@ -0,0 +1,6 @@ +module T13257 where + + import Data.Int + + int8 = -128 :: Int8 + word = -1 :: Word diff --git a/testsuite/tests/deSugar/should_compile/T13257.stderr b/testsuite/tests/deSugar/should_compile/T13257.stderr new file mode 100644 index 0000000000000000000000000000000000000000..93412f1d477430c9f0ac97218f91809d997ab12c --- /dev/null +++ b/testsuite/tests/deSugar/should_compile/T13257.stderr @@ -0,0 +1,3 @@ + +T13257.hs:6:11: warning: [-Woverflowed-literals (in -Wdefault)] + Literal -1 is out of the Word range 0..18446744073709551615 diff --git a/testsuite/tests/deSugar/should_compile/all.T b/testsuite/tests/deSugar/should_compile/all.T index 7694fb9de77320376ff7b2a793f72008aa637901..7a39b1eed750ad6555ec95bbcea12388177e50d7 100644 --- a/testsuite/tests/deSugar/should_compile/all.T +++ b/testsuite/tests/deSugar/should_compile/all.T @@ -97,3 +97,4 @@ test('T12950', normal, compile, ['']) test('T13043', normal, compile, ['']) test('T13215', normal, compile, ['']) test('T13290', normal, compile, ['']) +test('T13257', normal, compile, ['']) diff --git a/testsuite/tests/numeric/should_compile/T8542.stderr b/testsuite/tests/numeric/should_compile/T8542.stderr index f4143821f6c923f3754365e907607812188df6db..699ba5d57327c67f0a743a88458c0a6fb153cbaa 100644 --- a/testsuite/tests/numeric/should_compile/T8542.stderr +++ b/testsuite/tests/numeric/should_compile/T8542.stderr @@ -1,8 +1,4 @@ -T8542.hs:6:6: warning: [-Woverflowed-literals (in -Wdefault)] - Literal 128 is out of the Int8 range -128..127 - If you are trying to write a large negative literal, use NegativeLiterals - T8542.hs:9:5: warning: [-Woverflowed-literals (in -Wdefault)] Literal 128 is out of the Int8 range -128..127 If you are trying to write a large negative literal, use NegativeLiterals