[commit: ghc] wip/gadtpm: started adding some stuff in the testsuite (8a57cd7)
git at git.haskell.org
git at git.haskell.org
Mon Oct 12 15:29:59 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/gadtpm
Link : http://ghc.haskell.org/trac/ghc/changeset/8a57cd7414380afbe5f21810f0f2469f3071147b/ghc
>---------------------------------------------------------------
commit 8a57cd7414380afbe5f21810f0f2469f3071147b
Author: George Karachalias <george.karachalias at gmail.com>
Date: Mon Oct 12 17:09:04 2015 +0200
started adding some stuff in the testsuite
>---------------------------------------------------------------
8a57cd7414380afbe5f21810f0f2469f3071147b
testsuite/tests/{annotations => pmcheck}/Makefile | 0
.../{cabal/pkg02 => pmcheck/should_compile}/Makefile | 0
testsuite/tests/pmcheck/should_compile/T9951a.hs | 10 ++++++++++
testsuite/tests/pmcheck/should_compile/T9951a.stderr | 1 +
testsuite/tests/pmcheck/should_compile/T9951b.hs | 8 ++++++++
testsuite/tests/pmcheck/should_compile/T9951b.stderr | 9 +++++++++
testsuite/tests/pmcheck/should_compile/all.T | 18 ++++++++++++++++++
7 files changed, 46 insertions(+)
diff --git a/testsuite/tests/annotations/Makefile b/testsuite/tests/pmcheck/Makefile
similarity index 100%
copy from testsuite/tests/annotations/Makefile
copy to testsuite/tests/pmcheck/Makefile
diff --git a/testsuite/tests/cabal/pkg02/Makefile b/testsuite/tests/pmcheck/should_compile/Makefile
similarity index 100%
copy from testsuite/tests/cabal/pkg02/Makefile
copy to testsuite/tests/pmcheck/should_compile/Makefile
diff --git a/testsuite/tests/pmcheck/should_compile/T9951a.hs b/testsuite/tests/pmcheck/should_compile/T9951a.hs
new file mode 100644
index 0000000..30b6f56
--- /dev/null
+++ b/testsuite/tests/pmcheck/should_compile/T9951a.hs
@@ -0,0 +1,10 @@
+{-# OPTIONS_GHC -Wall #-}
+{-# LANGUAGE OverloadedLists #-}
+
+module T9951a where
+
+f :: [a] -> ()
+f x = case x of
+ [] -> ()
+ (_:_) -> ()
+
diff --git a/testsuite/tests/pmcheck/should_compile/T9951a.stderr b/testsuite/tests/pmcheck/should_compile/T9951a.stderr
new file mode 100644
index 0000000..c50b284
--- /dev/null
+++ b/testsuite/tests/pmcheck/should_compile/T9951a.stderr
@@ -0,0 +1 @@
+[1 of 1] Compiling T9951a ( T9951a.hs, T9951a.o )
diff --git a/testsuite/tests/pmcheck/should_compile/T9951b.hs b/testsuite/tests/pmcheck/should_compile/T9951b.hs
new file mode 100644
index 0000000..529731b
--- /dev/null
+++ b/testsuite/tests/pmcheck/should_compile/T9951b.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-# OPTIONS_GHC -Wall #-}
+
+module T9951b where
+
+f :: String -> Bool
+f "ab" = True
+
diff --git a/testsuite/tests/pmcheck/should_compile/T9951b.stderr b/testsuite/tests/pmcheck/should_compile/T9951b.stderr
new file mode 100644
index 0000000..17db80b
--- /dev/null
+++ b/testsuite/tests/pmcheck/should_compile/T9951b.stderr
@@ -0,0 +1,9 @@
+[1 of 1] Compiling T9951b ( T9951b.hs, T9951b.o )
+
+T9951b.hs:7:1: Warning:
+ Pattern match(es) are non-exhaustive
+ In an equation for ‘f’:
+ Patterns not matched:
+ ('a':_:_)
+ (t0:_) where t0 is not one of ['a']
+ []
diff --git a/testsuite/tests/pmcheck/should_compile/all.T b/testsuite/tests/pmcheck/should_compile/all.T
new file mode 100644
index 0000000..c1062fd
--- /dev/null
+++ b/testsuite/tests/pmcheck/should_compile/all.T
@@ -0,0 +1,18 @@
+# Tests for pattern match checker (coverage and exhaustiveness)
+
+# Just do the normal way...
+def f( name, opts ):
+ opts.only_ways = ['normal']
+
+setTestOpts(f)
+
+# Overloaded Lists
+test('T9951a', only_compiler_types(['ghc']), compile, ['-fwarn-incomplete-patterns'])
+
+# Overloaded Strings
+test('T9951b', only_compiler_types(['ghc']), compile, ['-fwarn-incomplete-patterns'])
+
+# other examples..
+# test('ds002', normal, compile, [''])
+# test('ds003', normal, compile, [''])
+
More information about the ghc-commits
mailing list