summaryrefslogtreecommitdiff
path: root/testsuite/tests/typecheck/should_fail
diff options
context:
space:
mode:
authorsheaf <sam.derbyshire@gmail.com>2021-08-18 14:28:18 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-08-18 17:58:19 -0400
commit4a10f0ff487c6effee125bedca095a80f68045b7 (patch)
tree54f50dbe6c2419b410d39037cb28240ca1f13e97 /testsuite/tests/typecheck/should_fail
parentd9cf2ec8207e6c159815b22f1ed8dbdc08a2342d (diff)
downloadhaskell-4a10f0ff487c6effee125bedca095a80f68045b7.tar.gz
Don't look for TypeError in type family arguments
Changes checkUserTypeError to no longer look for custom type errors inside type family arguments. This means that a program such as foo :: F xyz (TypeError (Text "blah")) -> bar does not throw a type error at definition site. This means that more programs can be accepted, as the custom type error might disappear upon reducing the above type family F. This applies only to user-written type signatures, which are checked within checkValidType. Custom type errors in type family arguments continue to be reported when they occur in unsolved Wanted constraints. Fixes #20241
Diffstat (limited to 'testsuite/tests/typecheck/should_fail')
-rw-r--r--testsuite/tests/typecheck/should_fail/T20241b.hs28
-rw-r--r--testsuite/tests/typecheck/should_fail/T20241b.stderr16
-rw-r--r--testsuite/tests/typecheck/should_fail/all.T3
3 files changed, 46 insertions, 1 deletions
diff --git a/testsuite/tests/typecheck/should_fail/T20241b.hs b/testsuite/tests/typecheck/should_fail/T20241b.hs
new file mode 100644
index 0000000000..ced85b29d0
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T20241b.hs
@@ -0,0 +1,28 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeFamilies #-}
+
+module ShouldFail where
+
+import Data.Kind
+ ( Type, Constraint )
+import Data.Proxy
+ ( Proxy(..) )
+import GHC.TypeLits
+ ( TypeError, ErrorMessage(..) )
+
+-- Check that custom type errors are still detected when they are
+-- used at different kinds and applied to many arguments.
+
+foo :: ( ( TypeError (Text "Boom") :: (Type -> Type) -> Type -> Constraint ) IO ) a
+ => Proxy a -> ()
+foo Proxy = ()
+
+bar :: ( ( c :: Constraint -> Type -> Constraint )
+ ( ( ( TypeError (Text "Boom") :: (Type -> Type) -> Type -> Constraint )
+ IO
+ )
+ a
+ )
+ ) a
+ => Proxy a -> ()
+bar Proxy = ()
diff --git a/testsuite/tests/typecheck/should_fail/T20241b.stderr b/testsuite/tests/typecheck/should_fail/T20241b.stderr
new file mode 100644
index 0000000000..7b742e7905
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T20241b.stderr
@@ -0,0 +1,16 @@
+
+T20241b.hs:16:8: error:
+ • Boom
+ • In the type signature:
+ foo :: ((TypeError (Text "Boom") :: (Type -> Type)
+ -> Type -> Constraint) IO) a =>
+ Proxy a -> ()
+
+T20241b.hs:20:8: error:
+ • Boom
+ • In the type signature:
+ bar :: ((c :: Constraint
+ -> Type -> Constraint) (((TypeError (Text "Boom") :: (Type -> Type)
+ -> Type
+ -> Constraint) IO) a)) a =>
+ Proxy a -> ()
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index b573f9b7f6..155500ab9f 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -633,4 +633,5 @@ test('T19615', normal, compile_fail, [''])
test('T17817', normal, compile_fail, [''])
test('T17817_elab', normal, compile_fail, ['-fprint-typechecker-elaboration'])
test('T19978', normal, compile_fail, [''])
-test('T20122', normal, compile_fail, ['']) \ No newline at end of file
+test('T20122', normal, compile_fail, [''])
+test('T20241b', normal, compile_fail, [''])