[commit: ghc] master: Add tests for #11391 (f0c4e46)
git at git.haskell.org
git at git.haskell.org
Thu Jan 14 11:44:04 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/f0c4e460ee0dad372d5b896a03cdac9666026174/ghc
>---------------------------------------------------------------
commit f0c4e460ee0dad372d5b896a03cdac9666026174
Author: Ben Gamari <ben at smart-cactus.org>
Date: Thu Jan 14 11:27:37 2016 +0100
Add tests for #11391
>---------------------------------------------------------------
f0c4e460ee0dad372d5b896a03cdac9666026174
.../tests/typecheck/should_fail/CustomTypeErrors04.hs | 14 ++++++++++++++
.../tests/typecheck/should_fail/CustomTypeErrors04.stderr | 5 +++++
.../tests/typecheck/should_fail/CustomTypeErrors05.hs | 14 ++++++++++++++
.../tests/typecheck/should_fail/CustomTypeErrors05.stderr | 5 +++++
testsuite/tests/typecheck/should_fail/all.T | 2 ++
5 files changed, 40 insertions(+)
diff --git a/testsuite/tests/typecheck/should_fail/CustomTypeErrors04.hs b/testsuite/tests/typecheck/should_fail/CustomTypeErrors04.hs
new file mode 100644
index 0000000..d1957bf
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/CustomTypeErrors04.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE TypeInType, TypeFamilies, UndecidableInstances #-}
+{-# LANGUAGE UndecidableInstances #-}
+
+-- The "bad case" in #11391
+module CustomTypeErrors04 where
+
+import Data.Kind
+import GHC.TypeLits (TypeError, ErrorMessage(..))
+
+type family Resolve (t :: Type -> Type) :: Type -> Type where
+ Resolve _ = TypeError (Text "ERROR")
+
+testNOTOK1 :: Resolve [] Int
+testNOTOK1 = ()
diff --git a/testsuite/tests/typecheck/should_fail/CustomTypeErrors04.stderr b/testsuite/tests/typecheck/should_fail/CustomTypeErrors04.stderr
new file mode 100644
index 0000000..9bec37b
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/CustomTypeErrors04.stderr
@@ -0,0 +1,5 @@
+
+CustomTypeErrors04.hs:14:14: error:
+ • ERROR
+ • In the expression: ()
+ In an equation for ‘testNOTOK1’: testNOTOK1 = ()
diff --git a/testsuite/tests/typecheck/should_fail/CustomTypeErrors05.hs b/testsuite/tests/typecheck/should_fail/CustomTypeErrors05.hs
new file mode 100644
index 0000000..5a15b6f
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/CustomTypeErrors05.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE TypeInType, TypeFamilies, UndecidableInstances #-}
+{-# LANGUAGE UndecidableInstances #-}
+
+-- The "tricky case" in #11391
+module CustomTypeErrors05 where
+
+import Data.Kind
+import GHC.TypeLits (TypeError, ErrorMessage(..))
+
+type family Resolve (t :: Type -> Type) :: Type -> Type where
+ Resolve _ = TypeError (Text "ERROR")
+
+testNOTOK2 :: Resolve [] Int
+testNOTOK2 = 1
diff --git a/testsuite/tests/typecheck/should_fail/CustomTypeErrors05.stderr b/testsuite/tests/typecheck/should_fail/CustomTypeErrors05.stderr
new file mode 100644
index 0000000..3164c86
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/CustomTypeErrors05.stderr
@@ -0,0 +1,5 @@
+
+CustomTypeErrors05.hs:14:14: error:
+ • ERROR
+ • In the expression: 1
+ In an equation for ‘testNOTOK2’: testNOTOK2 = 1
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 753708d..9aef820 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -394,6 +394,8 @@ test('T10971d', extra_clean(['T10971c.hi', 'T10971c.o']), multimod_compile_fail,
test('CustomTypeErrors01', normal, compile_fail, [''])
test('CustomTypeErrors02', normal, compile_fail, [''])
test('CustomTypeErrors03', normal, compile_fail, [''])
+test('CustomTypeErrors04', normal, compile_fail, [''])
+test('CustomTypeErrors05', normal, compile_fail, [''])
test('T11112', normal, compile_fail, [''])
test('ClassOperator', normal, compile_fail, [''])
test('T11274', normal, compile_fail, [''])
More information about the ghc-commits
mailing list