summaryrefslogtreecommitdiff
path: root/testsuite/tests
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests')
-rw-r--r--testsuite/tests/dependent/should_fail/T15859a.stderr12
-rw-r--r--testsuite/tests/impredicative/icfp20-fail.stderr9
-rw-r--r--testsuite/tests/indexed-types/should_fail/T8518.stderr23
-rw-r--r--testsuite/tests/typecheck/should_compile/PolytypeDecomp.stderr10
-rw-r--r--testsuite/tests/typecheck/should_compile/T12427a.stderr9
-rw-r--r--testsuite/tests/typecheck/should_compile/T19682.hs36
-rw-r--r--testsuite/tests/typecheck/should_compile/T19682b.hs17
-rw-r--r--testsuite/tests/typecheck/should_compile/all.T2
-rw-r--r--testsuite/tests/typecheck/should_compile/tc214.stderr18
-rw-r--r--testsuite/tests/typecheck/should_fail/T10619.stderr14
-rw-r--r--testsuite/tests/typecheck/should_fail/T10709.stderr43
-rw-r--r--testsuite/tests/typecheck/should_fail/T10715b.stderr7
-rw-r--r--testsuite/tests/typecheck/should_fail/T12563.stderr15
-rw-r--r--testsuite/tests/typecheck/should_fail/T13909.stderr2
-rw-r--r--testsuite/tests/typecheck/should_fail/T14618.stderr2
-rw-r--r--testsuite/tests/typecheck/should_fail/T14904a.stderr2
-rw-r--r--testsuite/tests/typecheck/should_fail/T3592.stderr9
-rw-r--r--testsuite/tests/typecheck/should_fail/T7264.stderr2
-rw-r--r--testsuite/tests/typecheck/should_fail/T8142.stderr12
19 files changed, 181 insertions, 63 deletions
diff --git a/testsuite/tests/dependent/should_fail/T15859a.stderr b/testsuite/tests/dependent/should_fail/T15859a.stderr
index 1fdac765f2..491733c7b9 100644
--- a/testsuite/tests/dependent/should_fail/T15859a.stderr
+++ b/testsuite/tests/dependent/should_fail/T15859a.stderr
@@ -1,6 +1,8 @@
-T15859a.hs:19:5: error:
- • Cannot apply expression of type ‘KindOf A’
- to a visible type argument ‘Int’
- • In the expression: (undefined :: KindOf A) @Int
- In an equation for ‘a’: a = (undefined :: KindOf A) @Int
+T15859a.hs:19:26: error:
+ • Expected kind ‘k0’, but ‘A’ has kind ‘forall k -> k -> *’
+ Cannot instantiate unification variable ‘k0’
+ with a kind involving polytypes: forall k -> k -> *
+ • In the first argument of ‘KindOf’, namely ‘A’
+ In an expression type signature: KindOf A
+ In the expression: undefined :: KindOf A
diff --git a/testsuite/tests/impredicative/icfp20-fail.stderr b/testsuite/tests/impredicative/icfp20-fail.stderr
index c9e06b10cc..ebe54ba6e3 100644
--- a/testsuite/tests/impredicative/icfp20-fail.stderr
+++ b/testsuite/tests/impredicative/icfp20-fail.stderr
@@ -10,14 +10,17 @@ icfp20-fail.hs:20:10: error:
auto'1 :: SId -> b -> b (bound at icfp20-fail.hs:20:1)
icfp20-fail.hs:23:9: error:
- • Couldn't match expected type ‘a0’
+ • Couldn't match expected type ‘a’
with actual type ‘SId -> b0 -> b0’
- Cannot instantiate unification variable ‘a0’
+ Cannot equate type variable ‘a’
with a type involving polytypes: SId -> b0 -> b0
+ ‘a’ is a rigid type variable bound by
+ the inferred type of a6 :: a
+ at icfp20-fail.hs:23:1-14
• In the first argument of ‘id’, namely ‘auto'2’
In the expression: id auto'2
In an equation for ‘a6’: a6 = id auto'2
- • Relevant bindings include a6 :: a0 (bound at icfp20-fail.hs:23:1)
+ • Relevant bindings include a6 :: a (bound at icfp20-fail.hs:23:1)
icfp20-fail.hs:26:16: error:
• Couldn't match type ‘SId’ with ‘b -> b’
diff --git a/testsuite/tests/indexed-types/should_fail/T8518.stderr b/testsuite/tests/indexed-types/should_fail/T8518.stderr
index 89ba8308a1..1f244f9ee2 100644
--- a/testsuite/tests/indexed-types/should_fail/T8518.stderr
+++ b/testsuite/tests/indexed-types/should_fail/T8518.stderr
@@ -1,9 +1,10 @@
T8518.hs:14:18: error:
- • Couldn't match type: F c
- with: Z c -> B c -> F c
- arising from a use of ‘rpt’
- • In the expression: rpt (4 :: Int) c z b
+ • Couldn't match expected type: Z c -> B c -> Maybe (F c)
+ with actual type: F c
+ • The function ‘rpt’ is applied to four value arguments,
+ but its type ‘Int -> c -> F c’ has only two
+ In the expression: rpt (4 :: Int) c z b
In an equation for ‘callCont’:
callCont c z b
= rpt (4 :: Int) c z b
@@ -15,3 +16,17 @@ T8518.hs:14:18: error:
z :: Z c (bound at T8518.hs:14:12)
c :: c (bound at T8518.hs:14:10)
callCont :: c -> Z c -> B c -> Maybe (F c) (bound at T8518.hs:14:1)
+
+T8518.hs:16:9: error:
+ • Couldn't match type: F t1
+ with: Z t1 -> B t1 -> F t1
+ Expected: t -> t1 -> F t1
+ Actual: t -> t1 -> Z t1 -> B t1 -> F t1
+ • In an equation for ‘callCont’:
+ callCont c z b
+ = rpt (4 :: Int) c z b
+ where
+ rpt 0 c' z' b' = fromJust (fst <$> (continue c' z' b'))
+ rpt i c' z' b' = let ... in rpt (i - 1) c''
+ • Relevant bindings include
+ rpt :: t -> t1 -> F t1 (bound at T8518.hs:16:9)
diff --git a/testsuite/tests/typecheck/should_compile/PolytypeDecomp.stderr b/testsuite/tests/typecheck/should_compile/PolytypeDecomp.stderr
index 0f1fd3e6c2..bdfddb70a1 100644
--- a/testsuite/tests/typecheck/should_compile/PolytypeDecomp.stderr
+++ b/testsuite/tests/typecheck/should_compile/PolytypeDecomp.stderr
@@ -8,3 +8,13 @@ PolytypeDecomp.hs:30:17: error:
• In the expression: x
In the first argument of ‘myLength’, namely ‘[x, f]’
In the expression: myLength [x, f]
+
+PolytypeDecomp.hs:30:19: error:
+ • Couldn't match type ‘a0’ with ‘[forall a. Maybe a]’
+ Expected: Id a0
+ Actual: [forall a. F [a]]
+ Cannot instantiate unification variable ‘a0’
+ with a type involving polytypes: [forall a. Maybe a]
+ • In the expression: f
+ In the first argument of ‘myLength’, namely ‘[x, f]’
+ In the expression: myLength [x, f]
diff --git a/testsuite/tests/typecheck/should_compile/T12427a.stderr b/testsuite/tests/typecheck/should_compile/T12427a.stderr
index 84f330e717..af229a725d 100644
--- a/testsuite/tests/typecheck/should_compile/T12427a.stderr
+++ b/testsuite/tests/typecheck/should_compile/T12427a.stderr
@@ -2,6 +2,8 @@
T12427a.hs:17:29: error:
• Couldn't match expected type ‘p’
with actual type ‘(forall b. [b] -> [b]) -> Int’
+ Cannot equate type variable ‘p’
+ with a type involving polytypes: (forall b. [b] -> [b]) -> Int
‘p’ is a rigid type variable bound by
the inferred type of h11 :: T -> p
at T12427a.hs:17:1-29
@@ -12,10 +14,13 @@ T12427a.hs:17:29: error:
h11 :: T -> p (bound at T12427a.hs:17:1)
T12427a.hs:28:6: error:
- • Couldn't match expected type ‘p0’
+ • Couldn't match expected type ‘p’
with actual type ‘(forall b. [b] -> [b]) -> Int’
- Cannot instantiate unification variable ‘p0’
+ Cannot equate type variable ‘p’
with a type involving polytypes: (forall b. [b] -> [b]) -> Int
+ ‘p’ is a rigid type variable bound by
+ the inferred type of x1 :: p
+ at T12427a.hs:28:1-19
• In the pattern: T1 _ x1
In a pattern binding: T1 _ x1 = undefined
diff --git a/testsuite/tests/typecheck/should_compile/T19682.hs b/testsuite/tests/typecheck/should_compile/T19682.hs
new file mode 100644
index 0000000000..bd59465ae1
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T19682.hs
@@ -0,0 +1,36 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeOperators #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE UndecidableSuperClasses #-}
+module T19682 where
+
+import Data.Kind
+import Data.Proxy
+
+convert :: (AllEq xs ys) => Proxy xs -> Proxy ys
+convert p = Proxy
+
+-- Works with ghc up to 9.0. Fails with ghc 9.2.
+test :: Proxy '[Char, Bool] -> ()
+test xs = const () (convert xs)
+
+class (AllEqF xs ys, SameShapeAs xs ys) => AllEq (xs :: [a]) (ys :: [a])
+instance (AllEqF xs ys, SameShapeAs xs ys) => AllEq xs ys
+
+type family SameShapeAs (xs :: [a]) (ys :: [a]) :: Constraint where
+ SameShapeAs '[] ys = (ys ~ '[])
+ SameShapeAs (x : xs) ys = (ys ~ (Head ys : Tail ys))
+
+type family AllEqF (xs :: [a]) (ys :: [a]) :: Constraint where
+ AllEqF '[] '[] = ()
+ AllEqF (x : xs) (y : ys) = (x ~ y, AllEq xs ys)
+
+type family Head (xs :: [a]) :: a where
+ Head (x : xs) = x
+
+type family Tail (xs :: [a]) :: [a] where
+ Tail (x : xs) = xs
diff --git a/testsuite/tests/typecheck/should_compile/T19682b.hs b/testsuite/tests/typecheck/should_compile/T19682b.hs
new file mode 100644
index 0000000000..f0ba98a99b
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T19682b.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE TypeFamilies #-}
+
+module T19682b where
+
+type family Arg x where
+ Arg (a -> b) = a
+
+type family Res x where
+ Res (a -> b) = b
+
+class C a
+instance C (a -> b)
+
+f :: (C x, x ~ (Arg x -> Res x)) => x
+f = undefined
+
+g = f
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 8183fe06a7..9cd7c732ca 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -721,6 +721,8 @@ test('T18023', normal, compile, [''])
test('T18036', normal, compile, [''])
test('T18036a', normal, compile, [''])
test('T18036b', normal, compile, [''])
+test('T19682', normal, compile, [''])
+test('T19682b', normal, compile, [''])
test('T17873', normal, compile, [''])
test('T18129', expect_broken(18129), compile, [''])
test('T18185', normal, compile, [''])
diff --git a/testsuite/tests/typecheck/should_compile/tc214.stderr b/testsuite/tests/typecheck/should_compile/tc214.stderr
new file mode 100644
index 0000000000..ea5cc8d93c
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/tc214.stderr
@@ -0,0 +1,18 @@
+
+tc214.hs:19:1: warning: [-Woverlapping-patterns (in -Wdefault)]
+ Pattern match has inaccessible right hand side
+ In an equation for ‘bar2’: bar2 (F2 _) = ...
+
+tc214.hs:19:7: warning: [-Winaccessible-code (in -Wdefault)]
+ • Couldn't match type ‘a’ with ‘forall a1. a1’
+ Cannot equate type variable ‘a’
+ with a type involving polytypes: forall a1. a1
+ ‘a’ is a rigid type variable bound by
+ a pattern with constructor: F2 :: forall a. a -> Foo2 [a],
+ in an equation for ‘bar2’
+ at tc214.hs:19:7-10
+ Inaccessible code in
+ a pattern with constructor: F2 :: forall a. a -> Foo2 [a],
+ in an equation for ‘bar2’
+ • In the pattern: F2 _
+ In an equation for ‘bar2’: bar2 (F2 _) = ()
diff --git a/testsuite/tests/typecheck/should_fail/T10619.stderr b/testsuite/tests/typecheck/should_fail/T10619.stderr
index c26e550f17..6f584b90db 100644
--- a/testsuite/tests/typecheck/should_fail/T10619.stderr
+++ b/testsuite/tests/typecheck/should_fail/T10619.stderr
@@ -19,11 +19,13 @@ T10619.hs:10:14: error:
\ y -> y
T10619.hs:14:15: error:
- • Couldn't match type ‘p’ with ‘forall a. a -> a’
- Expected: p -> p
+ • Couldn't match type ‘p2’ with ‘forall a. a -> a’
+ Expected: p2 -> p2
Actual: (forall a. a -> a) -> forall b. b -> b
- ‘p’ is a rigid type variable bound by
- the inferred type of bar :: p2 -> p -> p
+ Cannot equate type variable ‘p2’
+ with a type involving polytypes: forall a. a -> a
+ ‘p2’ is a rigid type variable bound by
+ the inferred type of bar :: p -> p2 -> p2
at T10619.hs:(12,1)-(14,66)
• In the expression:
(\ x -> x) :: (forall a. a -> a) -> forall b. b -> b
@@ -39,7 +41,7 @@ T10619.hs:14:15: error:
else
((\ x -> x) :: (forall a. a -> a) -> forall b. b -> b)
• Relevant bindings include
- bar :: p2 -> p -> p (bound at T10619.hs:12:1)
+ bar :: p -> p2 -> p2 (bound at T10619.hs:12:1)
T10619.hs:17:13: error:
• Couldn't match type ‘p0’ with ‘forall a. a -> a’
@@ -54,6 +56,8 @@ T10619.hs:20:14: error:
• Couldn't match type ‘p’ with ‘forall a. a -> a’
Expected: p -> p
Actual: (forall a. a -> a) -> forall b. b -> b
+ Cannot equate type variable ‘p’
+ with a type involving polytypes: forall a. a -> a
‘p’ is a rigid type variable bound by
the inferred type of quux :: Bool -> p -> p
at T10619.hs:(19,1)-(20,64)
diff --git a/testsuite/tests/typecheck/should_fail/T10709.stderr b/testsuite/tests/typecheck/should_fail/T10709.stderr
index 16429ea467..aa4d505bfc 100644
--- a/testsuite/tests/typecheck/should_fail/T10709.stderr
+++ b/testsuite/tests/typecheck/should_fail/T10709.stderr
@@ -1,34 +1,43 @@
T10709.hs:6:21: error:
- • Couldn't match type ‘a4’ with ‘(forall a. IO a -> IO a) -> IO a5’
- Expected: a4 -> IO a5
- Actual: ((forall a. IO a -> IO a) -> IO a5) -> IO a5
- Cannot instantiate unification variable ‘a4’
- with a type involving polytypes: (forall a. IO a -> IO a) -> IO a5
+ • Couldn't match type ‘a’
+ with ‘(forall a3. IO a3 -> IO a3) -> IO a2’
+ Expected: a -> IO a2
+ Actual: ((forall a. IO a -> IO a) -> IO a2) -> IO a2
+ Cannot equate type variable ‘a’
+ with a type involving polytypes:
+ (forall a3. IO a3 -> IO a3) -> IO a2
+ ‘a’ is a rigid type variable bound by
+ the inferred type of x1 :: a -> IO [a2]
+ at T10709.hs:6:1-24
• In the second argument of ‘(.)’, namely ‘mask’
In the expression: replicateM 2 . mask
In an equation for ‘x1’: x1 = replicateM 2 . mask
• Relevant bindings include
- x1 :: a4 -> IO [a5] (bound at T10709.hs:6:1)
+ x1 :: a -> IO [a2] (bound at T10709.hs:6:1)
T10709.hs:7:22: error:
- • Couldn't match type ‘a2’ with ‘(forall a. IO a -> IO a) -> IO a3’
- Expected: a2 -> IO a3
- Actual: ((forall a. IO a -> IO a) -> IO a3) -> IO a3
- Cannot instantiate unification variable ‘a2’
- with a type involving polytypes: (forall a. IO a -> IO a) -> IO a3
+ • Couldn't match type ‘a1’
+ with ‘(forall a2. IO a2 -> IO a2) -> IO a’
+ Expected: a1 -> IO a
+ Actual: ((forall a1. IO a1 -> IO a1) -> IO a) -> IO a
+ Cannot instantiate unification variable ‘a1’
+ with a type involving polytypes:
+ (forall a2. IO a2 -> IO a2) -> IO a
• In the second argument of ‘(.)’, namely ‘mask’
In the expression: (replicateM 2 . mask) undefined
In an equation for ‘x2’: x2 = (replicateM 2 . mask) undefined
- • Relevant bindings include x2 :: IO [a3] (bound at T10709.hs:7:1)
+ • Relevant bindings include x2 :: IO [a] (bound at T10709.hs:7:1)
T10709.hs:8:22: error:
- • Couldn't match type ‘a0’ with ‘(forall a. IO a -> IO a) -> IO a1’
- Expected: a0 -> IO a1
- Actual: ((forall a. IO a -> IO a) -> IO a1) -> IO a1
+ • Couldn't match type ‘a0’
+ with ‘(forall a2. IO a2 -> IO a2) -> IO a’
+ Expected: a0 -> IO a
+ Actual: ((forall a1. IO a1 -> IO a1) -> IO a) -> IO a
Cannot instantiate unification variable ‘a0’
- with a type involving polytypes: (forall a. IO a -> IO a) -> IO a1
+ with a type involving polytypes:
+ (forall a2. IO a2 -> IO a2) -> IO a
• In the second argument of ‘(.)’, namely ‘mask’
In the first argument of ‘($)’, namely ‘(replicateM 2 . mask)’
In the expression: (replicateM 2 . mask) $ undefined
- • Relevant bindings include x3 :: IO [a1] (bound at T10709.hs:8:1)
+ • Relevant bindings include x3 :: IO [a] (bound at T10709.hs:8:1)
diff --git a/testsuite/tests/typecheck/should_fail/T10715b.stderr b/testsuite/tests/typecheck/should_fail/T10715b.stderr
index 99875bbcf5..6eb2f698bd 100644
--- a/testsuite/tests/typecheck/should_fail/T10715b.stderr
+++ b/testsuite/tests/typecheck/should_fail/T10715b.stderr
@@ -1,12 +1,9 @@
T10715b.hs:7:7: error:
- • Couldn't match representation of type ‘b’ with that of ‘[b]’
+ • Couldn't match representation of type ‘b0’ with that of ‘[b0]’
arising from a use of ‘coerce’
- ‘b’ is a rigid type variable bound by
- the inferred type of foo :: [b] -> b
- at T10715b.hs:7:1-28
• In the first argument of ‘asTypeOf’, namely ‘coerce’
In the expression: coerce `asTypeOf` head
In an equation for ‘foo’: foo = coerce `asTypeOf` head
• Relevant bindings include
- foo :: [b] -> b (bound at T10715b.hs:7:1)
+ foo :: [b0] -> b0 (bound at T10715b.hs:7:1)
diff --git a/testsuite/tests/typecheck/should_fail/T12563.stderr b/testsuite/tests/typecheck/should_fail/T12563.stderr
index c5b8e1dc40..4b64ef1cc7 100644
--- a/testsuite/tests/typecheck/should_fail/T12563.stderr
+++ b/testsuite/tests/typecheck/should_fail/T12563.stderr
@@ -1,12 +1,15 @@
T12563.hs:8:15: error:
- • Couldn't match expected type ‘(forall a. f0 a) -> f0 r0’
- with actual type ‘p0’
- Cannot instantiate unification variable ‘p0’
- with a type involving polytypes: (forall a. f0 a) -> f0 r0
+ • Couldn't match expected type ‘(forall a. f a) -> f r’
+ with actual type ‘p’
+ Cannot equate type variable ‘p’
+ with a type involving polytypes: (forall a. f a) -> f r
+ ‘p’ is a rigid type variable bound by
+ the inferred type of x :: p -> f r
+ at T12563.hs:8:1-15
• In the first argument of ‘foo’, namely ‘g’
In the expression: foo g
In the expression: \ g -> foo g
• Relevant bindings include
- g :: p0 (bound at T12563.hs:8:6)
- x :: p0 -> f0 r0 (bound at T12563.hs:8:1)
+ g :: p (bound at T12563.hs:8:6)
+ x :: p -> f r (bound at T12563.hs:8:1)
diff --git a/testsuite/tests/typecheck/should_fail/T13909.stderr b/testsuite/tests/typecheck/should_fail/T13909.stderr
index 6ea5b32e66..d370d9ed05 100644
--- a/testsuite/tests/typecheck/should_fail/T13909.stderr
+++ b/testsuite/tests/typecheck/should_fail/T13909.stderr
@@ -2,6 +2,8 @@
T13909.hs:11:18: error:
• Expecting two more arguments to ‘Hm’
Expected kind ‘k’, but ‘Hm’ has kind ‘forall k -> k -> *’
+ Cannot equate type variable ‘k’
+ with a kind involving polytypes: forall k1 -> k1 -> *
‘k’ is a rigid type variable bound by
an instance declaration
at T13909.hs:11:10-19
diff --git a/testsuite/tests/typecheck/should_fail/T14618.stderr b/testsuite/tests/typecheck/should_fail/T14618.stderr
index c6fae3f81e..05a763048e 100644
--- a/testsuite/tests/typecheck/should_fail/T14618.stderr
+++ b/testsuite/tests/typecheck/should_fail/T14618.stderr
@@ -3,6 +3,8 @@ T14618.hs:7:14: error:
• Couldn't match type ‘b’ with ‘forall c. a’
Expected: a -> b
Actual: a -> forall c. a
+ Cannot equate type variable ‘b’
+ with a type involving polytypes: forall c. a
‘b’ is a rigid type variable bound by
the type signature for:
safeCoerce :: forall a b. a -> b
diff --git a/testsuite/tests/typecheck/should_fail/T14904a.stderr b/testsuite/tests/typecheck/should_fail/T14904a.stderr
index 1ed0946f6c..0de9206867 100644
--- a/testsuite/tests/typecheck/should_fail/T14904a.stderr
+++ b/testsuite/tests/typecheck/should_fail/T14904a.stderr
@@ -1,6 +1,8 @@
T14904a.hs:10:6: error:
• Expected kind ‘forall (a :: k). g a’, but ‘f’ has kind ‘k1’
+ Cannot equate type variable ‘k1’
+ with a kind involving polytypes: forall (a :: k). g a
‘k1’ is a rigid type variable bound by
a family instance declaration
at T14904a.hs:10:3-30
diff --git a/testsuite/tests/typecheck/should_fail/T3592.stderr b/testsuite/tests/typecheck/should_fail/T3592.stderr
index bc3f774ecc..458922cb91 100644
--- a/testsuite/tests/typecheck/should_fail/T3592.stderr
+++ b/testsuite/tests/typecheck/should_fail/T3592.stderr
@@ -9,12 +9,3 @@ T3592.hs:8:5: error:
In an equation for ‘f’: f = show
• Relevant bindings include
f :: T a -> String (bound at T3592.hs:8:1)
-
-T3592.hs:11:7: error:
- • No instance for (Show a) arising from a use of ‘show’
- Possible fix:
- add (Show a) to the context of
- the type signature for:
- g :: forall a. T a -> String
- • In the expression: show x
- In an equation for ‘g’: g x = show x
diff --git a/testsuite/tests/typecheck/should_fail/T7264.stderr b/testsuite/tests/typecheck/should_fail/T7264.stderr
index 4d2a153306..0f18dd41af 100644
--- a/testsuite/tests/typecheck/should_fail/T7264.stderr
+++ b/testsuite/tests/typecheck/should_fail/T7264.stderr
@@ -3,6 +3,8 @@ T7264.hs:13:19: error:
• Couldn't match type ‘a’ with ‘forall r. r -> String’
Expected: a -> Foo
Actual: (forall r. r -> String) -> Foo
+ Cannot equate type variable ‘a’
+ with a type involving polytypes: forall r. r -> String
‘a’ is a rigid type variable bound by
the inferred type of mkFoo2 :: a -> Maybe Foo
at T7264.hs:13:1-32
diff --git a/testsuite/tests/typecheck/should_fail/T8142.stderr b/testsuite/tests/typecheck/should_fail/T8142.stderr
index a362d35367..2c970aca2e 100644
--- a/testsuite/tests/typecheck/should_fail/T8142.stderr
+++ b/testsuite/tests/typecheck/should_fail/T8142.stderr
@@ -12,17 +12,15 @@ T8142.hs:6:10: error:
where
h = (\ (_, b) -> ((outI . fmap h) b)) . out
• Relevant bindings include
- h :: Nu ((,) a0) -> Nu f0 (bound at T8142.hs:6:18)
tracer :: (c -> f c) -> c -> f c (bound at T8142.hs:6:1)
T8142.hs:6:57: error:
- • Couldn't match type: Nu ((,) a0)
- with: f0 (Nu ((,) a0))
- Expected: Nu ((,) a0) -> (a0, f0 (Nu ((,) a0)))
- Actual: Nu ((,) a0) -> (a0, Nu ((,) a0))
- The type variables ‘f0’, ‘a0’ are ambiguous
+ • Couldn't match type: Nu ((,) a)
+ with: f1 (Nu ((,) a))
+ Expected: Nu ((,) a) -> (a, f1 (Nu ((,) a)))
+ Actual: Nu ((,) a) -> (a, Nu ((,) a))
• In the second argument of ‘(.)’, namely ‘out’
In the expression: (\ (_, b) -> ((outI . fmap h) b)) . out
In an equation for ‘h’: h = (\ (_, b) -> ((outI . fmap h) b)) . out
• Relevant bindings include
- h :: Nu ((,) a0) -> Nu f0 (bound at T8142.hs:6:18)
+ h :: Nu ((,) a) -> Nu f1 (bound at T8142.hs:6:18)