[commit: testsuite] master: Add a test for T7895 (literal overflow) (696047f)

Ian Lynagh igloo at ghc.haskell.org
Wed Jul 31 21:11:25 CEST 2013


Repository : http://darcs.haskell.org/ghc.git/

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/696047f3a103b53c8283e67df767503fc2f9dc2f

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

commit 696047f3a103b53c8283e67df767503fc2f9dc2f
Author: Ian Lynagh <ian at well-typed.com>
Date:   Wed Jul 31 18:49:59 2013 +0100

    Add a test for T7895 (literal overflow)

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

 tests/numeric/should_compile/T7895.hs     |   26 ++++++++++++++++++++++++++
 tests/numeric/should_compile/T7895.stderr |    4 ++++
 tests/numeric/should_compile/all.T        |    1 +
 3 files changed, 31 insertions(+)

diff --git a/tests/numeric/should_compile/T7895.hs b/tests/numeric/should_compile/T7895.hs
new file mode 100644
index 0000000..e5dbfc9
--- /dev/null
+++ b/tests/numeric/should_compile/T7895.hs
@@ -0,0 +1,26 @@
+
+{-# LANGUAGE NegativeLiterals #-}
+
+module T7895 where
+
+import Data.Int
+import Data.Word
+
+v1 :: Word8
+v1 = 300
+
+v2 :: Int8
+v2 = -129
+
+v3 :: Int8
+v3 = -128
+
+v4 :: Int8
+v4 = -127
+
+v5 :: Int8
+v5 = -5
+
+v6 :: Int8
+v6 = 127
+
diff --git a/tests/numeric/should_compile/T7895.stderr b/tests/numeric/should_compile/T7895.stderr
new file mode 100644
index 0000000..b72faea
--- /dev/null
+++ b/tests/numeric/should_compile/T7895.stderr
@@ -0,0 +1,4 @@
+
+T7895.hs:10:6: Warning: Literal 300 of type Word8 overflows
+
+T7895.hs:13:6: Warning: Literal -129 of type Int8 overflows
diff --git a/tests/numeric/should_compile/all.T b/tests/numeric/should_compile/all.T
index 3e8d4d3..27a9242 100644
--- a/tests/numeric/should_compile/all.T
+++ b/tests/numeric/should_compile/all.T
@@ -1 +1,2 @@
 test('T7116', normal, run_command, ['$MAKE -s --no-print-directory T7116'])
+test('T7895', normal, compile, [''])






More information about the ghc-commits mailing list