[commit: testsuite] master: Tests for nullary type classes (#7642) (1968572)
Simon Peyton Jones
simonpj at microsoft.com
Thu Mar 14 19:13:23 CET 2013
Repository : ssh://darcs.haskell.org//srv/darcs/testsuite
On branch : master
http://hackage.haskell.org/trac/ghc/changeset/19685729fb23860694ed433587efa0c1a822ea9b
>---------------------------------------------------------------
commit 19685729fb23860694ed433587efa0c1a822ea9b
Author: Krzysztof Gogolewski <krz.gogolewski at gmail.com>
Date: Mon Mar 11 13:32:58 2013 +0100
Tests for nullary type classes (#7642)
>---------------------------------------------------------------
tests/driver/T4437.hs | 3 ++-
tests/typecheck/should_fail/TcNoNullaryTC.hs | 4 ++++
tests/typecheck/should_fail/TcNoNullaryTC.stderr | 5 +++++
tests/typecheck/should_fail/TcNullaryTCFail.hs | 6 ++++++
tests/typecheck/should_fail/TcNullaryTCFail.stderr | 5 +++++
tests/typecheck/should_fail/all.T | 2 ++
tests/typecheck/should_run/TcNullaryTC.hs | 13 +++++++++++++
.../should_run/TcNullaryTC.stdout} | 0
tests/typecheck/should_run/all.T | 1 +
9 files changed, 38 insertions(+), 1 deletions(-)
diff --git a/tests/driver/T4437.hs b/tests/driver/T4437.hs
index 617484c..cb1d5f8 100644
--- a/tests/driver/T4437.hs
+++ b/tests/driver/T4437.hs
@@ -39,7 +39,8 @@ expectedGhcOnlyExtensions = [
"TypeHoles",
"OverloadedLists",
"EmptyCase",
- "AutoDeriveTypeable"]
+ "AutoDeriveTypeable",
+ "NullaryTypeClasses"]
expectedCabalOnlyExtensions :: [String]
expectedCabalOnlyExtensions = ["Generics",
diff --git a/tests/typecheck/should_fail/TcNoNullaryTC.hs b/tests/typecheck/should_fail/TcNoNullaryTC.hs
new file mode 100644
index 0000000..de5e443
--- /dev/null
+++ b/tests/typecheck/should_fail/TcNoNullaryTC.hs
@@ -0,0 +1,4 @@
+module NoNullaryTC where
+
+class A where
+ f :: a -> a
diff --git a/tests/typecheck/should_fail/TcNoNullaryTC.stderr b/tests/typecheck/should_fail/TcNoNullaryTC.stderr
new file mode 100644
index 0000000..9619004
--- /dev/null
+++ b/tests/typecheck/should_fail/TcNoNullaryTC.stderr
@@ -0,0 +1,5 @@
+
+TcNoNullaryTC.hs:3:1:
+ No parameters for class âAâ
+ (Use -XNullaryTypeClasses to allow no-parameter classes)
+ In the class declaration for âAâ
diff --git a/tests/typecheck/should_fail/TcNullaryTCFail.hs b/tests/typecheck/should_fail/TcNullaryTCFail.hs
new file mode 100644
index 0000000..b127300
--- /dev/null
+++ b/tests/typecheck/should_fail/TcNullaryTCFail.hs
@@ -0,0 +1,6 @@
+{-# LANGUAGE NullaryTypeClasses #-}
+module TcNullaryTCFail where
+
+class A
+instance A
+instance A
diff --git a/tests/typecheck/should_fail/TcNullaryTCFail.stderr b/tests/typecheck/should_fail/TcNullaryTCFail.stderr
new file mode 100644
index 0000000..1dd7ba2
--- /dev/null
+++ b/tests/typecheck/should_fail/TcNullaryTCFail.stderr
@@ -0,0 +1,5 @@
+
+TcNullaryTCFail.hs:5:10:
+ Duplicate instance declarations:
+ instance A -- Defined at TcNullaryTCFail.hs:5:10
+ instance A -- Defined at TcNullaryTCFail.hs:6:10
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index bb4d220..f1bc64f 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -301,3 +301,5 @@ test('T7734', normal, compile_fail, [''])
test('T7697', normal, compile_fail, [''])
test('T7696', normal, compile_fail, [''])
test('T7748a', normal, compile_fail, [''])
+test('TcNoNullaryTC', when(compiler_lt('ghc', '7.7'), skip), compile_fail, [''])
+test('TcNullaryTCFail', when(compiler_lt('ghc', '7.7'), skip), compile_fail, [''])
diff --git a/tests/typecheck/should_run/TcNullaryTC.hs b/tests/typecheck/should_run/TcNullaryTC.hs
new file mode 100644
index 0000000..a94d305
--- /dev/null
+++ b/tests/typecheck/should_run/TcNullaryTC.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE NullaryTypeClasses #-}
+
+module Main where
+
+class R where
+ f :: Int -> Int
+ g :: a -> a
+
+instance R where
+ f = (+1)
+ g = id
+
+main = print (g (f 0))
diff --git a/tests/codeGen/should_run/T5149.stdout b/tests/typecheck/should_run/TcNullaryTC.stdout
similarity index 100%
copy from tests/codeGen/should_run/T5149.stdout
copy to tests/typecheck/should_run/TcNullaryTC.stdout
diff --git a/tests/typecheck/should_run/all.T b/tests/typecheck/should_run/all.T
index 0049769..55d88ec 100755
--- a/tests/typecheck/should_run/all.T
+++ b/tests/typecheck/should_run/all.T
@@ -108,3 +108,4 @@ test('T6117', normal, compile_and_run, [''])
test('T5751', normal, compile_and_run, [''])
test('T5913', normal, compile_and_run, [''])
test('T7748', normal, compile_and_run, [''])
+test('TcNullaryTC', when(compiler_lt('ghc', '7.7'), skip), compile_and_run, [''])
More information about the ghc-commits
mailing list