summaryrefslogtreecommitdiff
path: root/testsuite/tests/typecheck/should_fail
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/typecheck/should_fail')
-rw-r--r--testsuite/tests/typecheck/should_fail/T18891a.hs13
-rw-r--r--testsuite/tests/typecheck/should_fail/T18891a.stderr12
-rw-r--r--testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr14
-rw-r--r--testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs23
-rw-r--r--testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr18
-rw-r--r--testsuite/tests/typecheck/should_fail/all.T2
6 files changed, 72 insertions, 10 deletions
diff --git a/testsuite/tests/typecheck/should_fail/T18891a.hs b/testsuite/tests/typecheck/should_fail/T18891a.hs
new file mode 100644
index 0000000000..d211fc94f2
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T18891a.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE GADTs, UnliftedNewtypes, StandaloneKindSignatures, RankNTypes, TypeFamilies, PolyKinds #-}
+
+module T18891 where
+
+import GHC.Exts( TYPE )
+
+newtype N1 :: forall k. TYPE k where
+ MkN1 :: N1 -> N1
+
+type N2 :: forall k. TYPE k
+newtype N2 :: forall k. TYPE k where
+ MkN2 :: N2 -> N2
+
diff --git a/testsuite/tests/typecheck/should_fail/T18891a.stderr b/testsuite/tests/typecheck/should_fail/T18891a.stderr
new file mode 100644
index 0000000000..881924c8a1
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T18891a.stderr
@@ -0,0 +1,12 @@
+
+T18891a.hs:8:4: error:
+ • A newtype constructor must have a return type of form T a1 ... an
+ MkN1 :: N1 -> N1
+ • In the definition of data constructor ‘MkN1’
+ In the newtype declaration for ‘N1’
+
+T18891a.hs:12:3: error:
+ • A newtype constructor must have a return type of form T a1 ... an
+ MkN2 :: N2 -> N2
+ • In the definition of data constructor ‘MkN2’
+ In the newtype declaration for ‘N2’
diff --git a/testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr b/testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr
index 05f3a935eb..d609c850b7 100644
--- a/testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr
+++ b/testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr
@@ -1,11 +1,5 @@
-UnliftedNewtypesFamilyKindFail2.hs:12:20:
- Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’
- In the first argument of ‘F’, namely ‘5’
- In the newtype instance declaration for ‘F’
-
-UnliftedNewtypesFamilyKindFail2.hs:12:31:
- Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’
- In the first argument of ‘F’, namely ‘5’
- In the type ‘(F 5)’
- In the definition of data constructor ‘MkF’
+UnliftedNewtypesFamilyKindFail2.hs:12:20: error:
+ • Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’
+ • In the first argument of ‘F’, namely ‘5’
+ In the newtype instance declaration for ‘F’
diff --git a/testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs b/testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs
new file mode 100644
index 0000000000..adac27fe90
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs
@@ -0,0 +1,23 @@
+{-# LANGUAGE UnliftedNewtypes #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE GADTs #-}
+
+module UnliftedNewtypesUnassociatedFamily where
+
+import GHC.Int (Int(I#))
+import GHC.Word (Word(W#))
+import GHC.Exts (Int#,Word#)
+import GHC.Exts (TYPE,RuntimeRep(LiftedRep,IntRep,WordRep,TupleRep))
+
+data family DF :: TYPE (r :: RuntimeRep)
+
+-- All these fail: see #18891 and !4419
+-- See Note [Kind inference for data family instances]
+-- in GHC.Tc.TyCl.Instance
+newtype instance DF = MkDF1a Int#
+newtype instance DF = MkDF2a Word#
+newtype instance DF = MkDF3a (# Int#, Word# #)
diff --git a/testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr b/testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr
new file mode 100644
index 0000000000..972f873e62
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr
@@ -0,0 +1,18 @@
+
+UnliftedNewtypesUnassociatedFamilyFail.hs:21:30: error:
+ • Expecting a lifted type, but ‘Int#’ is unlifted
+ • In the type ‘Int#’
+ In the definition of data constructor ‘MkDF1a’
+ In the newtype instance declaration for ‘DF’
+
+UnliftedNewtypesUnassociatedFamilyFail.hs:22:30: error:
+ • Expecting a lifted type, but ‘Word#’ is unlifted
+ • In the type ‘Word#’
+ In the definition of data constructor ‘MkDF2a’
+ In the newtype instance declaration for ‘DF’
+
+UnliftedNewtypesUnassociatedFamilyFail.hs:23:30: error:
+ • Expecting a lifted type, but ‘(# Int#, Word# #)’ is unlifted
+ • In the type ‘(# Int#, Word# #)’
+ In the definition of data constructor ‘MkDF3a’
+ In the newtype instance declaration for ‘DF’
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 958811d428..913d6d8029 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -546,6 +546,7 @@ test('UnliftedNewtypesConstraintFamily', normal, compile_fail, [''])
test('UnliftedNewtypesMismatchedKind', normal, compile_fail, [''])
test('UnliftedNewtypesMismatchedKindRecord', normal, compile_fail, [''])
test('UnliftedNewtypesMultiFieldGadt', normal, compile_fail, [''])
+test('UnliftedNewtypesUnassociatedFamilyFail', normal, compile_fail, [''])
test('T13834', normal, compile_fail, [''])
test('T17077', normal, compile_fail, [''])
test('T16512a', normal, compile_fail, [''])
@@ -591,3 +592,4 @@ test('T18640c', normal, compile_fail, [''])
test('T10709', normal, compile_fail, [''])
test('T10709b', normal, compile_fail, [''])
test('GivenForallLoop', normal, compile_fail, [''])
+test('T18891a', normal, compile_fail, [''])