[commit: ghc] master: Changed OverLit warnings to work with negative literals (#13257) (3fdabe9)

git at git.haskell.org git at git.haskell.org
Mon Mar 6 22:26:32 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/3fdabe9873e311571f614d455d1b16bc3f4fdc0f/ghc

>---------------------------------------------------------------

commit 3fdabe9873e311571f614d455d1b16bc3f4fdc0f
Author: Rupert Horlick <ruperthorlick at gmail.com>
Date:   Mon Mar 6 13:43:34 2017 -0500

    Changed OverLit warnings to work with negative literals (#13257)
    
    Test Plan: Validate, check generated warnings
    
    Reviewers: austin, bgamari, dfeuer
    
    Reviewed By: bgamari, dfeuer
    
    Subscribers: dfeuer, thomie
    
    Differential Revision: https://phabricator.haskell.org/D3281


>---------------------------------------------------------------

3fdabe9873e311571f614d455d1b16bc3f4fdc0f
 compiler/deSugar/DsExpr.hs                           | 9 +++++++++
 compiler/deSugar/MatchLit.hs                         | 5 +++--
 testsuite/tests/deSugar/should_compile/T13257.hs     | 6 ++++++
 testsuite/tests/deSugar/should_compile/T13257.stderr | 3 +++
 testsuite/tests/deSugar/should_compile/all.T         | 1 +
 testsuite/tests/numeric/should_compile/T8542.stderr  | 4 ----
 6 files changed, 22 insertions(+), 6 deletions(-)

diff --git a/compiler/deSugar/DsExpr.hs b/compiler/deSugar/DsExpr.hs
index 28254c9..faf562e 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 2e9a523..6ed34f4 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 0000000..b9188df
--- /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 0000000..93412f1
--- /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 7694fb9..7a39b1e 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 f414382..699ba5d 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



More information about the ghc-commits mailing list