diff options
author | Simon Peyton Jones <simonpj@microsoft.com> | 2013-01-08 08:30:05 +0000 |
---|---|---|
committer | Simon Peyton Jones <simonpj@microsoft.com> | 2013-01-08 08:30:05 +0000 |
commit | 441a87a10e0a97c7af8beb19dfb02eb375c0e01f (patch) | |
tree | 32cc04cdf7bb37361195738647b59ed5393d9963 /testsuite/tests | |
parent | 8f01d1e494edfe94810d73705e61acb0d1e695c2 (diff) | |
download | haskell-441a87a10e0a97c7af8beb19dfb02eb375c0e01f.tar.gz |
Wibbles to error messages and tests, following ambiguity-check changes
Diffstat (limited to 'testsuite/tests')
59 files changed, 898 insertions, 885 deletions
diff --git a/testsuite/tests/deriving/should_fail/T3101.hs b/testsuite/tests/deriving/should_fail/T3101.hs index 134694a4fe..f13b2f0696 100644 --- a/testsuite/tests/deriving/should_fail/T3101.hs +++ b/testsuite/tests/deriving/should_fail/T3101.hs @@ -5,5 +5,5 @@ module T3101 where type family F a :: * -data Boom = Boom (forall a. F a) +data Boom = Boom (forall a. a -> F a) deriving Show diff --git a/testsuite/tests/deriving/should_fail/T5287.hs b/testsuite/tests/deriving/should_fail/T5287.hs index cb1259ca01..6495b62be9 100644 --- a/testsuite/tests/deriving/should_fail/T5287.hs +++ b/testsuite/tests/deriving/should_fail/T5287.hs @@ -2,8 +2,13 @@ module Bug where class A a oops data D d = D d + instance A a oops => Read (D a) +-- Actually this instance is ambiguous +-- and is now rightly rejected + data E e = E (D e) deriving Read + instance A Int Bool diff --git a/testsuite/tests/deriving/should_fail/T5287.stderr b/testsuite/tests/deriving/should_fail/T5287.stderr index d74166e7aa..9de62ef2fc 100644 --- a/testsuite/tests/deriving/should_fail/T5287.stderr +++ b/testsuite/tests/deriving/should_fail/T5287.stderr @@ -1,12 +1,10 @@ - -T5287.hs:6:29: - No instance for (A e oops) - arising from the 'deriving' clause of a data type declaration - The type variable `oops' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Note: there is a potential instance available: - instance A Int Bool -- Defined at T5287.hs:7:10 - Possible fix: - use a standalone 'deriving instance' declaration, - so you can specify the instance context yourself - When deriving the instance for (Read (E e)) +
+T5287.hs:6:10:
+ Could not deduce (A a oops0)
+ arising from the ambiguity check for an instance declaration
+ from the context (A a oops)
+ bound by an instance declaration: A a oops => Read (D a)
+ at T5287.hs:6:10-31
+ The type variable `oops0' is ambiguous
+ In the ambiguity check for: forall a oops. A a oops => Read (D a)
+ In the instance declaration for `Read (D a)'
diff --git a/testsuite/tests/driver/T4437.hs b/testsuite/tests/driver/T4437.hs index 4b1b1105b6..f51707a546 100644 --- a/testsuite/tests/driver/T4437.hs +++ b/testsuite/tests/driver/T4437.hs @@ -31,6 +31,7 @@ check title expected got expectedGhcOnlyExtensions :: [String] expectedGhcOnlyExtensions = [ + "AlloAmbiguousTypes", "RelaxedLayout", "AlternativeLayoutRule", "AlternativeLayoutRuleTransitional", diff --git a/testsuite/tests/ghci/scripts/Defer02.stderr b/testsuite/tests/ghci/scripts/Defer02.stderr index db02b16308..b0937a7bd3 100644 --- a/testsuite/tests/ghci/scripts/Defer02.stderr +++ b/testsuite/tests/ghci/scripts/Defer02.stderr @@ -1,179 +1,185 @@ - -../../typecheck/should_run/Defer01.hs:11:40: Warning: - Couldn't match type `Char' with `[Char]' - Expected type: String - Actual type: Char - In the first argument of `putStr', namely ',' - In the second argument of `(>>)', namely putStr ',' - In the expression: putStr "Hello World" >> putStr ',' - -../../typecheck/should_run/Defer01.hs:14:5: Warning: - Couldn't match expected type `Int' with actual type `Char' - In the expression: 'p' - In an equation for `a': a = 'p' - -../../typecheck/should_run/Defer01.hs:18:9: Warning: - No instance for (Eq B) arising from a use of `==' - In the expression: x == x - In an equation for `b': b x = x == x - -../../typecheck/should_run/Defer01.hs:25:4: Warning: - Couldn't match type `Int' with `Bool' - Inaccessible code in - a pattern with constructor - C2 :: Bool -> C Bool, - in an equation for `c' - In the pattern: C2 x - In an equation for `c': c (C2 x) = True - -../../typecheck/should_run/Defer01.hs:28:5: Warning: - No instance for (Num (a -> a)) arising from the literal `1' - In the expression: 1 - In an equation for `d': d = 1 - -../../typecheck/should_run/Defer01.hs:31:5: Warning: - Couldn't match expected type `Char -> t' with actual type `Char' - Relevant bindings include - f :: t (bound at ../../typecheck/should_run/Defer01.hs:31:1) - The function `e' is applied to one argument, - but its type `Char' has none - In the expression: e 'q' - In an equation for `f': f = e 'q' - -../../typecheck/should_run/Defer01.hs:34:8: Warning: - Couldn't match expected type `Char' with actual type `a' - `a' is a rigid type variable bound by - the type signature for h :: a -> (Char, Char) - at ../../typecheck/should_run/Defer01.hs:33:6 - Relevant bindings include - h :: a -> (Char, Char) - (bound at ../../typecheck/should_run/Defer01.hs:34:1) - x :: a (bound at ../../typecheck/should_run/Defer01.hs:34:3) - In the expression: x - In the expression: (x, 'c') - In an equation for `h': h x = (x, 'c') - -../../typecheck/should_run/Defer01.hs:39:17: Warning: - Couldn't match expected type `Bool' with actual type `T a' - Relevant bindings include - i :: a -> () (bound at ../../typecheck/should_run/Defer01.hs:39:1) - a :: a (bound at ../../typecheck/should_run/Defer01.hs:39:3) - In the return type of a call of `K' - In the first argument of `not', namely `(K a)' - In the expression: (not (K a)) - -../../typecheck/should_run/Defer01.hs:43:5: Warning: - No instance for (MyClass a1) arising from a use of `myOp' - In the expression: myOp 23 - In an equation for `j': j = myOp 23 - -../../typecheck/should_run/Defer01.hs:43:10: Warning: - No instance for (Num a1) arising from the literal `23' - The type variable `a1' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Note: there are several potential instances: - instance Num Double -- Defined in `GHC.Float' - instance Num Float -- Defined in `GHC.Float' - instance Integral a => Num (GHC.Real.Ratio a) - -- Defined in `GHC.Real' - ...plus three others - In the first argument of `myOp', namely `23' - In the expression: myOp 23 - In an equation for `j': j = myOp 23 - -../../typecheck/should_run/Defer01.hs:45:6: Warning: - Couldn't match type `Int' with `Bool' - Inaccessible code in - the type signature for k :: Int ~ Bool => Int -> Bool - -../../typecheck/should_run/Defer01.hs:46:7: Warning: - Couldn't match expected type `Bool' with actual type `Int' - In the expression: x - In an equation for `k': k x = x - -../../typecheck/should_run/Defer01.hs:49:5: Warning: - Couldn't match expected type `IO a0' - with actual type `Char -> IO ()' - In the first argument of `(>>)', namely `putChar' - In the expression: putChar >> putChar 'p' - In an equation for `l': l = putChar >> putChar 'p' -*** Exception: ../../typecheck/should_run/Defer01.hs:11:40: - Couldn't match type `Char' with `[Char]' - Expected type: String - Actual type: Char - In the first argument of `putStr', namely ',' - In the second argument of `(>>)', namely putStr ',' - In the expression: putStr "Hello World" >> putStr ',' -(deferred type error) -*** Exception: ../../typecheck/should_run/Defer01.hs:14:5: - Couldn't match expected type `Int' with actual type `Char' - In the expression: 'p' - In an equation for `a': a = 'p' -(deferred type error) -*** Exception: ../../typecheck/should_run/Defer01.hs:18:9: - No instance for (Eq B) arising from a use of `==' - In the expression: x == x - In an equation for `b': b x = x == x -(deferred type error) - -<interactive>:8:11: - Couldn't match type `Bool' with `Int' - Expected type: C Int - Actual type: C Bool - In the return type of a call of `C2' - In the first argument of `c', namely `(C2 True)' - In the first argument of `print', namely `(c (C2 True))' -*** Exception: ../../typecheck/should_run/Defer01.hs:28:5: - No instance for (Num (a -> a)) arising from the literal `1' - In the expression: 1 - In an equation for `d': d = 1 -(deferred type error) -*** Exception: ../../typecheck/should_run/Defer01.hs:31:5: - Couldn't match expected type `Char -> t' with actual type `Char' - Relevant bindings include - f :: t (bound at ../../typecheck/should_run/Defer01.hs:31:1) - The function `e' is applied to one argument, - but its type `Char' has none - In the expression: e 'q' - In an equation for `f': f = e 'q' -(deferred type error) -*** Exception: ../../typecheck/should_run/Defer01.hs:34:8: - Couldn't match expected type `Char' with actual type `a' - `a' is a rigid type variable bound by - the type signature for h :: a -> (Char, Char) - at ../../typecheck/should_run/Defer01.hs:33:6 - Relevant bindings include - h :: a -> (Char, Char) - (bound at ../../typecheck/should_run/Defer01.hs:34:1) - x :: a (bound at ../../typecheck/should_run/Defer01.hs:34:3) - In the expression: x - In the expression: (x, 'c') - In an equation for `h': h x = (x, 'c') -(deferred type error) -*** Exception: ../../typecheck/should_run/Defer01.hs:39:17: - Couldn't match expected type `Bool' with actual type `T a' - Relevant bindings include - i :: a -> () (bound at ../../typecheck/should_run/Defer01.hs:39:1) - a :: a (bound at ../../typecheck/should_run/Defer01.hs:39:3) - In the return type of a call of `K' - In the first argument of `not', namely `(K a)' - In the expression: (not (K a)) -(deferred type error) -*** Exception: ../../typecheck/should_run/Defer01.hs:43:5: - No instance for (MyClass a1) arising from a use of `myOp' - In the expression: myOp 23 - In an equation for `j': j = myOp 23 -(deferred type error) - -<interactive>:14:8: - Couldn't match expected type `Bool' with actual type `Int' - In the first argument of `print', namely `(k 2)' - In the expression: print (k 2) - In an equation for `it': it = print (k 2) -*** Exception: ../../typecheck/should_run/Defer01.hs:49:5: - Couldn't match expected type `IO a0' - with actual type `Char -> IO ()' - In the first argument of `(>>)', namely `putChar' - In the expression: putChar >> putChar 'p' - In an equation for `l': l = putChar >> putChar 'p' -(deferred type error) +
+..\..\typecheck\should_run\Defer01.hs:11:40: Warning:
+ Couldn't match type `Char' with `[Char]'
+ Expected type: String
+ Actual type: Char
+ In the first argument of `putStr', namely ','
+ In the second argument of `(>>)', namely putStr ','
+ In the expression: putStr "Hello World" >> putStr ','
+
+..\..\typecheck\should_run\Defer01.hs:14:5: Warning:
+ Couldn't match expected type `Int' with actual type `Char'
+ In the expression: 'p'
+ In an equation for `a': a = 'p'
+
+..\..\typecheck\should_run\Defer01.hs:18:9: Warning:
+ No instance for (Eq B) arising from a use of `=='
+ In the expression: x == x
+ In an equation for `b': b x = x == x
+
+..\..\typecheck\should_run\Defer01.hs:25:4: Warning:
+ Couldn't match type `Int' with `Bool'
+ Inaccessible code in
+ a pattern with constructor
+ C2 :: Bool -> C Bool,
+ in an equation for `c'
+ In the pattern: C2 x
+ In an equation for `c': c (C2 x) = True
+
+..\..\typecheck\should_run\Defer01.hs:28:5: Warning:
+ No instance for (Num (a -> a)) arising from the literal `1'
+ In the expression: 1
+ In an equation for `d': d = 1
+
+..\..\typecheck\should_run\Defer01.hs:31:5: Warning:
+ Couldn't match expected type `Char -> t' with actual type `Char'
+ Relevant bindings include
+ f :: t (bound at ..\..\typecheck\should_run\Defer01.hs:31:1)
+ The function `e' is applied to one argument,
+ but its type `Char' has none
+ In the expression: e 'q'
+ In an equation for `f': f = e 'q'
+
+..\..\typecheck\should_run\Defer01.hs:34:8: Warning:
+ Couldn't match expected type `Char' with actual type `a'
+ `a' is a rigid type variable bound by
+ the type signature for h :: a -> (Char, Char)
+ at ..\..\typecheck\should_run\Defer01.hs:33:6
+ Relevant bindings include
+ h :: a -> (Char, Char)
+ (bound at ..\..\typecheck\should_run\Defer01.hs:34:1)
+ x :: a (bound at ..\..\typecheck\should_run\Defer01.hs:34:3)
+ In the expression: x
+ In the expression: (x, 'c')
+ In an equation for `h': h x = (x, 'c')
+
+..\..\typecheck\should_run\Defer01.hs:39:17: Warning:
+ Couldn't match expected type `Bool' with actual type `T a'
+ Relevant bindings include
+ i :: a -> () (bound at ..\..\typecheck\should_run\Defer01.hs:39:1)
+ a :: a (bound at ..\..\typecheck\should_run\Defer01.hs:39:3)
+ In the return type of a call of `K'
+ In the first argument of `not', namely `(K a)'
+ In the expression: (not (K a))
+
+..\..\typecheck\should_run\Defer01.hs:43:5: Warning:
+ No instance for (MyClass a1) arising from a use of `myOp'
+ In the expression: myOp 23
+ In an equation for `j': j = myOp 23
+
+..\..\typecheck\should_run\Defer01.hs:43:10: Warning:
+ No instance for (Num a1) arising from the literal `23'
+ The type variable `a1' is ambiguous
+ Note: there are several potential instances:
+ instance Num Double -- Defined in `GHC.Float'
+ instance Num Float -- Defined in `GHC.Float'
+ instance Integral a => Num (GHC.Real.Ratio a)
+ -- Defined in `GHC.Real'
+ ...plus three others
+ In the first argument of `myOp', namely `23'
+ In the expression: myOp 23
+ In an equation for `j': j = myOp 23
+
+..\..\typecheck\should_run\Defer01.hs:45:6: Warning:
+ Couldn't match type `Int' with `Bool'
+ Inaccessible code in
+ the type signature for k :: Int ~ Bool => Int -> Bool
+ In the ambiguity check for: Int ~ Bool => Int -> Bool
+ In the type signature for `k': k :: Int ~ Bool => Int -> Bool
+
+..\..\typecheck\should_run\Defer01.hs:45:6: Warning:
+ Couldn't match type `Int' with `Bool'
+ Inaccessible code in
+ the type signature for k :: Int ~ Bool => Int -> Bool
+
+..\..\typecheck\should_run\Defer01.hs:46:7: Warning:
+ Couldn't match expected type `Bool' with actual type `Int'
+ In the expression: x
+ In an equation for `k': k x = x
+
+..\..\typecheck\should_run\Defer01.hs:49:5: Warning:
+ Couldn't match expected type `IO a0'
+ with actual type `Char -> IO ()'
+ In the first argument of `(>>)', namely `putChar'
+ In the expression: putChar >> putChar 'p'
+ In an equation for `l': l = putChar >> putChar 'p'
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:11:40:
+ Couldn't match type `Char' with `[Char]'
+ Expected type: String
+ Actual type: Char
+ In the first argument of `putStr', namely ','
+ In the second argument of `(>>)', namely putStr ','
+ In the expression: putStr "Hello World" >> putStr ','
+(deferred type error)
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:14:5:
+ Couldn't match expected type `Int' with actual type `Char'
+ In the expression: 'p'
+ In an equation for `a': a = 'p'
+(deferred type error)
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:18:9:
+ No instance for (Eq B) arising from a use of `=='
+ In the expression: x == x
+ In an equation for `b': b x = x == x
+(deferred type error)
+
+<interactive>:8:11:
+ Couldn't match type `Bool' with `Int'
+ Expected type: C Int
+ Actual type: C Bool
+ In the return type of a call of `C2'
+ In the first argument of `c', namely `(C2 True)'
+ In the first argument of `print', namely `(c (C2 True))'
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:28:5:
+ No instance for (Num (a -> a)) arising from the literal `1'
+ In the expression: 1
+ In an equation for `d': d = 1
+(deferred type error)
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:31:5:
+ Couldn't match expected type `Char -> t' with actual type `Char'
+ Relevant bindings include
+ f :: t (bound at ..\..\typecheck\should_run\Defer01.hs:31:1)
+ The function `e' is applied to one argument,
+ but its type `Char' has none
+ In the expression: e 'q'
+ In an equation for `f': f = e 'q'
+(deferred type error)
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:34:8:
+ Couldn't match expected type `Char' with actual type `a'
+ `a' is a rigid type variable bound by
+ the type signature for h :: a -> (Char, Char)
+ at ..\..\typecheck\should_run\Defer01.hs:33:6
+ Relevant bindings include
+ h :: a -> (Char, Char)
+ (bound at ..\..\typecheck\should_run\Defer01.hs:34:1)
+ x :: a (bound at ..\..\typecheck\should_run\Defer01.hs:34:3)
+ In the expression: x
+ In the expression: (x, 'c')
+ In an equation for `h': h x = (x, 'c')
+(deferred type error)
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:39:17:
+ Couldn't match expected type `Bool' with actual type `T a'
+ Relevant bindings include
+ i :: a -> () (bound at ..\..\typecheck\should_run\Defer01.hs:39:1)
+ a :: a (bound at ..\..\typecheck\should_run\Defer01.hs:39:3)
+ In the return type of a call of `K'
+ In the first argument of `not', namely `(K a)'
+ In the expression: (not (K a))
+(deferred type error)
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:43:5:
+ No instance for (MyClass a1) arising from a use of `myOp'
+ In the expression: myOp 23
+ In an equation for `j': j = myOp 23
+(deferred type error)
+
+<interactive>:14:8:
+ Couldn't match expected type `Bool' with actual type `Int'
+ In the first argument of `print', namely `(k 2)'
+ In the expression: print (k 2)
+ In an equation for `it': it = print (k 2)
+*** Exception: ..\..\typecheck\should_run\Defer01.hs:49:5:
+ Couldn't match expected type `IO a0'
+ with actual type `Char -> IO ()'
+ In the first argument of `(>>)', namely `putChar'
+ In the expression: putChar >> putChar 'p'
+ In an equation for `l': l = putChar >> putChar 'p'
+(deferred type error)
diff --git a/testsuite/tests/indexed-types/should_compile/GADT12.hs b/testsuite/tests/indexed-types/should_compile/GADT12.hs index 4eb5124c1d..89362f3cbb 100644 --- a/testsuite/tests/indexed-types/should_compile/GADT12.hs +++ b/testsuite/tests/indexed-types/should_compile/GADT12.hs @@ -22,17 +22,17 @@ data Type a where data Expr :: * -> * -> * {- tu a -} where Const :: Type a -> a -> Expr tu (TU tu a) - Var2 :: String -> TU tu (Type a) -> Expr tu (TU tu a) + Var2 :: a -> TU tu (Type a) -> Expr tu (TU tu a) bug1 :: Expr Typed Bool -> () bug1 (Const TypeBool False) = () bug2a :: Expr Typed Bool -> () -bug2a (Var2 "x" (TypeBool :: Type Bool)) = () +bug2a (Var2 x (TypeBool :: Type Bool)) = () bug2c :: Expr Typed Bool -> () -bug2c (Var2 "x" TypeBool) = () +bug2c (Var2 x TypeBool) = () bug2b :: Expr Typed (TU Typed Bool) -> () -bug2b (Var2 "x" TypeBool) = () +bug2b (Var2 x TypeBool) = () diff --git a/testsuite/tests/indexed-types/should_compile/GADT5.hs b/testsuite/tests/indexed-types/should_compile/GADT5.hs index 69a6481fd0..44b9656a93 100644 --- a/testsuite/tests/indexed-types/should_compile/GADT5.hs +++ b/testsuite/tests/indexed-types/should_compile/GADT5.hs @@ -9,6 +9,6 @@ data T a where type family F a -bar :: T (F a) -> () -bar T = () +bar :: a -> T (F a) -> () +bar x T = () diff --git a/testsuite/tests/indexed-types/should_compile/Simple19.hs b/testsuite/tests/indexed-types/should_compile/Simple19.hs index d738b0bd85..8df1fd4c4b 100644 --- a/testsuite/tests/indexed-types/should_compile/Simple19.hs +++ b/testsuite/tests/indexed-types/should_compile/Simple19.hs @@ -6,5 +6,5 @@ module ShouldCompile where type family Element c :: * -f :: Element x -f = undefined +f :: x -> Element x +f x = undefined diff --git a/testsuite/tests/indexed-types/should_compile/T1981.hs b/testsuite/tests/indexed-types/should_compile/T1981.hs index 658821ea73..906fdaf217 100644 --- a/testsuite/tests/indexed-types/should_compile/T1981.hs +++ b/testsuite/tests/indexed-types/should_compile/T1981.hs @@ -4,5 +4,5 @@ module ShouldCompile where type family T a -f :: T a -> Int -f x = x `seq` 3 +f :: a -> T a -> Int +f p x = x `seq` 3 diff --git a/testsuite/tests/indexed-types/should_compile/T3208b.stderr b/testsuite/tests/indexed-types/should_compile/T3208b.stderr index 0d8a4596b9..5eee19a1ae 100644 --- a/testsuite/tests/indexed-types/should_compile/T3208b.stderr +++ b/testsuite/tests/indexed-types/should_compile/T3208b.stderr @@ -7,7 +7,6 @@ T3208b.hs:15:10: at T3208b.hs:14:9-56
NB: `STerm' is a type function, and may not be injective
The type variable `o0' is ambiguous
- Possible fix: add a type signature that fixes these type variable(s)
Expected type: STerm o0
Actual type: OTerm o0
Relevant bindings include
@@ -23,7 +22,6 @@ T3208b.hs:15:15: fce' :: (OTerm a ~ STerm a, OBJECT a, SUBST a) => a -> c
at T3208b.hs:14:9-56
The type variable `o0' is ambiguous
- Possible fix: add a type signature that fixes these type variable(s)
Relevant bindings include
fce' :: a -> c (bound at T3208b.hs:15:1)
f :: a (bound at T3208b.hs:15:6)
diff --git a/testsuite/tests/indexed-types/should_compile/T4981-V1.hs b/testsuite/tests/indexed-types/should_compile/T4981-V1.hs index 14f675ca59..629028748a 100644 --- a/testsuite/tests/indexed-types/should_compile/T4981-V1.hs +++ b/testsuite/tests/indexed-types/should_compile/T4981-V1.hs @@ -30,5 +30,5 @@ joinPatches = id cleverNamedResolve :: (Conflict (OnPrim p)
,PrimOf (OnPrim p) ~ WithName (PrimOf p))
- => FL (OnPrim p) -> WithName (PrimOf p)
-cleverNamedResolve = resolveConflicts . joinPatches
+ => p -> FL (OnPrim p) -> WithName (PrimOf p)
+cleverNamedResolve x = resolveConflicts . joinPatches
diff --git a/testsuite/tests/indexed-types/should_compile/T4981-V2.hs b/testsuite/tests/indexed-types/should_compile/T4981-V2.hs index d18d67e91c..716f161340 100644 --- a/testsuite/tests/indexed-types/should_compile/T4981-V2.hs +++ b/testsuite/tests/indexed-types/should_compile/T4981-V2.hs @@ -27,5 +27,5 @@ joinPatches = id cleverNamedResolve :: (Conflict (OnPrim p)
,PrimOf (OnPrim p) ~ WithName (PrimOf p))
- => FL (OnPrim p) -> WithName (PrimOf p)
-cleverNamedResolve = resolveConflicts . joinPatches
+ => p -> FL (OnPrim p) -> WithName (PrimOf p)
+cleverNamedResolve x = resolveConflicts . joinPatches
diff --git a/testsuite/tests/indexed-types/should_compile/T4981-V3.hs b/testsuite/tests/indexed-types/should_compile/T4981-V3.hs index 9e0eda54eb..fe810f2657 100644 --- a/testsuite/tests/indexed-types/should_compile/T4981-V3.hs +++ b/testsuite/tests/indexed-types/should_compile/T4981-V3.hs @@ -27,5 +27,18 @@ joinPatches = id cleverNamedResolve :: (Conflict (OnPrim p)
,PrimOf (OnPrim p) ~ WithName (PrimOf p))
- => FL (OnPrim p) -> WithName (PrimOf p)
-cleverNamedResolve = resolveConflicts . joinPatches
+ => p -> FL (OnPrim p) -> WithName (PrimOf p)
+cleverNamedResolve x = resolveConflicts . joinPatches
+-- I added the parameter 'x' to make the signature unambiguous
+-- I don't think that ambiguity is essential to the original problem
+
+{-
+resolveConflicts :: q -> PrimOf q
+ (w) FL (OnPrim p) ~ q
+ (w) WithName (PrimOf p) ~ PrimOf q
+==>
+ (w) PrimOf (OnPrim p) ~ PrimOf (FL (OnPrim p))
+==>
+ (w) PrimOf (OnPrim p) ~ PrimOf (OnPrim p)
+
+-}
\ No newline at end of file diff --git a/testsuite/tests/indexed-types/should_fail/NoMatchErr.stderr b/testsuite/tests/indexed-types/should_fail/NoMatchErr.stderr index b8a45c3ef7..0176ffe2ec 100644 --- a/testsuite/tests/indexed-types/should_fail/NoMatchErr.stderr +++ b/testsuite/tests/indexed-types/should_fail/NoMatchErr.stderr @@ -1,16 +1,13 @@ - -NoMatchErr.hs:20:5: - Could not deduce (Memo d0 ~ Memo d) - from the context (Fun d) - bound by the type signature for f :: Fun d => Memo d a -> Memo d a - at NoMatchErr.hs:19:7-37 - NB: `Memo' is a type function, and may not be injective - The type variable `d0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Expected type: (d0 -> a) -> Memo d a - Actual type: (d0 -> a) -> Memo d0 a - Relevant bindings include - f :: Memo d a -> Memo d a (bound at NoMatchErr.hs:20:1) - In the first argument of `(.)', namely `abst' - In the expression: abst . appl - In an equation for `f': f = abst . appl +
+NoMatchErr.hs:19:7:
+ Could not deduce (Memo d0 ~ Memo d)
+ from the context (Fun d)
+ bound by the type signature for f :: Fun d => Memo d a -> Memo d a
+ at NoMatchErr.hs:19:7-37
+ NB: `Memo' is a type function, and may not be injective
+ The type variable `d0' is ambiguous
+ Expected type: Memo d a -> Memo d a
+ Actual type: Memo d0 a -> Memo d0 a
+ In the ambiguity check for:
+ forall d a. Fun d => Memo d a -> Memo d a
+ In the type signature for `f': f :: Fun d => Memo d a -> Memo d a
diff --git a/testsuite/tests/indexed-types/should_fail/Overlap10.hs b/testsuite/tests/indexed-types/should_fail/Overlap10.hs index 25fca9a720..07a13e0219 100644 --- a/testsuite/tests/indexed-types/should_fail/Overlap10.hs +++ b/testsuite/tests/indexed-types/should_fail/Overlap10.hs @@ -7,8 +7,8 @@ type instance where F a a = Int F a b = b -g :: F a Bool -g = False +g :: a -> F a Bool +g x = False diff --git a/testsuite/tests/indexed-types/should_fail/Overlap10.stderr b/testsuite/tests/indexed-types/should_fail/Overlap10.stderr index c8f68bad94..63fa4d9c38 100644 --- a/testsuite/tests/indexed-types/should_fail/Overlap10.stderr +++ b/testsuite/tests/indexed-types/should_fail/Overlap10.stderr @@ -1,7 +1,8 @@ - -Overlap10.hs:11:5: - Couldn't match expected type `F a Bool' with actual type `Bool' - Relevant bindings include - g :: F a Bool (bound at Overlap10.hs:11:1) - In the expression: False - In an equation for `g': g = False +
+Overlap10.hs:11:7:
+ Couldn't match expected type `F a Bool' with actual type `Bool'
+ Relevant bindings include
+ g :: a -> F a Bool (bound at Overlap10.hs:11:1)
+ x :: a (bound at Overlap10.hs:11:3)
+ In the expression: False
+ In an equation for `g': g x = False
diff --git a/testsuite/tests/indexed-types/should_fail/Overlap11.hs b/testsuite/tests/indexed-types/should_fail/Overlap11.hs index f103759583..1498d5946a 100644 --- a/testsuite/tests/indexed-types/should_fail/Overlap11.hs +++ b/testsuite/tests/indexed-types/should_fail/Overlap11.hs @@ -7,8 +7,8 @@ type instance where F a a = Int F a b = b -g :: F a Int -g = (5 :: Int) +g :: a -> F a Int +g x = (5 :: Int) diff --git a/testsuite/tests/indexed-types/should_fail/Overlap11.stderr b/testsuite/tests/indexed-types/should_fail/Overlap11.stderr index 0d657dac88..929ce34603 100644 --- a/testsuite/tests/indexed-types/should_fail/Overlap11.stderr +++ b/testsuite/tests/indexed-types/should_fail/Overlap11.stderr @@ -1,6 +1,8 @@ - -Overlap11.hs:11:6: - Couldn't match expected type `F a Int' with actual type `Int' - Relevant bindings include g :: F a Int (bound at Overlap11.hs:11:1) - In the expression: (5 :: Int) - In an equation for `g': g = (5 :: Int) +
+Overlap11.hs:11:8:
+ Couldn't match expected type `F a Int' with actual type `Int'
+ Relevant bindings include
+ g :: a -> F a Int (bound at Overlap11.hs:11:1)
+ x :: a (bound at Overlap11.hs:11:3)
+ In the expression: (5 :: Int)
+ In an equation for `g': g x = (5 :: Int)
diff --git a/testsuite/tests/indexed-types/should_fail/SimpleFail16.stderr b/testsuite/tests/indexed-types/should_fail/SimpleFail16.stderr index 4ccdbc33bf..3ad3cc7707 100644 --- a/testsuite/tests/indexed-types/should_fail/SimpleFail16.stderr +++ b/testsuite/tests/indexed-types/should_fail/SimpleFail16.stderr @@ -1,12 +1,9 @@ - -SimpleFail16.hs:10:12: - Couldn't match expected type `p0 a0' with actual type `F ()' - The type variables `p0', `a0' are ambiguous - Possible cause: the monomorphism restriction applied to: `bar' - Probable fix: give these definition(s) an explicit type signature - or use -XNoMonomorphismRestriction - Relevant bindings include - bar :: p0 a0 (bound at SimpleFail16.hs:10:1) - In the first argument of `foo', namely `(undefined :: F ())' - In the expression: foo (undefined :: F ()) - In an equation for `bar': bar = foo (undefined :: F ()) +
+SimpleFail16.hs:10:12:
+ Couldn't match expected type `p0 a0' with actual type `F ()'
+ The type variables `p0', `a0' are ambiguous
+ Relevant bindings include
+ bar :: p0 a0 (bound at SimpleFail16.hs:10:1)
+ In the first argument of `foo', namely `(undefined :: F ())'
+ In the expression: foo (undefined :: F ())
+ In an equation for `bar': bar = foo (undefined :: F ())
diff --git a/testsuite/tests/indexed-types/should_fail/T1897b.stderr b/testsuite/tests/indexed-types/should_fail/T1897b.stderr index 7311270168..32bb3cff9f 100644 --- a/testsuite/tests/indexed-types/should_fail/T1897b.stderr +++ b/testsuite/tests/indexed-types/should_fail/T1897b.stderr @@ -1,15 +1,14 @@ - -T1897b.hs:16:1: - Could not deduce (Depend a0 ~ Depend a) - from the context (Bug a) - bound by the inferred type for `isValid': - Bug a => [Depend a] -> Bool - at T1897b.hs:16:1-41 - NB: `Depend' is a type function, and may not be injective - The type variable `a0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Expected type: [Depend a] -> Bool - Actual type: [Depend a0] -> Bool - When checking that `isValid' - has the inferred type `forall a. Bug a => [Depend a] -> Bool' - Probable cause: the inferred type is ambiguous +
+T1897b.hs:16:1:
+ Could not deduce (Depend a0 ~ Depend a)
+ from the context (Bug a)
+ bound by the inferred type for `isValid':
+ Bug a => [Depend a] -> Bool
+ at T1897b.hs:16:1-41
+ NB: `Depend' is a type function, and may not be injective
+ The type variable `a0' is ambiguous
+ Expected type: [Depend a] -> Bool
+ Actual type: [Depend a0] -> Bool
+ When checking that `isValid'
+ has the inferred type `forall a. Bug a => [Depend a] -> Bool'
+ Probable cause: the inferred type is ambiguous
diff --git a/testsuite/tests/indexed-types/should_fail/T1900.stderr b/testsuite/tests/indexed-types/should_fail/T1900.stderr index 93b566d972..6d7eb62e30 100644 --- a/testsuite/tests/indexed-types/should_fail/T1900.stderr +++ b/testsuite/tests/indexed-types/should_fail/T1900.stderr @@ -1,21 +1,13 @@ - -T1900.hs:11:12: - No instance for (Num ()) arising from a use of `+' - In the expression: (+ 1) - In an equation for `trans': trans = (+ 1) - In the instance declaration for `Bug Int' - -T1900.hs:14:16: - Could not deduce (Depend s0 ~ Depend s) - from the context (Bug s) - bound by the type signature for check :: Bug s => Depend s -> Bool - at T1900.hs:13:10-36 - NB: `Depend' is a type function, and may not be injective - The type variable `s0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Relevant bindings include - check :: Depend s -> Bool (bound at T1900.hs:14:1) - d :: Depend s (bound at T1900.hs:14:7) - In the return type of a call of `trans' - In the second argument of `(==)', namely `trans d' - In the expression: d == trans d +
+T1900.hs:13:10:
+ Could not deduce (Depend s0 ~ Depend s)
+ from the context (Bug s)
+ bound by the type signature for check :: Bug s => Depend s -> Bool
+ at T1900.hs:13:10-36
+ NB: `Depend' is a type function, and may not be injective
+ The type variable `s0' is ambiguous
+ Expected type: Depend s -> Bool
+ Actual type: Depend s0 -> Bool
+ In the ambiguity check for: forall s. Bug s => Depend s -> Bool
+ In the type signature for `check':
+ check :: Bug s => Depend s -> Bool
diff --git a/testsuite/tests/indexed-types/should_fail/T2544.stderr b/testsuite/tests/indexed-types/should_fail/T2544.stderr index bd816720c3..fae7cbf284 100644 --- a/testsuite/tests/indexed-types/should_fail/T2544.stderr +++ b/testsuite/tests/indexed-types/should_fail/T2544.stderr @@ -1,30 +1,28 @@ - -T2544.hs:15:18: - Could not deduce (IxMap i0 ~ IxMap l) - from the context (Ix l, Ix r) - bound by the instance declaration at T2544.hs:13:10-37 - NB: `IxMap' is a type function, and may not be injective - The type variable `i0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Expected type: IxMap l [Int] - Actual type: IxMap i0 [Int] - Relevant bindings include - empty :: IxMap (l :|: r) [Int] (bound at T2544.hs:15:4) - In the first argument of `BiApp', namely `empty' - In the expression: BiApp empty empty - In an equation for `empty': empty = BiApp empty empty - -T2544.hs:15:24: - Could not deduce (IxMap i1 ~ IxMap r) - from the context (Ix l, Ix r) - bound by the instance declaration at T2544.hs:13:10-37 - NB: `IxMap' is a type function, and may not be injective - The type variable `i1' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Expected type: IxMap r [Int] - Actual type: IxMap i1 [Int] - Relevant bindings include - empty :: IxMap (l :|: r) [Int] (bound at T2544.hs:15:4) - In the second argument of `BiApp', namely `empty' - In the expression: BiApp empty empty - In an equation for `empty': empty = BiApp empty empty +
+T2544.hs:15:18:
+ Could not deduce (IxMap i0 ~ IxMap l)
+ from the context (Ix l, Ix r)
+ bound by the instance declaration at T2544.hs:13:10-37
+ NB: `IxMap' is a type function, and may not be injective
+ The type variable `i0' is ambiguous
+ Expected type: IxMap l [Int]
+ Actual type: IxMap i0 [Int]
+ Relevant bindings include
+ empty :: IxMap (l :|: r) [Int] (bound at T2544.hs:15:4)
+ In the first argument of `BiApp', namely `empty'
+ In the expression: BiApp empty empty
+ In an equation for `empty': empty = BiApp empty empty
+
+T2544.hs:15:24:
+ Could not deduce (IxMap i1 ~ IxMap r)
+ from the context (Ix l, Ix r)
+ bound by the instance declaration at T2544.hs:13:10-37
+ NB: `IxMap' is a type function, and may not be injective
+ The type variable `i1' is ambiguous
+ Expected type: IxMap r [Int]
+ Actual type: IxMap i1 [Int]
+ Relevant bindings include
+ empty :: IxMap (l :|: r) [Int] (bound at T2544.hs:15:4)
+ In the second argument of `BiApp', namely `empty'
+ In the expression: BiApp empty empty
+ In an equation for `empty': empty = BiApp empty empty
diff --git a/testsuite/tests/indexed-types/should_fail/T2627b.stderr b/testsuite/tests/indexed-types/should_fail/T2627b.stderr index acf77ab303..871d455ea8 100644 --- a/testsuite/tests/indexed-types/should_fail/T2627b.stderr +++ b/testsuite/tests/indexed-types/should_fail/T2627b.stderr @@ -1,9 +1,8 @@ - -T2627b.hs:20:24: - Occurs check: cannot construct the infinite type: - a0 ~ Dual (Dual a0) - The type variable `a0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - In the expression: conn undefined undefined - In an equation for `conn': - conn (Rd k) (Wr a r) = conn undefined undefined +
+T2627b.hs:20:24:
+ Occurs check: cannot construct the infinite type:
+ a0 ~ Dual (Dual a0)
+ The type variable `a0' is ambiguous
+ In the expression: conn undefined undefined
+ In an equation for `conn':
+ conn (Rd k) (Wr a r) = conn undefined undefined
diff --git a/testsuite/tests/indexed-types/should_fail/T2693.hs b/testsuite/tests/indexed-types/should_fail/T2693.hs index e986652331..d60293a441 100644 --- a/testsuite/tests/indexed-types/should_fail/T2693.hs +++ b/testsuite/tests/indexed-types/should_fail/T2693.hs @@ -1,4 +1,5 @@ -{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE AllowAmbiguousTypes, TypeFamilies #-} +-- Type of x is ambiguous module T2693 where diff --git a/testsuite/tests/indexed-types/should_fail/T2693.stderr b/testsuite/tests/indexed-types/should_fail/T2693.stderr index b02edd1ad1..4427018fd0 100644 --- a/testsuite/tests/indexed-types/should_fail/T2693.stderr +++ b/testsuite/tests/indexed-types/should_fail/T2693.stderr @@ -1,9 +1,8 @@ -T2693.hs:10:7:
+T2693.hs:11:7:
Couldn't match expected type `TFn a' with actual type `TFn a0'
NB: `TFn' is a type function, and may not be injective
The type variable `a0' is ambiguous
- Possible fix: add a type signature that fixes these type variable(s)
When checking that `x' has the inferred type `forall a. TFn a'
Probable cause: the inferred type is ambiguous
In the expression:
@@ -15,28 +14,25 @@ T2693.hs:10:7: let n = ...;
return () }
-T2693.hs:18:15:
+T2693.hs:19:15:
Couldn't match expected type `(a2, b0)' with actual type `TFn a3'
The type variables `a2', `b0', `a3' are ambiguous
- Possible fix: add a type signature that fixes these type variable(s)
- Relevant bindings include n :: a2 (bound at T2693.hs:18:7)
+ Relevant bindings include n :: a2 (bound at T2693.hs:19:7)
In the first argument of `fst', namely `x'
In the first argument of `(+)', namely `fst x'
In the expression: fst x + snd x
-T2693.hs:18:23:
+T2693.hs:19:23:
Couldn't match expected type `(a4, a2)' with actual type `TFn a5'
The type variables `a2', `a4', `a5' are ambiguous
- Possible fix: add a type signature that fixes these type variable(s)
- Relevant bindings include n :: a2 (bound at T2693.hs:18:7)
+ Relevant bindings include n :: a2 (bound at T2693.hs:19:7)
In the first argument of `snd', namely `x'
In the second argument of `(+)', namely `snd x'
In the expression: fst x + snd x
-T2693.hs:28:20:
+T2693.hs:29:20:
Couldn't match type `TFn a0' with `PVR a1'
The type variables `a0', `a1' are ambiguous
- Possible fix: add a type signature that fixes these type variable(s)
Expected type: () -> Maybe (PVR a1)
Actual type: () -> Maybe (TFn a0)
In the first argument of `mapM', namely `g'
diff --git a/testsuite/tests/indexed-types/should_fail/T4099.hs b/testsuite/tests/indexed-types/should_fail/T4099.hs index 1ca3c7a4a5..e0c41179ca 100644 --- a/testsuite/tests/indexed-types/should_fail/T4099.hs +++ b/testsuite/tests/indexed-types/should_fail/T4099.hs @@ -4,11 +4,11 @@ module T4099 where type family T a -foo :: T a -> Int +foo :: a -> T a -> Int foo x = error "urk" -bar1 :: T b -> Int -bar1 x = foo x +bar1 :: b -> T b -> Int +bar1 a x = foo (error "urk") x -bar2 :: Maybe b -> Int -bar2 x = foo x +bar2 :: b -> Maybe b -> Int +bar2 a x = foo (error "urk") x diff --git a/testsuite/tests/indexed-types/should_fail/T4099.stderr b/testsuite/tests/indexed-types/should_fail/T4099.stderr index 74410ec108..60e379525a 100644 --- a/testsuite/tests/indexed-types/should_fail/T4099.stderr +++ b/testsuite/tests/indexed-types/should_fail/T4099.stderr @@ -1,23 +1,23 @@ - -T4099.hs:11:14: - Couldn't match expected type `T a0' with actual type `T b' - NB: `T' is a type function, and may not be injective - The type variable `a0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Relevant bindings include - bar1 :: T b -> Int (bound at T4099.hs:11:1) - x :: T b (bound at T4099.hs:11:6) - In the first argument of `foo', namely `x' - In the expression: foo x - In an equation for `bar1': bar1 x = foo x - -T4099.hs:14:14: - Couldn't match expected type `T a1' with actual type `Maybe b' - The type variable `a1' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Relevant bindings include - bar2 :: Maybe b -> Int (bound at T4099.hs:14:1) - x :: Maybe b (bound at T4099.hs:14:6) - In the first argument of `foo', namely `x' - In the expression: foo x - In an equation for `bar2': bar2 x = foo x +
+T4099.hs:11:30:
+ Couldn't match expected type `T a0' with actual type `T b'
+ NB: `T' is a type function, and may not be injective
+ The type variable `a0' is ambiguous
+ Relevant bindings include
+ bar1 :: b -> T b -> Int (bound at T4099.hs:11:1)
+ a :: b (bound at T4099.hs:11:6)
+ x :: T b (bound at T4099.hs:11:8)
+ In the second argument of `foo', namely `x'
+ In the expression: foo (error "urk") x
+ In an equation for `bar1': bar1 a x = foo (error "urk") x
+
+T4099.hs:14:30:
+ Couldn't match expected type `T a1' with actual type `Maybe b'
+ The type variable `a1' is ambiguous
+ Relevant bindings include
+ bar2 :: b -> Maybe b -> Int (bound at T4099.hs:14:1)
+ a :: b (bound at T4099.hs:14:6)
+ x :: Maybe b (bound at T4099.hs:14:8)
+ In the second argument of `foo', namely `x'
+ In the expression: foo (error "urk") x
+ In an equation for `bar2': bar2 a x = foo (error "urk") x
diff --git a/testsuite/tests/indexed-types/should_fail/T4485.stderr b/testsuite/tests/indexed-types/should_fail/T4485.stderr index d07eedce97..3588869520 100644 --- a/testsuite/tests/indexed-types/should_fail/T4485.stderr +++ b/testsuite/tests/indexed-types/should_fail/T4485.stderr @@ -1,31 +1,30 @@ - -T4485.hs:47:15: - Overlapping instances for EmbedAsChild - (IdentityT IO) (XMLGenT m0 (XML m0)) - arising from a use of `asChild' - Matching instances: - instance [overlap ok] (EmbedAsChild m c, m1 ~ m) => - EmbedAsChild m (XMLGenT m1 c) - -- Defined at T4485.hs:29:10 - instance [overlap ok] EmbedAsChild - (IdentityT IO) (XMLGenT Identity ()) - -- Defined at T4485.hs:42:10 - (The choice depends on the instantiation of `m0' - To pick the first instance above, use -XIncoherentInstances - when compiling the other instance declarations) - In the expression: asChild - In the expression: asChild $ (genElement "foo") - In an equation for `asChild': - asChild b = asChild $ (genElement "foo") - -T4485.hs:47:26: - No instance for (XMLGen m0) arising from a use of `genElement' - The type variable `m0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Note: there is a potential instance available: - instance [overlap ok] XMLGen (IdentityT m) - -- Defined at T4485.hs:36:10 - In the second argument of `($)', namely `(genElement "foo")' - In the expression: asChild $ (genElement "foo") - In an equation for `asChild': - asChild b = asChild $ (genElement "foo") +
+T4485.hs:47:15:
+ Overlapping instances for EmbedAsChild
+ (IdentityT IO) (XMLGenT m0 (XML m0))
+ arising from a use of `asChild'
+ Matching instances:
+ instance [overlap ok] (EmbedAsChild m c, m1 ~ m) =>
+ EmbedAsChild m (XMLGenT m1 c)
+ -- Defined at T4485.hs:29:10
+ instance [overlap ok] EmbedAsChild
+ (IdentityT IO) (XMLGenT Identity ())
+ -- Defined at T4485.hs:42:10
+ (The choice depends on the instantiation of `m0'
+ To pick the first instance above, use -XIncoherentInstances
+ when compiling the other instance declarations)
+ In the expression: asChild
+ In the expression: asChild $ (genElement "foo")
+ In an equation for `asChild':
+ asChild b = asChild $ (genElement "foo")
+
+T4485.hs:47:26:
+ No instance for (XMLGen m0) arising from a use of `genElement'
+ The type variable `m0' is ambiguous
+ Note: there is a potential instance available:
+ instance [overlap ok] XMLGen (IdentityT m)
+ -- Defined at T4485.hs:36:10
+ In the second argument of `($)', namely `(genElement "foo")'
+ In the expression: asChild $ (genElement "foo")
+ In an equation for `asChild':
+ asChild b = asChild $ (genElement "foo")
diff --git a/testsuite/tests/indexed-types/should_fail/T5934.hs b/testsuite/tests/indexed-types/should_fail/T5934.hs index 2af0b97887..892340e5ab 100644 --- a/testsuite/tests/indexed-types/should_fail/T5934.hs +++ b/testsuite/tests/indexed-types/should_fail/T5934.hs @@ -1,4 +1,6 @@ -{-# LANGUAGE RankNTypes, TypeFamilies, KindSignatures #-} +{-# LANGUAGE AllowAmbiguousTypes, RankNTypes, TypeFamilies, KindSignatures #-} + +-- The type of 'run' is actually ambiguous module T5934 where import Control.Monad.ST diff --git a/testsuite/tests/indexed-types/should_fail/T5934.stderr b/testsuite/tests/indexed-types/should_fail/T5934.stderr index 387dde4dc6..8925899346 100644 --- a/testsuite/tests/indexed-types/should_fail/T5934.stderr +++ b/testsuite/tests/indexed-types/should_fail/T5934.stderr @@ -1,5 +1,5 @@ -T5934.hs:10:7:
+T5934.hs:12:7:
Cannot instantiate unification variable `a0'
with a type involving foralls: (forall s. GenST s) -> Int
Perhaps you want -XImpredicativeTypes
diff --git a/testsuite/tests/indexed-types/should_fail/T6123.stderr b/testsuite/tests/indexed-types/should_fail/T6123.stderr index 4f7f6919f4..cf8eedda06 100644 --- a/testsuite/tests/indexed-types/should_fail/T6123.stderr +++ b/testsuite/tests/indexed-types/should_fail/T6123.stderr @@ -1,11 +1,7 @@ - -T6123.hs:10:14: - Occurs check: cannot construct the infinite type: a0 ~ Id a0 - The type variable `a0' is ambiguous - Possible cause: the monomorphism restriction applied to: - `cundefined' - Probable fix: give these definition(s) an explicit type signature - or use -XNoMonomorphismRestriction - Relevant bindings include cundefined :: a0 (bound at T6123.hs:10:1) - In the expression: cid undefined - In an equation for `cundefined': cundefined = cid undefined +
+T6123.hs:10:14:
+ Occurs check: cannot construct the infinite type: a0 ~ Id a0
+ The type variable `a0' is ambiguous
+ Relevant bindings include cundefined :: a0 (bound at T6123.hs:10:1)
+ In the expression: cid undefined
+ In an equation for `cundefined': cundefined = cid undefined
diff --git a/testsuite/tests/polykinds/T5770.hs b/testsuite/tests/polykinds/T5770.hs index 132a1538a8..96e75d90da 100644 --- a/testsuite/tests/polykinds/T5770.hs +++ b/testsuite/tests/polykinds/T5770.hs @@ -11,11 +11,11 @@ convert = convert type family Foo a type instance Foo Int = Bool -barT5770 :: forall a b c dummya. (b -> c) -> ((Foo a) -> c) -barT5770 f = (convert f :: (Foo a) -> c) +barT5770 :: forall a b c dummya. (b -> c) -> Foo a -> a +barT5770 f = (convert f :: Foo a -> a) -barT5769 :: forall b a. b -> (Foo a) -barT5769 f = (convert f :: (Foo a)) +barT5769 :: forall b a. b -> (a, Foo a) +barT5769 f = (convert f :: (a, Foo a)) -barT5768 :: forall b a. b -> (Foo a) -barT5768 f = (convert f :: (Foo a)) +barT5768 :: forall a b. b -> (a, Foo a) +barT5768 f = (convert f :: (a, Foo a)) diff --git a/testsuite/tests/polykinds/T6020.hs b/testsuite/tests/polykinds/T6020.hs index f9812392a0..a044efe380 100644 --- a/testsuite/tests/polykinds/T6020.hs +++ b/testsuite/tests/polykinds/T6020.hs @@ -7,9 +7,15 @@ module T6020 where class Id (a :: k) (b :: k) | a -> b
instance Id a a
-class Test (x :: a) (y :: a) | x -> y
-instance (Id x y, Id y z) => Test x z
+f :: Id x y => x -> y
+f = f
-test :: Test True True => ()
-test = ()
+--class Test (x :: a) (y :: a) | x -> y
+--instance (Id x y, Id y z) => Test x z
+
+-- (Id x0 y0, Id y0 z0, x~x0, z~z0)
+-- (Id x y0, Id y0 z, y0~z, y0~y)
+
+--test :: Test True True => ()
+--test = ()
diff --git a/testsuite/tests/polykinds/T7090.hs b/testsuite/tests/polykinds/T7090.hs index 855633bbef..2364b0cd5a 100644 --- a/testsuite/tests/polykinds/T7090.hs +++ b/testsuite/tests/polykinds/T7090.hs @@ -21,6 +21,8 @@ type family (a :: Nat) :==: (b :: Nat) :: Bool boolToProp :: (a :==: b) ~ True => Dict (a ~ b) boolToProp = undefined -foo :: forall n. (Succ n :==: Plus n One) ~ True => () +data T (n :: Nat) = MkT + +foo :: forall n. (Succ n :==: Plus n One) ~ True => T n foo = case (boolToProp :: Dict (Succ n ~ Plus n One)) of - Dict -> () + Dict -> MkT diff --git a/testsuite/tests/rebindable/rebindable6.stderr b/testsuite/tests/rebindable/rebindable6.stderr index 5130968c02..a12cef09f2 100644 --- a/testsuite/tests/rebindable/rebindable6.stderr +++ b/testsuite/tests/rebindable/rebindable6.stderr @@ -1,70 +1,67 @@ - -rebindable6.hs:106:17: - No instance for (HasSeq (IO a -> t0 -> IO b)) - arising from a do statement - The type variable `t0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Relevant bindings include - test_do :: IO a -> IO (Maybe b) -> IO b - (bound at rebindable6.hs:104:9) - f :: IO a (bound at rebindable6.hs:104:17) - g :: IO (Maybe b) (bound at rebindable6.hs:104:19) - Note: there is a potential instance available: - instance HasSeq (IO a -> IO b -> IO b) - -- Defined at rebindable6.hs:52:18 - In a stmt of a 'do' block: f - In the expression: - do { f; - Just (b :: b) <- g; - return b } - In an equation for `test_do': - test_do f g - = do { f; - Just (b :: b) <- g; - return b } - -rebindable6.hs:107:17: - No instance for (HasBind (IO (Maybe b) -> (Maybe b -> t1) -> t0)) - arising from a do statement - The type variables `t0', `t1' are ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Relevant bindings include - test_do :: IO a -> IO (Maybe b) -> IO b - (bound at rebindable6.hs:104:9) - g :: IO (Maybe b) (bound at rebindable6.hs:104:19) - Note: there is a potential instance available: - instance HasBind (IO a -> (a -> IO b) -> IO b) - -- Defined at rebindable6.hs:47:18 - In a stmt of a 'do' block: Just (b :: b) <- g - In the expression: - do { f; - Just (b :: b) <- g; - return b } - In an equation for `test_do': - test_do f g - = do { f; - Just (b :: b) <- g; - return b } - -rebindable6.hs:108:17: - No instance for (HasReturn (b -> t1)) - arising from a use of `return' - The type variable `t1' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Relevant bindings include - test_do :: IO a -> IO (Maybe b) -> IO b - (bound at rebindable6.hs:104:9) - g :: IO (Maybe b) (bound at rebindable6.hs:104:19) - b :: b (bound at rebindable6.hs:107:23) - Note: there is a potential instance available: - instance HasReturn (a -> IO a) -- Defined at rebindable6.hs:42:18 - In a stmt of a 'do' block: return b - In the expression: - do { f; - Just (b :: b) <- g; - return b } - In an equation for `test_do': - test_do f g - = do { f; - Just (b :: b) <- g; - return b } +
+rebindable6.hs:106:17:
+ No instance for (HasSeq (IO a -> t0 -> IO b))
+ arising from a do statement
+ The type variable `t0' is ambiguous
+ Relevant bindings include
+ test_do :: IO a -> IO (Maybe b) -> IO b
+ (bound at rebindable6.hs:104:9)
+ f :: IO a (bound at rebindable6.hs:104:17)
+ g :: IO (Maybe b) (bound at rebindable6.hs:104:19)
+ Note: there is a potential instance available:
+ instance HasSeq (IO a -> IO b -> IO b)
+ -- Defined at rebindable6.hs:52:18
+ In a stmt of a 'do' block: f
+ In the expression:
+ do { f;
+ Just (b :: b) <- g;
+ return b }
+ In an equation for `test_do':
+ test_do f g
+ = do { f;
+ Just (b :: b) <- g;
+ return b }
+
+rebindable6.hs:107:17:
+ No instance for (HasBind (IO (Maybe b) -> (Maybe b -> t1) -> t0))
+ arising from a do statement
+ The type variables `t0', `t1' are ambiguous
+ Relevant bindings include
+ test_do :: IO a -> IO (Maybe b) -> IO b
+ (bound at rebindable6.hs:104:9)
+ g :: IO (Maybe b) (bound at rebindable6.hs:104:19)
+ Note: there is a potential instance available:
+ instance HasBind (IO a -> (a -> IO b) -> IO b)
+ -- Defined at rebindable6.hs:47:18
+ In a stmt of a 'do' block: Just (b :: b) <- g
+ In the expression:
+ do { f;
+ Just (b :: b) <- g;
+ return b }
+ In an equation for `test_do':
+ test_do f g
+ = do { f;
+ Just (b :: b) <- g;
+ return b }
+
+rebindable6.hs:108:17:
+ No instance for (HasReturn (b -> t1))
+ arising from a use of `return'
+ The type variable `t1' is ambiguous
+ Relevant bindings include
+ test_do :: IO a -> IO (Maybe b) -> IO b
+ (bound at rebindable6.hs:104:9)
+ g :: IO (Maybe b) (bound at rebindable6.hs:104:19)
+ b :: b (bound at rebindable6.hs:107:23)
+ Note: there is a potential instance available:
+ instance HasReturn (a -> IO a) -- Defined at rebindable6.hs:42:18
+ In a stmt of a 'do' block: return b
+ In the expression:
+ do { f;
+ Just (b :: b) <- g;
+ return b }
+ In an equation for `test_do':
+ test_do f g
+ = do { f;
+ Just (b :: b) <- g;
+ return b }
diff --git a/testsuite/tests/simplCore/should_compile/T7360.hs b/testsuite/tests/simplCore/should_compile/T7360.hs index b877da6a0d..99b7a7ac46 100644 --- a/testsuite/tests/simplCore/should_compile/T7360.hs +++ b/testsuite/tests/simplCore/should_compile/T7360.hs @@ -6,11 +6,14 @@ module T7360 where data Foo = Foo1 | Foo2 | Foo3 !Int fun1 :: Foo -> () +{-# NOINLINE fun1 #-} fun1 x = case x of Foo1 -> () Foo2 -> () Foo3 {} -> () -fun2 x = case x of +fun2 x = (fun1 Foo1, -- Keep -ddump-simpl output + -- in a predicatable order + case x of [] -> length x - (_:_) -> length x + (_:_) -> length x) diff --git a/testsuite/tests/simplCore/should_compile/T7360.stderr b/testsuite/tests/simplCore/should_compile/T7360.stderr index 5cc46cb80f..895a411386 100644 --- a/testsuite/tests/simplCore/should_compile/T7360.stderr +++ b/testsuite/tests/simplCore/should_compile/T7360.stderr @@ -1,47 +1,50 @@ - -==================== Tidy Core ==================== -Result size of Tidy Core = {terms: 20, types: 17, coercions: 0} - -T7360.$WFoo3 [InlPrag=INLINE] :: GHC.Types.Int -> T7360.Foo -[GblId[DataConWrapper], - Arity=1, - Caf=NoCafRefs, - Str=DmdType S, - Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, - ConLike=True, WorkFree=True, Expandable=True, - Guidance=ALWAYS_IF(unsat_ok=False,boring_ok=False) - Tmpl= \ (dt [Occ=Once] :: GHC.Types.Int) -> - case dt of dt { __DEFAULT -> T7360.Foo3 dt }}] -T7360.$WFoo3 = - \ (dt [Occ=Once] :: GHC.Types.Int) -> - case dt of dt { __DEFAULT -> T7360.Foo3 dt } - -T7360.fun1 :: T7360.Foo -> () -[GblId, - Arity=1, - Caf=NoCafRefs, - Str=DmdType S, - Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=1, Value=True, - ConLike=True, WorkFree=True, Expandable=True, - Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=True)}] -T7360.fun1 = - \ (x :: T7360.Foo) -> case x of _ { __DEFAULT -> GHC.Tuple.() } - -T7360.fun2 :: forall a. [a] -> GHC.Types.Int -[GblId, - Arity=1, - Caf=NoCafRefs, - Str=DmdType Sm, - Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, - ConLike=True, WorkFree=True, Expandable=True, - Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) - Tmpl= \ (@ a) (x [Occ=Once] :: [a]) -> - case GHC.List.$wlen @ a x 0 of ww { __DEFAULT -> - GHC.Types.I# ww - }}] -T7360.fun2 = - \ (@ a) (x :: [a]) -> - case GHC.List.$wlen @ a x 0 of ww { __DEFAULT -> GHC.Types.I# ww } - - - +
+==================== Tidy Core ====================
+Result size of Tidy Core = {terms: 25, types: 22, coercions: 0}
+
+T7360.$WFoo3 [InlPrag=INLINE] :: GHC.Types.Int -> T7360.Foo
+[GblId[DataConWrapper],
+ Arity=1,
+ Caf=NoCafRefs,
+ Str=DmdType S,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
+ ConLike=True, WorkFree=True, Expandable=True,
+ Guidance=ALWAYS_IF(unsat_ok=False,boring_ok=False)
+ Tmpl= \ (dt [Occ=Once] :: GHC.Types.Int) ->
+ case dt of dt { __DEFAULT -> T7360.Foo3 dt }}]
+T7360.$WFoo3 =
+ \ (dt [Occ=Once] :: GHC.Types.Int) ->
+ case dt of dt { __DEFAULT -> T7360.Foo3 dt }
+
+T7360.fun1 [InlPrag=NOINLINE] :: T7360.Foo -> ()
+[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType S]
+T7360.fun1 =
+ \ (x :: T7360.Foo) -> case x of _ { __DEFAULT -> GHC.Tuple.() }
+
+T7360.fun3 :: ()
+[GblId,
+ Str=DmdType,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=False,
+ ConLike=False, WorkFree=False, Expandable=False,
+ Guidance=IF_ARGS [] 20 0}]
+T7360.fun3 = T7360.fun1 T7360.Foo1
+
+T7360.fun2 :: forall a. [a] -> ((), GHC.Types.Int)
+[GblId,
+ Arity=1,
+ Str=DmdType Lm,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
+ ConLike=True, WorkFree=True, Expandable=True,
+ Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
+ Tmpl= \ (@ a) (x [Occ=Once] :: [a]) ->
+ (T7360.fun3,
+ case GHC.List.$wlen @ a x 0 of ww { __DEFAULT ->
+ GHC.Types.I# ww
+ })}]
+T7360.fun2 =
+ \ (@ a) (x :: [a]) ->
+ (T7360.fun3,
+ case GHC.List.$wlen @ a x 0 of ww { __DEFAULT -> GHC.Types.I# ww })
+
+
+
diff --git a/testsuite/tests/typecheck/should_compile/holes2.stderr b/testsuite/tests/typecheck/should_compile/holes2.stderr index 433b5a0b3e..13604264e1 100644 --- a/testsuite/tests/typecheck/should_compile/holes2.stderr +++ b/testsuite/tests/typecheck/should_compile/holes2.stderr @@ -1,20 +1,19 @@ - -holes2.hs:7:5: Warning: - No instance for (Show a0) arising from a use of `show' - The type variable `a0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Note: there are several potential instances: - instance Show Double -- Defined in `GHC.Float' - instance Show Float -- Defined in `GHC.Float' - instance (Integral a, Show a) => Show (GHC.Real.Ratio a) - -- Defined in `GHC.Real' - ...plus 23 others - In the expression: show _ - In an equation for `f': f = show _ - -holes2.hs:7:10: Warning: - Found hole `_' with type a0 - Where: `a0' is an ambiguous type variable - In the first argument of `show', namely `_' - In the expression: show _ - In an equation for `f': f = show _ +
+holes2.hs:7:5: Warning:
+ No instance for (Show a0) arising from a use of `show'
+ The type variable `a0' is ambiguous
+ Note: there are several potential instances:
+ instance Show Double -- Defined in `GHC.Float'
+ instance Show Float -- Defined in `GHC.Float'
+ instance (Integral a, Show a) => Show (GHC.Real.Ratio a)
+ -- Defined in `GHC.Real'
+ ...plus 23 others
+ In the expression: show _
+ In an equation for `f': f = show _
+
+holes2.hs:7:10: Warning:
+ Found hole `_' with type a0
+ Where: `a0' is an ambiguous type variable
+ In the first argument of `show', namely `_'
+ In the expression: show _
+ In an equation for `f': f = show _
diff --git a/testsuite/tests/typecheck/should_compile/tc168.stderr b/testsuite/tests/typecheck/should_compile/tc168.stderr index 8c0c81330f..96fa5a0629 100644 --- a/testsuite/tests/typecheck/should_compile/tc168.stderr +++ b/testsuite/tests/typecheck/should_compile/tc168.stderr @@ -1,12 +1,11 @@ - -tc168.hs:17:1: - Could not deduce (C a1 (a, b0)) - arising from the ambiguity check for `g' - from the context (C a1 (a, b)) - bound by the inferred type for `g': C a1 (a, b) => a1 -> a - at tc168.hs:17:1-16 - The type variable `b0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - When checking that `g' - has the inferred type `forall a b a1. C a1 (a, b) => a1 -> a' - Probable cause: the inferred type is ambiguous +
+tc168.hs:17:1:
+ Could not deduce (C a1 (a, b0))
+ arising from the ambiguity check for `g'
+ from the context (C a1 (a, b))
+ bound by the inferred type for `g': C a1 (a, b) => a1 -> a
+ at tc168.hs:17:1-16
+ The type variable `b0' is ambiguous
+ When checking that `g'
+ has the inferred type `forall a b a1. C a1 (a, b) => a1 -> a'
+ Probable cause: the inferred type is ambiguous
diff --git a/testsuite/tests/typecheck/should_fail/FrozenErrorTests.hs b/testsuite/tests/typecheck/should_fail/FrozenErrorTests.hs index 479087b0d6..390333c1b2 100644 --- a/testsuite/tests/typecheck/should_fail/FrozenErrorTests.hs +++ b/testsuite/tests/typecheck/should_fail/FrozenErrorTests.hs @@ -6,10 +6,6 @@ data T a where MkT :: a -> T a MkT3 :: forall a. (a ~ Bool) => T a --- Occurs checks in givens -foo :: forall a. (a ~ T a) => a -> a -foo x = x - -- Mismatches in givens bloh :: T Int -> () bloh x = case x of diff --git a/testsuite/tests/typecheck/should_fail/FrozenErrorTests.stderr b/testsuite/tests/typecheck/should_fail/FrozenErrorTests.stderr index 0e2ec6c2ff..5a36d7d54b 100644 --- a/testsuite/tests/typecheck/should_fail/FrozenErrorTests.stderr +++ b/testsuite/tests/typecheck/should_fail/FrozenErrorTests.stderr @@ -1,61 +1,53 @@ - -FrozenErrorTests.hs:10:8: - Couldn't match type `a' with `T a' - `a' is a rigid type variable bound by - the type signature for foo :: a ~ T a => a -> a - at FrozenErrorTests.hs:10:15 - Inaccessible code in - the type signature for foo :: a ~ T a => a -> a - -FrozenErrorTests.hs:16:12: - Couldn't match type `Int' with `Bool' - Inaccessible code in - a pattern with constructor - MkT3 :: forall a. a ~ Bool => T a, - in a case alternative - In the pattern: MkT3 - In a case alternative: MkT3 -> () - In the expression: case x of { MkT3 -> () } - -FrozenErrorTests.hs:30:9: - Occurs check: cannot construct the infinite type: a ~ [a] - Expected type: [a] - Actual type: F a Bool - Relevant bindings include - test1 :: a (bound at FrozenErrorTests.hs:30:1) - In the expression: goo1 False undefined - In an equation for `test1': test1 = goo1 False undefined - -FrozenErrorTests.hs:33:15: - Couldn't match type `Int' with `[Int]' - Expected type: [[Int]] - Actual type: F [Int] Bool - In the first argument of `goo2', namely `(goo1 False undefined)' - In the expression: goo2 (goo1 False undefined) - In an equation for `test2': test2 = goo2 (goo1 False undefined) - -FrozenErrorTests.hs:34:9: - Couldn't match type `Int' with `[Int]' - Expected type: [[Int]] - Actual type: F [Int] Bool - In the expression: goo1 False (goo2 undefined) - In an equation for `test3': test3 = goo1 False (goo2 undefined) - -FrozenErrorTests.hs:49:15: - Couldn't match type `T2 c c' with `M (T2 (T2 c c) c)' - Expected type: T2 (M (T2 (T2 c c) c)) (T2 (T2 c c) c) - Actual type: F (T2 (T2 c c) c) Bool - Relevant bindings include - test4 :: T2 (T2 c c) c (bound at FrozenErrorTests.hs:49:1) - In the first argument of `goo4', namely `(goo3 False undefined)' - In the expression: goo4 (goo3 False undefined) - In an equation for `test4': test4 = goo4 (goo3 False undefined) - -FrozenErrorTests.hs:50:9: - Couldn't match type `T2 c c' with `M (T2 (T2 c c) c)' - Expected type: T2 (M (T2 (T2 c c) c)) (T2 (T2 c c) c) - Actual type: F (T2 (T2 c c) c) Bool - Relevant bindings include - test5 :: T2 (T2 c c) c (bound at FrozenErrorTests.hs:50:1) - In the expression: goo3 False (goo4 undefined) - In an equation for `test5': test5 = goo3 False (goo4 undefined) +
+FrozenErrorTests.hs:12:12:
+ Couldn't match type `Int' with `Bool'
+ Inaccessible code in
+ a pattern with constructor
+ MkT3 :: forall a. a ~ Bool => T a,
+ in a case alternative
+ In the pattern: MkT3
+ In a case alternative: MkT3 -> ()
+ In the expression: case x of { MkT3 -> () }
+
+FrozenErrorTests.hs:26:9:
+ Occurs check: cannot construct the infinite type: a ~ [a]
+ Expected type: [a]
+ Actual type: F a Bool
+ Relevant bindings include
+ test1 :: a (bound at FrozenErrorTests.hs:26:1)
+ In the expression: goo1 False undefined
+ In an equation for `test1': test1 = goo1 False undefined
+
+FrozenErrorTests.hs:29:15:
+ Couldn't match type `Int' with `[Int]'
+ Expected type: [[Int]]
+ Actual type: F [Int] Bool
+ In the first argument of `goo2', namely `(goo1 False undefined)'
+ In the expression: goo2 (goo1 False undefined)
+ In an equation for `test2': test2 = goo2 (goo1 False undefined)
+
+FrozenErrorTests.hs:30:9:
+ Couldn't match type `Int' with `[Int]'
+ Expected type: [[Int]]
+ Actual type: F [Int] Bool
+ In the expression: goo1 False (goo2 undefined)
+ In an equation for `test3': test3 = goo1 False (goo2 undefined)
+
+FrozenErrorTests.hs:45:15:
+ Couldn't match type `T2 c c' with `M (T2 (T2 c c) c)'
+ Expected type: T2 (M (T2 (T2 c c) c)) (T2 (T2 c c) c)
+ Actual type: F (T2 (T2 c c) c) Bool
+ Relevant bindings include
+ test4 :: T2 (T2 c c) c (bound at FrozenErrorTests.hs:45:1)
+ In the first argument of `goo4', namely `(goo3 False undefined)'
+ In the expression: goo4 (goo3 False undefined)
+ In an equation for `test4': test4 = goo4 (goo3 False undefined)
+
+FrozenErrorTests.hs:46:9:
+ Couldn't match type `T2 c c' with `M (T2 (T2 c c) c)'
+ Expected type: T2 (M (T2 (T2 c c) c)) (T2 (T2 c c) c)
+ Actual type: F (T2 (T2 c c) c) Bool
+ Relevant bindings include
+ test5 :: T2 (T2 c c) c (bound at FrozenErrorTests.hs:46:1)
+ In the expression: goo3 False (goo4 undefined)
+ In an equation for `test5': test5 = goo3 False (goo4 undefined)
diff --git a/testsuite/tests/typecheck/should_fail/T1897a.stderr b/testsuite/tests/typecheck/should_fail/T1897a.stderr index 6e5ee1c7a9..eb1204850f 100644 --- a/testsuite/tests/typecheck/should_fail/T1897a.stderr +++ b/testsuite/tests/typecheck/should_fail/T1897a.stderr @@ -1,12 +1,11 @@ - -T1897a.hs:9:1: - Could not deduce (Wob a0 b) - arising from the ambiguity check for `foo' - from the context (Wob a b) - bound by the inferred type for `foo': Wob a b => b -> [b] - at T1897a.hs:9:1-24 - The type variable `a0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - When checking that `foo' - has the inferred type `forall a b. Wob a b => b -> [b]' - Probable cause: the inferred type is ambiguous +
+T1897a.hs:9:1:
+ Could not deduce (Wob a0 b)
+ arising from the ambiguity check for `foo'
+ from the context (Wob a b)
+ bound by the inferred type for `foo': Wob a b => b -> [b]
+ at T1897a.hs:9:1-24
+ The type variable `a0' is ambiguous
+ When checking that `foo'
+ has the inferred type `forall a b. Wob a b => b -> [b]'
+ Probable cause: the inferred type is ambiguous
diff --git a/testsuite/tests/typecheck/should_fail/T5236.stderr b/testsuite/tests/typecheck/should_fail/T5236.stderr index a2da439690..74e4606993 100644 --- a/testsuite/tests/typecheck/should_fail/T5236.stderr +++ b/testsuite/tests/typecheck/should_fail/T5236.stderr @@ -1,10 +1,12 @@ - -T5236.hs:17:5: - Couldn't match type `A' with `B' - When using functional dependencies to combine - Id A A, - arising from the dependency `a -> b' - in the instance declaration at T5236.hs:10:10 - Id A B, arising from a use of `loop' at T5236.hs:17:5-8 - In the expression: loop - In an equation for `f': f = loop +
+T5236.hs:13:9:
+ Couldn't match type `A' with `B'
+ When using functional dependencies to combine
+ Id A A,
+ arising from the dependency `a -> b'
+ in the instance declaration at T5236.hs:10:10
+ Id A B,
+ arising from the type signature for loop :: Id A B => Bool
+ at T5236.hs:13:9-22
+ In the ambiguity check for: Id A B => Bool
+ In the type signature for `loop': loop :: Id A B => Bool
diff --git a/testsuite/tests/typecheck/should_fail/T5300.stderr b/testsuite/tests/typecheck/should_fail/T5300.stderr index 728655f88a..749bd22b2f 100644 --- a/testsuite/tests/typecheck/should_fail/T5300.stderr +++ b/testsuite/tests/typecheck/should_fail/T5300.stderr @@ -1,16 +1,32 @@ - -T5300.hs:15:9: - Could not deduce (C1 a1 b2 c0) arising from a use of `f1' - from the context (Monad m, C1 a1 b1 c1, C2 a2 b2 c2) - bound by the type signature for - f2 :: (Monad m, C1 a1 b1 c1, C2 a2 b2 c2) => - a1 -> StateT (T b2) m a2 - at T5300.hs:14:7-69 - The type variable `c0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Relevant bindings include - f2 :: a1 -> StateT (T b2) m a2 (bound at T5300.hs:15:1) - fm :: a1 (bound at T5300.hs:15:4) - In the first argument of `(>>=)', namely `f1 fm' - In the expression: f1 fm >>= return . undefined - In an equation for `f2': f2 fm = f1 fm >>= return . undefined +
+T5300.hs:11:7:
+ Could not deduce (C1 a b c0)
+ arising from the ambiguity check for `f1'
+ from the context (Monad m, C1 a b c)
+ bound by the type signature for
+ f1 :: (Monad m, C1 a b c) => a -> StateT (T b) m a
+ at T5300.hs:11:7-50
+ The type variable `c0' is ambiguous
+ In the ambiguity check for:
+ forall a b (m :: * -> *) c.
+ (Monad m, C1 a b c) =>
+ a -> StateT (T b) m a
+ In the type signature for `f1':
+ f1 :: (Monad m, C1 a b c) => a -> StateT (T b) m a
+
+T5300.hs:14:7:
+ Could not deduce (C1 a1 b1 c10)
+ arising from the ambiguity check for `f2'
+ from the context (Monad m, C1 a1 b1 c1, C2 a2 b2 c2)
+ bound by the type signature for
+ f2 :: (Monad m, C1 a1 b1 c1, C2 a2 b2 c2) =>
+ a1 -> StateT (T b2) m a2
+ at T5300.hs:14:7-69
+ The type variable `c10' is ambiguous
+ In the ambiguity check for:
+ forall a1 b2 (m :: * -> *) a2 b1 c1 c2.
+ (Monad m, C1 a1 b1 c1, C2 a2 b2 c2) =>
+ a1 -> StateT (T b2) m a2
+ In the type signature for `f2':
+ f2 :: (Monad m, C1 a1 b1 c1, C2 a2 b2 c2) =>
+ a1 -> StateT (T b2) m a2
diff --git a/testsuite/tests/typecheck/should_fail/T5858.stderr b/testsuite/tests/typecheck/should_fail/T5858.stderr index 0ce0d5df9f..0ecd766ec6 100644 --- a/testsuite/tests/typecheck/should_fail/T5858.stderr +++ b/testsuite/tests/typecheck/should_fail/T5858.stderr @@ -1,11 +1,10 @@ - -T5858.hs:11:7: - No instance for (InferOverloaded ([a0], [a1])) - arising from a use of `infer' - The type variables `a0', `a1' are ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Note: there is a potential instance available: - instance t1 ~ String => InferOverloaded (t1, t1) - -- Defined at T5858.hs:8:10 - In the expression: infer ([], []) - In an equation for `foo': foo = infer ([], []) +
+T5858.hs:11:7:
+ No instance for (InferOverloaded ([a0], [a1]))
+ arising from a use of `infer'
+ The type variables `a0', `a1' are ambiguous
+ Note: there is a potential instance available:
+ instance t1 ~ String => InferOverloaded (t1, t1)
+ -- Defined at T5858.hs:8:10
+ In the expression: infer ([], [])
+ In an equation for `foo': foo = infer ([], [])
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 0dc39af06b..bbf6eb6332 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -82,7 +82,7 @@ test('tcfail094', normal, compile_fail, ['']) test('tcfail095', only_compiler_types(['ghc']), compile_fail, ['']) test('tcfail096', normal, compile_fail, ['']) test('tcfail097', normal, compile_fail, ['']) -test('tcfail098', normal, compile, ['']) +test('tcfail098', normal, compile_fail, ['']) test('tcfail099', normal, compile_fail, ['']) test('tcfail100', normal, compile_fail, ['']) test('tcfail101', normal, compile_fail, ['']) diff --git a/testsuite/tests/typecheck/should_fail/tcfail008.stderr b/testsuite/tests/typecheck/should_fail/tcfail008.stderr index c0791f2b2e..7abed93f58 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail008.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail008.stderr @@ -1,23 +1,20 @@ - -tcfail008.hs:3:5: - No instance for (Num a0) arising from the literal `1' - The type variable `a0' is ambiguous - Possible cause: the monomorphism restriction applied to: `o' - Probable fix: give these definition(s) an explicit type signature - or use -XNoMonomorphismRestriction - Relevant bindings include o :: [a0] (bound at tcfail008.hs:3:1) - Note: there are several potential instances: - instance Num Double -- Defined in `GHC.Float' - instance Num Float -- Defined in `GHC.Float' - instance Integral a => Num (GHC.Real.Ratio a) - -- Defined in `GHC.Real' - ...plus three others - In the first argument of `(:)', namely `1' - In the expression: 1 : 2 - In an equation for `o': o = 1 : 2 - -tcfail008.hs:3:7: - No instance for (Num [a0]) arising from the literal `2' - In the second argument of `(:)', namely `2' - In the expression: 1 : 2 - In an equation for `o': o = 1 : 2 +
+tcfail008.hs:3:5:
+ No instance for (Num a0) arising from the literal `1'
+ The type variable `a0' is ambiguous
+ Relevant bindings include o :: [a0] (bound at tcfail008.hs:3:1)
+ Note: there are several potential instances:
+ instance Num Double -- Defined in `GHC.Float'
+ instance Num Float -- Defined in `GHC.Float'
+ instance Integral a => Num (GHC.Real.Ratio a)
+ -- Defined in `GHC.Real'
+ ...plus three others
+ In the first argument of `(:)', namely `1'
+ In the expression: 1 : 2
+ In an equation for `o': o = 1 : 2
+
+tcfail008.hs:3:7:
+ No instance for (Num [a0]) arising from the literal `2'
+ In the second argument of `(:)', namely `2'
+ In the expression: 1 : 2
+ In an equation for `o': o = 1 : 2
diff --git a/testsuite/tests/typecheck/should_fail/tcfail040.stderr b/testsuite/tests/typecheck/should_fail/tcfail040.stderr index 8ee305f03f..003cb9f6d0 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail040.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail040.stderr @@ -1,10 +1,9 @@ - -tcfail040.hs:19:5: - No instance for (ORD a0) arising from a use of `<<' - The type variable `a0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Note: there is a potential instance available: - instance ORD (a -> b) -- Defined at tcfail040.hs:17:10 - In the first argument of `(===)', namely `(<<)' - In the expression: (<<) === (<<) - In an equation for `f': f = (<<) === (<<) +
+tcfail040.hs:19:5:
+ No instance for (ORD a0) arising from a use of `<<'
+ The type variable `a0' is ambiguous
+ Note: there is a potential instance available:
+ instance ORD (a -> b) -- Defined at tcfail040.hs:17:10
+ In the first argument of `(===)', namely `(<<)'
+ In the expression: (<<) === (<<)
+ In an equation for `f': f = (<<) === (<<)
diff --git a/testsuite/tests/typecheck/should_fail/tcfail043.stderr b/testsuite/tests/typecheck/should_fail/tcfail043.stderr index 606750091b..ef4e999996 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail043.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail043.stderr @@ -1,46 +1,40 @@ - -tcfail043.hs:38:17: - No instance for (Ord_ a0) arising from a use of `gt' - The type variable `a0' is ambiguous - Possible cause: the monomorphism restriction applied to: `search' - Probable fix: give these definition(s) an explicit type signature - or use -XNoMonomorphismRestriction - Relevant bindings include - search :: a0 -> [a0] -> Bool (bound at tcfail043.hs:37:1) - a :: a0 (bound at tcfail043.hs:38:6) - bs :: [a0] (bound at tcfail043.hs:38:8) - Note: there is a potential instance available: - instance Ord_ Int -- Defined at tcfail043.hs:34:10 - In the expression: gt (hd bs) a - In the expression: - if gt (hd bs) a then - False - else - if eq a (hd bs) then True else search a (tl bs) - In the expression: - \ a bs - -> if gt (hd bs) a then - False - else - if eq a (hd bs) then True else search a (tl bs) - -tcfail043.hs:40:25: - No instance for (Eq_ a0) arising from a use of `eq' - The type variable `a0' is ambiguous - Possible cause: the monomorphism restriction applied to: `search' - Probable fix: give these definition(s) an explicit type signature - or use -XNoMonomorphismRestriction - Relevant bindings include - search :: a0 -> [a0] -> Bool (bound at tcfail043.hs:37:1) - a :: a0 (bound at tcfail043.hs:38:6) - bs :: [a0] (bound at tcfail043.hs:38:8) - Note: there are several potential instances: - instance Eq_ a => Eq_ [a] -- Defined at tcfail043.hs:23:10 - instance Eq_ Int -- Defined at tcfail043.hs:20:10 - In the expression: eq a (hd bs) - In the expression: if eq a (hd bs) then True else search a (tl bs) - In the expression: - if gt (hd bs) a then - False - else - if eq a (hd bs) then True else search a (tl bs) +
+tcfail043.hs:38:17:
+ No instance for (Ord_ a0) arising from a use of `gt'
+ The type variable `a0' is ambiguous
+ Relevant bindings include
+ search :: a0 -> [a0] -> Bool (bound at tcfail043.hs:37:1)
+ a :: a0 (bound at tcfail043.hs:38:6)
+ bs :: [a0] (bound at tcfail043.hs:38:8)
+ Note: there is a potential instance available:
+ instance Ord_ Int -- Defined at tcfail043.hs:34:10
+ In the expression: gt (hd bs) a
+ In the expression:
+ if gt (hd bs) a then
+ False
+ else
+ if eq a (hd bs) then True else search a (tl bs)
+ In the expression:
+ \ a bs
+ -> if gt (hd bs) a then
+ False
+ else
+ if eq a (hd bs) then True else search a (tl bs)
+
+tcfail043.hs:40:25:
+ No instance for (Eq_ a0) arising from a use of `eq'
+ The type variable `a0' is ambiguous
+ Relevant bindings include
+ search :: a0 -> [a0] -> Bool (bound at tcfail043.hs:37:1)
+ a :: a0 (bound at tcfail043.hs:38:6)
+ bs :: [a0] (bound at tcfail043.hs:38:8)
+ Note: there are several potential instances:
+ instance Eq_ a => Eq_ [a] -- Defined at tcfail043.hs:23:10
+ instance Eq_ Int -- Defined at tcfail043.hs:20:10
+ In the expression: eq a (hd bs)
+ In the expression: if eq a (hd bs) then True else search a (tl bs)
+ In the expression:
+ if gt (hd bs) a then
+ False
+ else
+ if eq a (hd bs) then True else search a (tl bs)
diff --git a/testsuite/tests/typecheck/should_fail/tcfail072.stderr b/testsuite/tests/typecheck/should_fail/tcfail072.stderr index 087d12b400..a71b0effda 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail072.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail072.stderr @@ -1,17 +1,16 @@ - -tcfail072.hs:23:13: - Could not deduce (Ord q0) arising from a use of `g' - from the context (Ord p, Ord q) - bound by the type signature for - g :: (Ord p, Ord q) => AB p q -> Bool - at tcfail072.hs:22:6-38 - The type variable `q0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Note: there are several potential instances: - instance Integral a => Ord (GHC.Real.Ratio a) - -- Defined in `GHC.Real' - instance Ord () -- Defined in `GHC.Classes' - instance (Ord a, Ord b) => Ord (a, b) -- Defined in `GHC.Classes' - ...plus 22 others - In the expression: g A - In an equation for `g': g (B _ _) = g A +
+tcfail072.hs:23:13:
+ Could not deduce (Ord q0) arising from a use of `g'
+ from the context (Ord p, Ord q)
+ bound by the type signature for
+ g :: (Ord p, Ord q) => AB p q -> Bool
+ at tcfail072.hs:22:6-38
+ The type variable `q0' is ambiguous
+ Note: there are several potential instances:
+ instance Integral a => Ord (GHC.Real.Ratio a)
+ -- Defined in `GHC.Real'
+ instance Ord () -- Defined in `GHC.Classes'
+ instance (Ord a, Ord b) => Ord (a, b) -- Defined in `GHC.Classes'
+ ...plus 22 others
+ In the expression: g A
+ In an equation for `g': g (B _ _) = g A
diff --git a/testsuite/tests/typecheck/should_fail/tcfail080.stderr b/testsuite/tests/typecheck/should_fail/tcfail080.stderr index 520078682b..31ad546213 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail080.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail080.stderr @@ -1,14 +1,13 @@ - -tcfail080.hs:27:1: - Could not deduce (Collection c0 a) - arising from the ambiguity check for `q' - from the context (Collection c a) - bound by the inferred type for `q': Collection c a => a -> Bool - at tcfail080.hs:27:1-27 - The type variable `c0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - When checking that `q' - has the inferred type `forall (c :: * -> *) a. - Collection c a => - a -> Bool' - Probable cause: the inferred type is ambiguous +
+tcfail080.hs:27:1:
+ Could not deduce (Collection c0 a)
+ arising from the ambiguity check for `q'
+ from the context (Collection c a)
+ bound by the inferred type for `q': Collection c a => a -> Bool
+ at tcfail080.hs:27:1-27
+ The type variable `c0' is ambiguous
+ When checking that `q'
+ has the inferred type `forall (c :: * -> *) a.
+ Collection c a =>
+ a -> Bool'
+ Probable cause: the inferred type is ambiguous
diff --git a/testsuite/tests/typecheck/should_fail/tcfail083.stderr b/testsuite/tests/typecheck/should_fail/tcfail083.stderr index 589d2c9959..07717e090b 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail083.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail083.stderr @@ -1,21 +1,20 @@ - -tcfail083.hs:8:39: - Constructor `Bar' does not have field `baz' - In the pattern: Bar {flag = f, baz = b} - In the pattern: State {bar = Bar {flag = f, baz = b}} - In an equation for `display': - display (State {bar = Bar {flag = f, baz = b}}) = print (f, b) - -tcfail083.hs:8:53: - No instance for (Show t0) arising from a use of `print' - The type variable `t0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Relevant bindings include b :: t0 (bound at tcfail083.hs:8:45) - Note: there are several potential instances: - instance Show Bar -- Defined at tcfail083.hs:3:43 - instance Show Double -- Defined in `GHC.Float' - instance Show Float -- Defined in `GHC.Float' - ...plus 24 others - In the expression: print (f, b) - In an equation for `display': - display (State {bar = Bar {flag = f, baz = b}}) = print (f, b) +
+tcfail083.hs:8:39:
+ Constructor `Bar' does not have field `baz'
+ In the pattern: Bar {flag = f, baz = b}
+ In the pattern: State {bar = Bar {flag = f, baz = b}}
+ In an equation for `display':
+ display (State {bar = Bar {flag = f, baz = b}}) = print (f, b)
+
+tcfail083.hs:8:53:
+ No instance for (Show t0) arising from a use of `print'
+ The type variable `t0' is ambiguous
+ Relevant bindings include b :: t0 (bound at tcfail083.hs:8:45)
+ Note: there are several potential instances:
+ instance Show Bar -- Defined at tcfail083.hs:3:43
+ instance Show Double -- Defined in `GHC.Float'
+ instance Show Float -- Defined in `GHC.Float'
+ ...plus 24 others
+ In the expression: print (f, b)
+ In an equation for `display':
+ display (State {bar = Bar {flag = f, baz = b}}) = print (f, b)
diff --git a/testsuite/tests/typecheck/should_fail/tcfail097.stderr b/testsuite/tests/typecheck/should_fail/tcfail097.stderr index 2fabae4b40..e7dadd4a6c 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail097.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail097.stderr @@ -1,6 +1,9 @@ - -tcfail097.hs:5:6: - Ambiguous constraint `Eq a' - At least one of the forall'd type variables mentioned by the constraint - must be reachable from the type after the '=>' - In the type signature for `f': f :: Eq a => Int -> Int +
+tcfail097.hs:5:6:
+ Could not deduce (Eq a0) arising from the ambiguity check for `f'
+ from the context (Eq a)
+ bound by the type signature for f :: Eq a => Int -> Int
+ at tcfail097.hs:5:6-23
+ The type variable `a0' is ambiguous
+ In the ambiguity check for: forall a. Eq a => Int -> Int
+ In the type signature for `f': f :: Eq a => Int -> Int
diff --git a/testsuite/tests/typecheck/should_fail/tcfail098.stderr b/testsuite/tests/typecheck/should_fail/tcfail098.stderr index e69de29bb2..8853e69326 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail098.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail098.stderr @@ -0,0 +1,10 @@ +
+tcfail098.hs:12:10:
+ Could not deduce (Bar a0)
+ arising from the ambiguity check for an instance declaration
+ from the context (Bar a)
+ bound by an instance declaration: Bar a => Bar Bool
+ at tcfail098.hs:12:10-26
+ The type variable `a0' is ambiguous
+ In the ambiguity check for: forall a. Bar a => Bar Bool
+ In the instance declaration for `Bar Bool'
diff --git a/testsuite/tests/typecheck/should_fail/tcfail128.stderr b/testsuite/tests/typecheck/should_fail/tcfail128.stderr index 265b783465..9a1564fb85 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail128.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail128.stderr @@ -1,22 +1,21 @@ - -tcfail128.hs:18:16: - No instance for (Data.Array.Base.MArray b0 FlatVector IO) - arising from a use of `thaw' - The type variable `b0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Note: there is a potential instance available: - instance Data.Array.Base.MArray GHC.IOArray.IOArray e IO - -- Defined in `Data.Array.Base' - In a stmt of a 'do' block: v <- thaw tmp - In the expression: - do { let sL = ... - dim = length sL - ....; - v <- thaw tmp; - return () } - In an equation for `main': - main - = do { let sL = ... - ....; - v <- thaw tmp; - return () } +
+tcfail128.hs:18:16:
+ No instance for (Data.Array.Base.MArray b0 FlatVector IO)
+ arising from a use of `thaw'
+ The type variable `b0' is ambiguous
+ Note: there is a potential instance available:
+ instance Data.Array.Base.MArray GHC.IOArray.IOArray e IO
+ -- Defined in `Data.Array.Base'
+ In a stmt of a 'do' block: v <- thaw tmp
+ In the expression:
+ do { let sL = ...
+ dim = length sL
+ ....;
+ v <- thaw tmp;
+ return () }
+ In an equation for `main':
+ main
+ = do { let sL = ...
+ ....;
+ v <- thaw tmp;
+ return () }
diff --git a/testsuite/tests/typecheck/should_fail/tcfail133.stderr b/testsuite/tests/typecheck/should_fail/tcfail133.stderr index b18a27f4c7..4a7c564b3b 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail133.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail133.stderr @@ -5,7 +5,6 @@ tcfail133.hs:2:61: Warning: tcfail133.hs:68:7:
No instance for (Show s0) arising from a use of `show'
The type variable `s0' is ambiguous
- Possible fix: add a type signature that fixes these type variable(s)
Note: there are several potential instances:
instance Show Zero -- Defined at tcfail133.hs:8:29
instance Show One -- Defined at tcfail133.hs:9:28
diff --git a/testsuite/tests/typecheck/should_fail/tcfail142.stderr b/testsuite/tests/typecheck/should_fail/tcfail142.stderr index 635a670495..e0ec8f4ca1 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail142.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail142.stderr @@ -1,7 +1,10 @@ - -tcfail142.hs:21:12: - No instance for (Bar a0 r0) - arising from a use of `bar' - In the first argument of `foo', namely `bar' - In the expression: foo bar - In an equation for `test': test = foo bar +
+tcfail142.hs:18:8:
+ Could not deduce (Bar a0 r)
+ arising from the ambiguity check for `bar'
+ from the context (Bar a r)
+ bound by the type signature for bar :: Bar a r => r -> ()
+ at tcfail142.hs:18:8-25
+ The type variable `a0' is ambiguous
+ In the ambiguity check for: forall r a. Bar a r => r -> ()
+ In the type signature for `bar': bar :: Bar a r => r -> ()
diff --git a/testsuite/tests/typecheck/should_fail/tcfail181.stderr b/testsuite/tests/typecheck/should_fail/tcfail181.stderr index 690cbe7cf1..d6e622cb30 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail181.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail181.stderr @@ -1,17 +1,15 @@ - -tcfail181.hs:17:9: - Could not deduce (Monad m0) arising from a use of `foo' - from the context (Monad m) - bound by the inferred type of - wog :: Monad m => t -> Something (m Bool) e - at tcfail181.hs:17:1-30 - The type variable `m0' is ambiguous - Possible fix: add a type signature that fixes these type variable(s) - Note: there are several potential instances: - instance Monad ((->) r) -- Defined in `GHC.Base' - instance Monad IO -- Defined in `GHC.Base' - instance Monad [] -- Defined in `GHC.Base' - In the expression: foo - In the expression: foo {bar = return True} - In an equation for `wog': wog x = foo {bar = return True} - +
+tcfail181.hs:17:9:
+ Could not deduce (Monad m0) arising from a use of `foo'
+ from the context (Monad m)
+ bound by the inferred type of
+ wog :: Monad m => t -> Something (m Bool) e
+ at tcfail181.hs:17:1-30
+ The type variable `m0' is ambiguous
+ Note: there are several potential instances:
+ instance Monad ((->) r) -- Defined in `GHC.Base'
+ instance Monad IO -- Defined in `GHC.Base'
+ instance Monad [] -- Defined in `GHC.Base'
+ In the expression: foo
+ In the expression: foo {bar = return True}
+ In an equation for `wog': wog x = foo {bar = return True}
diff --git a/testsuite/tests/typecheck/should_run/tcrun035.stderr b/testsuite/tests/typecheck/should_run/tcrun035.stderr index 8c795ce2f3..f0fc2d53b7 100644 --- a/testsuite/tests/typecheck/should_run/tcrun035.stderr +++ b/testsuite/tests/typecheck/should_run/tcrun035.stderr @@ -1,10 +1,11 @@ - -tcrun035.hs:13:12: - Couldn't match type `forall (m :: * -> *). Monad m => m a' - with `IO a' - Expected type: (forall (m :: * -> *). Monad m => m a) -> IO a - Actual type: (forall (m :: * -> *). Monad m => m a) - -> forall (m :: * -> *). Monad m => m a - In the second argument of `(.)', namely `id' - In the expression: id . id - In an equation for `foo': foo = id . id +
+tcrun035.hs:13:7:
+ Couldn't match type `IO a'
+ with `forall (m :: * -> *). Monad m => m a'
+ Expected type: (forall (m :: * -> *). Monad m => m a) -> IO a
+ Actual type: IO a -> IO a
+ Relevant bindings include
+ foo :: (forall (m :: * -> *). Monad m => m a) -> IO a
+ (bound at tcrun035.hs:13:1)
+ In the expression: id . id
+ In an equation for `foo': foo = id . id
|