diff options
author | Dimitrios Vytiniotis <dimitris@microsoft.com> | 2011-11-16 15:52:35 +0000 |
---|---|---|
committer | Dimitrios Vytiniotis <dimitris@microsoft.com> | 2011-11-16 15:52:35 +0000 |
commit | 83e84e35ab4b307381ac0d0cd15df3227496defb (patch) | |
tree | c858825df187de20157b903692bb09bfa8a5a278 | |
parent | efb1debac24e40ad2f720d536abbd48a7bcd0904 (diff) | |
download | haskell-83e84e35ab4b307381ac0d0cd15df3227496defb.tar.gz |
Error message modifications for the new constraint solver.
42 files changed, 930 insertions, 974 deletions
diff --git a/testsuite/tests/annotations/should_fail/annfail08.stderr b/testsuite/tests/annotations/should_fail/annfail08.stderr index e8b14d1f8a..a97ca4e2b5 100644 --- a/testsuite/tests/annotations/should_fail/annfail08.stderr +++ b/testsuite/tests/annotations/should_fail/annfail08.stderr @@ -1,16 +1,15 @@ - -annfail08.hs:9:1: - No instance for (Data.Data.Data (a0 -> a0)) - arising from an annotation - Possible fix: - add an instance declaration for (Data.Data.Data (a0 -> a0)) - In the expression: (id + 1) - In the annotation: {-# ANN f (id + 1) #-} - -annfail08.hs:9:17: - No instance for (Num (a0 -> a0)) - arising from the literal `1' - Possible fix: add an instance declaration for (Num (a0 -> a0)) - In the second argument of `(+)', namely `1' - In the expression: (id + 1) - In the annotation: {-# ANN f (id + 1) #-} +
+annfail08.hs:9:1:
+ No instance for (Data.Data.Data (a0 -> a0))
+ arising from an annotation
+ Possible fix:
+ add an instance declaration for (Data.Data.Data (a0 -> a0))
+ In the expression: (id + 1)
+ In the annotation: {-# ANN f (id + 1) #-}
+
+annfail08.hs:9:15:
+ No instance for (Num (a0 -> a0))
+ arising from a use of `+'
+ Possible fix: add an instance declaration for (Num (a0 -> a0))
+ In the expression: (id + 1)
+ In the annotation: {-# ANN f (id + 1) #-}
diff --git a/testsuite/tests/arrows/should_fail/T5380.stderr b/testsuite/tests/arrows/should_fail/T5380.stderr index f1846dd425..07b89eef84 100644 --- a/testsuite/tests/arrows/should_fail/T5380.stderr +++ b/testsuite/tests/arrows/should_fail/T5380.stderr @@ -1,22 +1,22 @@ - -T5380.hs:7:27: - Couldn't match type `not_bool' with `Bool' - `not_bool' is a rigid type variable bound by - the type signature for - testB :: not_bool -> (() -> ()) -> () -> not_unit - at T5380.hs:7:1 - In the expression: b - In the expression: proc () -> if b then f -< () else f -< () - In an equation for `testB': - testB b f = proc () -> if b then f -< () else f -< () - -T5380.hs:7:47: - Couldn't match type `not_unit' with `()' - `not_unit' is a rigid type variable bound by - the type signature for - testB :: not_bool -> (() -> ()) -> () -> not_unit - at T5380.hs:7:1 - Expected type: () -> not_unit - Actual type: () -> () - In the expression: f - In the expression: proc () -> if b then f -< () else f -< () +
+T5380.hs:7:27:
+ Couldn't match type `not_bool' with `Bool'
+ `not_bool' is a rigid type variable bound by
+ the type signature for
+ testB :: not_bool -> (() -> ()) -> () -> not_unit
+ at T5380.hs:7:1
+ In the expression: b
+ In the expression: proc () -> if b then f -< () else f -< ()
+ In an equation for `testB':
+ testB b f = proc () -> if b then f -< () else f -< ()
+
+T5380.hs:7:34:
+ Couldn't match type `not_unit' with `()'
+ `not_unit' is a rigid type variable bound by
+ the type signature for
+ testB :: not_bool -> (() -> ()) -> () -> not_unit
+ at T5380.hs:7:1
+ Expected type: () -> not_unit
+ Actual type: () -> ()
+ In the expression: f
+ In the expression: proc () -> if b then f -< () else f -< ()
diff --git a/testsuite/tests/deriving/should_fail/T3621.stderr b/testsuite/tests/deriving/should_fail/T3621.stderr index dc9dc849ab..a944956da5 100644 --- a/testsuite/tests/deriving/should_fail/T3621.stderr +++ b/testsuite/tests/deriving/should_fail/T3621.stderr @@ -1,13 +1,9 @@ - -T3621.hs:21:21: - Couldn't match type `s' with `state' - `s' is an unknown type variable - `state' is an unknown type variable - When using functional dependencies to combine - MonadState s (State s), - arising from the dependency `m -> s' - in the instance declaration at T3621.hs:18:10 - MonadState state (State s), - arising from the 'deriving' clause of a data type declaration - at T3621.hs:21:21-36 - When deriving the instance for (MonadState state (WrappedState s)) +
+T3621.hs:21:21:
+ No instance for (MonadState state (State s))
+ arising from the 'deriving' clause of a data type declaration
+ Possible fix:
+ add an instance declaration for (MonadState state (State s))
+ or use a standalone 'deriving instance' declaration,
+ so you can specify the instance context yourself
+ When deriving the instance for (MonadState state (WrappedState s))
diff --git a/testsuite/tests/gadt/T3169.stderr b/testsuite/tests/gadt/T3169.stderr index 100077066c..878324caeb 100644 --- a/testsuite/tests/gadt/T3169.stderr +++ b/testsuite/tests/gadt/T3169.stderr @@ -1,11 +1,11 @@ - -T3169.hs:13:13: - Couldn't match type `elt' with `Map b elt' - `elt' is a rigid type variable bound by - the type signature for - lookup :: (a, b) -> Map (a, b) elt -> Maybe elt - at T3169.hs:12:3 - Expected type: Maybe (Map b elt) - Actual type: Maybe elt - In the return type of a call of `lookup' - In the expression: lookup a m :: Maybe (Map b elt) +
+T3169.hs:13:13:
+ Couldn't match type `elt' with `Map b elt'
+ `elt' is a rigid type variable bound by
+ the type signature for
+ lookup :: (a, b) -> Map (a, b) elt -> Maybe elt
+ at T3169.hs:12:3
+ Expected type: Maybe (Map b elt)
+ Actual type: Maybe elt
+ In the return type of a call of `lookup'
+ In the expression: lookup a m :: Maybe (Map b elt)
diff --git a/testsuite/tests/gadt/T3651.stderr b/testsuite/tests/gadt/T3651.stderr index d15e27aefa..283e429737 100644 --- a/testsuite/tests/gadt/T3651.stderr +++ b/testsuite/tests/gadt/T3651.stderr @@ -1,21 +1,21 @@ - -T3651.hs:11:11: - Couldn't match type `()' with `Bool' - Inaccessible code in - a pattern with constructor U :: Z (), in an equation for `unsafe1' - In the pattern: U - In an equation for `unsafe1': unsafe1 B U = () - -T3651.hs:14:11: - Couldn't match type `()' with `Bool' - Inaccessible code in - a pattern with constructor U :: Z (), in an equation for `unsafe2' - In the pattern: U - In an equation for `unsafe2': unsafe2 B U = () - -T3651.hs:17:11: - Couldn't match type `()' with `Bool' - Inaccessible code in - a pattern with constructor U :: Z (), in an equation for `unsafe3' - In the pattern: U - In an equation for `unsafe3': unsafe3 B U = True +
+T3651.hs:11:11:
+ Couldn't match type `Bool' with `()'
+ Inaccessible code in
+ a pattern with constructor U :: Z (), in an equation for `unsafe1'
+ In the pattern: U
+ In an equation for `unsafe1': unsafe1 B U = ()
+
+T3651.hs:14:11:
+ Couldn't match type `Bool' with `()'
+ Inaccessible code in
+ a pattern with constructor U :: Z (), in an equation for `unsafe2'
+ In the pattern: U
+ In an equation for `unsafe2': unsafe2 B U = ()
+
+T3651.hs:17:11:
+ Couldn't match type `Bool' with `()'
+ Inaccessible code in
+ a pattern with constructor U :: Z (), in an equation for `unsafe3'
+ In the pattern: U
+ In an equation for `unsafe3': unsafe3 B U = True
diff --git a/testsuite/tests/ghci/scripts/ghci050.stderr b/testsuite/tests/ghci/scripts/ghci050.stderr index 7825133285..6f0e2c2ff2 100644 --- a/testsuite/tests/ghci/scripts/ghci050.stderr +++ b/testsuite/tests/ghci/scripts/ghci050.stderr @@ -1,8 +1,8 @@ - -<interactive>:6:51: - Couldn't match type `a' with `ListableElem (a, a)' - `a' is a rigid type variable bound by - the instance declaration at <interactive>:6:20 - In the expression: b - In the expression: [a, b] - In an equation for `asList': asList (a, b) = [a, b] +
+<interactive>:6:49:
+ Couldn't match type `a' with `ListableElem (a, a)'
+ `a' is a rigid type variable bound by
+ the instance declaration at <interactive>:6:20
+ In the expression: a
+ In the expression: [a, b]
+ In an equation for `asList': asList (a, b) = [a, b]
diff --git a/testsuite/tests/indexed-types/should_compile/T3017.stderr b/testsuite/tests/indexed-types/should_compile/T3017.stderr index 591b0bc800..61bc40bcea 100644 --- a/testsuite/tests/indexed-types/should_compile/T3017.stderr +++ b/testsuite/tests/indexed-types/should_compile/T3017.stderr @@ -1,23 +1,23 @@ -TYPE SIGNATURES - emptyL :: forall a. ListColl a - test2 :: forall c t t1. - (Num t1, Num t, Coll c, Elem c ~ (t, t1)) => - c -> c -TYPE CONSTRUCTORS - class Coll c - RecFlag NonRecursive - type family Elem c :: * - empty :: c insert :: Elem c -> c -> c - data ListColl a - RecFlag NonRecursive - = L :: forall a. [a] -> ListColl a Stricts: _ - FamilyInstance: none -COERCION AXIOMS - axiom Foo.TFCo:R:ElemListColl [a] - :: Elem (ListColl a) ~ Foo.R:ElemListColl a -INSTANCES - instance Coll (ListColl a) -- Defined at T3017.hs:12:11 -FAMILY INSTANCES - type Elem (ListColl a) -- Defined at T3017.hs:13:9 -Dependent modules: [] -Dependent packages: [base, ghc-prim, integer-gmp] +TYPE SIGNATURES
+ emptyL :: forall a. ListColl a
+ test2 :: forall c t t1.
+ (Num t1, Num t, Coll c, Elem c ~ (t, t1)) =>
+ c -> c
+TYPE CONSTRUCTORS
+ class Coll c
+ RecFlag NonRecursive
+ type family Elem c :: *
+ empty :: c insert :: Elem c -> c -> c
+ data ListColl a
+ RecFlag NonRecursive
+ = L :: forall a. [a] -> ListColl a Stricts: _
+ FamilyInstance: none
+COERCION AXIOMS
+ axiom Foo.TFCo:R:ElemListColl [a]
+ :: Elem (ListColl a) ~# Foo.R:ElemListColl a
+INSTANCES
+ instance Coll (ListColl a) -- Defined at T3017.hs:12:11
+FAMILY INSTANCES
+ type Elem (ListColl a) -- Defined at T3017.hs:13:9
+Dependent modules: []
+Dependent packages: [base, ghc-prim, integer-gmp]
diff --git a/testsuite/tests/indexed-types/should_fail/T1900.stderr b/testsuite/tests/indexed-types/should_fail/T1900.stderr index 4e3be835c4..8ea2bb97be 100644 --- a/testsuite/tests/indexed-types/should_fail/T1900.stderr +++ b/testsuite/tests/indexed-types/should_fail/T1900.stderr @@ -1,18 +1,18 @@ - -T1900.hs:11:13: - No instance for (Num ()) - arising from the literal `1' - Possible fix: add an instance declaration for (Num ()) - In the second argument of `(+)', namely `1' - In the expression: (+ 1) - In an equation for `trans': trans = (+ 1) - -T1900.hs:14:22: - 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:14:1-22 - NB: `Depend' is a type function, and may not be injective - In the first argument of `trans', namely `d' - In the second argument of `(==)', namely `trans d' - In the expression: d == trans d +
+T1900.hs:11:12:
+ No instance for (Num ())
+ arising from a use of `+'
+ Possible fix: add an instance declaration for (Num ())
+ In the expression: (+ 1)
+ In an equation for `trans': trans = (+ 1)
+ In the instance declaration for `Bug Int'
+
+T1900.hs:14:22:
+ 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:14:1-22
+ NB: `Depend' is a type function, and may not be injective
+ In the first argument of `trans', namely `d'
+ In the second argument of `(==)', namely `trans d'
+ In the expression: d == trans d
diff --git a/testsuite/tests/indexed-types/should_fail/T2544.stderr b/testsuite/tests/indexed-types/should_fail/T2544.stderr index d25e4b0ba0..cacd5a3610 100644 --- a/testsuite/tests/indexed-types/should_fail/T2544.stderr +++ b/testsuite/tests/indexed-types/should_fail/T2544.stderr @@ -1,22 +1,22 @@ - -T2544.hs:15:12: - Could not deduce (IxMap l ~ IxMap i0) - 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 - Expected type: IxMap (l :|: r) [Int] - Actual type: BiApp (IxMap i0) (IxMap r) [Int] - In the return type of a call of `BiApp' - 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 - Expected type: IxMap r [Int] - Actual type: IxMap i1 [Int] - 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:12:
+ Could not deduce (IxMap r ~ IxMap i1)
+ 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
+ Expected type: IxMap (l :|: r) [Int]
+ Actual type: BiApp (IxMap i0) (IxMap i1) [Int]
+ In the return type of a call of `BiApp'
+ In the expression: BiApp empty empty
+ In an equation for `empty': empty = BiApp empty empty
+
+T2544.hs:15:12:
+ Could not deduce (IxMap l ~ IxMap i0)
+ 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
+ Expected type: IxMap (l :|: r) [Int]
+ Actual type: BiApp (IxMap i0) (IxMap i1) [Int]
+ In the return type of a call of `BiApp'
+ In the expression: BiApp empty empty
+ In an equation for `empty': empty = BiApp empty empty
diff --git a/testsuite/tests/indexed-types/should_fail/T2664.stderr b/testsuite/tests/indexed-types/should_fail/T2664.stderr index bba0274108..2ed47d9e1a 100644 --- a/testsuite/tests/indexed-types/should_fail/T2664.stderr +++ b/testsuite/tests/indexed-types/should_fail/T2664.stderr @@ -1,20 +1,20 @@ - -T2664.hs:31:17: - Could not deduce (b ~ a) - from the context (Connect a, Connect b) - bound by the instance declaration at T2664.hs:22:10-52 - or from ((a :*: b) ~ Dual c, c ~ Dual (a :*: b)) - bound by the type signature for - newPChan :: ((a :*: b) ~ Dual c, c ~ Dual (a :*: b)) => - IO (PChan (a :*: b), PChan c) - at T2664.hs:(23,5)-(31,87) - `b' is a rigid type variable bound by - the instance declaration at T2664.hs:22:30 - `a' is a rigid type variable bound by - the instance declaration at T2664.hs:22:19 - Expected type: PChan (a :*: b) - Actual type: PChan (b :*: a) - In the expression: O $ takeMVar v - In the first argument of `return', namely - `(O $ takeMVar v, - E (pchoose Right v newPChan) (pchoose Left v newPChan))' +
+T2664.hs:31:17:
+ Could not deduce (a ~ b)
+ from the context (Connect a, Connect b)
+ bound by the instance declaration at T2664.hs:22:10-52
+ or from ((a :*: b) ~ Dual c, c ~ Dual (a :*: b))
+ bound by the type signature for
+ newPChan :: ((a :*: b) ~ Dual c, c ~ Dual (a :*: b)) =>
+ IO (PChan (a :*: b), PChan c)
+ at T2664.hs:(23,5)-(31,87)
+ `a' is a rigid type variable bound by
+ the instance declaration at T2664.hs:22:19
+ `b' is a rigid type variable bound by
+ the instance declaration at T2664.hs:22:30
+ Expected type: PChan (a :*: b)
+ Actual type: PChan (b :*: a)
+ In the expression: O $ takeMVar v
+ In the first argument of `return', namely
+ `(O $ takeMVar v,
+ E (pchoose Right v newPChan) (pchoose Left v newPChan))'
diff --git a/testsuite/tests/indexed-types/should_fail/T3330a.stderr b/testsuite/tests/indexed-types/should_fail/T3330a.stderr index cfe7f67270..cafc6bcfac 100644 --- a/testsuite/tests/indexed-types/should_fail/T3330a.stderr +++ b/testsuite/tests/indexed-types/should_fail/T3330a.stderr @@ -1,9 +1,9 @@ - -T3330a.hs:17:34: - Couldn't match type `s' with `(->) (s ix1 -> ix1)' - `s' is a rigid type variable bound by - the type signature for children :: s ix -> PF s r ix -> [AnyF s] - at T3330a.hs:17:1 - In the first argument of `hmapM', namely `p' - In the first argument of `execWriter', namely `(hmapM p collect x)' - In the expression: execWriter (hmapM p collect x) +
+T3330a.hs:17:34:
+ Couldn't match type `s' with `(->) (s ix1 -> ix1)'
+ `s' is a rigid type variable bound by
+ the type signature for children :: s ix -> PF s r ix -> [AnyF s]
+ at T3330a.hs:17:1
+ In the first argument of `hmapM', namely `p'
+ In the first argument of `execWriter', namely `(hmapM p collect x)'
+ In the expression: execWriter (hmapM p collect x)
diff --git a/testsuite/tests/indexed-types/should_fail/T3330c.stderr b/testsuite/tests/indexed-types/should_fail/T3330c.stderr index e43c4652d8..506f91e47e 100644 --- a/testsuite/tests/indexed-types/should_fail/T3330c.stderr +++ b/testsuite/tests/indexed-types/should_fail/T3330c.stderr @@ -1,18 +1,18 @@ - -T3330c.hs:23:43: - Couldn't match type `f1' with `f1 x' - `f1' is a rigid type variable bound by - a pattern with constructor - RSum :: forall (f :: * -> *) (g :: * -> *). - R f -> R g -> R (f :+: g), - in an equation for plug' - at T3330c.hs:23:8 - In the first argument of `plug', namely `rf' - In the first argument of `Inl', namely `(plug rf df x)' - In the expression: Inl (plug rf df x) - -T3330c.hs:23:43: - Couldn't match type `Der ((->) x)' with `R' - In the first argument of `plug', namely `rf' - In the first argument of `Inl', namely `(plug rf df x)' - In the expression: Inl (plug rf df x) +
+T3330c.hs:23:43:
+ Couldn't match type `Der ((->) x)' with `R'
+ In the first argument of `plug', namely `rf'
+ In the first argument of `Inl', namely `(plug rf df x)'
+ In the expression: Inl (plug rf df x)
+
+T3330c.hs:23:43:
+ Couldn't match type `f1' with `f1 x'
+ `f1' is a rigid type variable bound by
+ a pattern with constructor
+ RSum :: forall (f :: * -> *) (g :: * -> *).
+ R f -> R g -> R (f :+: g),
+ in an equation for plug'
+ at T3330c.hs:23:8
+ In the first argument of `plug', namely `rf'
+ In the first argument of `Inl', namely `(plug rf df x)'
+ In the expression: Inl (plug rf df x)
diff --git a/testsuite/tests/indexed-types/should_fail/T4099.stderr b/testsuite/tests/indexed-types/should_fail/T4099.stderr index 4d1935678b..926579de74 100644 --- a/testsuite/tests/indexed-types/should_fail/T4099.stderr +++ b/testsuite/tests/indexed-types/should_fail/T4099.stderr @@ -1,13 +1,13 @@ - -T4099.hs:11:14: - Couldn't match type `T a0' with `T b' - NB: `T' is a type function, and may not be injective - 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 type `T a1' with `Maybe b' - 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:14:
+ Couldn't match type `T b' with `T a0'
+ NB: `T' is a type function, and may not be injective
+ 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 type `T a1' with `Maybe b'
+ In the first argument of `foo', namely `x'
+ In the expression: foo x
+ In an equation for `bar2': bar2 x = foo x
diff --git a/testsuite/tests/indexed-types/should_fail/T4179.stderr b/testsuite/tests/indexed-types/should_fail/T4179.stderr index 50c1ad5365..11bd7d62ad 100644 --- a/testsuite/tests/indexed-types/should_fail/T4179.stderr +++ b/testsuite/tests/indexed-types/should_fail/T4179.stderr @@ -1,63 +1,59 @@ - -T4179.hs:26:16: - Could not deduce (DoC (x (A2 (FCon x) -> A3 (FCon x)))) - arising from a use of `op' - from the context (Functor x, DoC (FCon x)) - bound by the type signature for - fCon :: (Functor x, DoC (FCon x)) => - Con x -> A2 (FCon x) -> A3 (FCon x) - at T4179.hs:26:1-17 - Possible fix: - add (DoC (x (A2 (FCon x) -> A3 (FCon x)))) to the context of - the type signature for - fCon :: (Functor x, DoC (FCon x)) => - Con x -> A2 (FCon x) -> A3 (FCon x) - or add an instance declaration for - (DoC (x (A2 (FCon x) -> A3 (FCon x)))) - In the first argument of `foldDoC', namely `op' - In the expression: foldDoC op - In an equation for `fCon': fCon = foldDoC op - -T4179.hs:26:16: - Could not deduce (A2 (x (A2 (FCon x) -> A3 (FCon x))) - ~ - A2 (FCon x)) - from the context (Functor x, DoC (FCon x)) - bound by the type signature for - fCon :: (Functor x, DoC (FCon x)) => - Con x -> A2 (FCon x) -> A3 (FCon x) - at T4179.hs:26:1-17 - NB: `A2' is a type function, and may not be injective - Expected type: A2 (FCon x) -> A3 (FCon x) - Actual type: A2 (x (A2 (FCon x) -> A3 (FCon x))) - -> A3 (x (A2 (FCon x) -> A3 (FCon x))) - Expected type: x (A2 (FCon x) -> A3 (FCon x)) - -> A2 (FCon x) - -> A3 (FCon x) - Actual type: x (A2 (FCon x) -> A3 (FCon x)) - -> A2 (x (A2 (FCon x) -> A3 (FCon x))) - -> A3 (x (A2 (FCon x) -> A3 (FCon x))) - In the first argument of `foldDoC', namely `op' - In the expression: foldDoC op - -T4179.hs:26:16: - Could not deduce (A3 (x (A2 (FCon x) -> A3 (FCon x))) - ~ - A3 (FCon x)) - from the context (Functor x, DoC (FCon x)) - bound by the type signature for - fCon :: (Functor x, DoC (FCon x)) => - Con x -> A2 (FCon x) -> A3 (FCon x) - at T4179.hs:26:1-17 - NB: `A3' is a type function, and may not be injective - Expected type: A2 (FCon x) -> A3 (FCon x) - Actual type: A2 (x (A2 (FCon x) -> A3 (FCon x))) - -> A3 (x (A2 (FCon x) -> A3 (FCon x))) - Expected type: x (A2 (FCon x) -> A3 (FCon x)) - -> A2 (FCon x) - -> A3 (FCon x) - Actual type: x (A2 (FCon x) -> A3 (FCon x)) - -> A2 (x (A2 (FCon x) -> A3 (FCon x))) - -> A3 (x (A2 (FCon x) -> A3 (FCon x))) - In the first argument of `foldDoC', namely `op' - In the expression: foldDoC op +
+T4179.hs:26:16:
+ Could not deduce (DoC (x (A2 (FCon x) -> A3 (FCon x))))
+ arising from a use of `op'
+ from the context (Functor x, DoC (FCon x))
+ bound by the type signature for
+ fCon :: (Functor x, DoC (FCon x)) =>
+ Con x -> A2 (FCon x) -> A3 (FCon x)
+ at T4179.hs:26:1-17
+ Possible fix:
+ add (DoC (x (A2 (FCon x) -> A3 (FCon x)))) to the context of
+ the type signature for
+ fCon :: (Functor x, DoC (FCon x)) =>
+ Con x -> A2 (FCon x) -> A3 (FCon x)
+ or add an instance declaration for
+ (DoC (x (A2 (FCon x) -> A3 (FCon x))))
+ In the first argument of `foldDoC', namely `op'
+ In the expression: foldDoC op
+ In an equation for `fCon': fCon = foldDoC op
+
+T4179.hs:26:16:
+ Could not deduce (A3 (x (A2 (FCon x) -> A3 (FCon x)))
+ ~ A3 (FCon x))
+ from the context (Functor x, DoC (FCon x))
+ bound by the type signature for
+ fCon :: (Functor x, DoC (FCon x)) =>
+ Con x -> A2 (FCon x) -> A3 (FCon x)
+ at T4179.hs:26:1-17
+ NB: `A3' is a type function, and may not be injective
+ Expected type: A2 (FCon x) -> A3 (FCon x)
+ Actual type: A2 (x (A2 (FCon x) -> A3 (FCon x)))
+ -> A3 (x (A2 (FCon x) -> A3 (FCon x)))
+ Expected type: x (A2 (FCon x) -> A3 (FCon x))
+ -> A2 (FCon x) -> A3 (FCon x)
+ Actual type: x (A2 (FCon x) -> A3 (FCon x))
+ -> A2 (x (A2 (FCon x) -> A3 (FCon x)))
+ -> A3 (x (A2 (FCon x) -> A3 (FCon x)))
+ In the first argument of `foldDoC', namely `op'
+ In the expression: foldDoC op
+
+T4179.hs:26:16:
+ Could not deduce (A2 (x (A2 (FCon x) -> A3 (FCon x)))
+ ~ A2 (FCon x))
+ from the context (Functor x, DoC (FCon x))
+ bound by the type signature for
+ fCon :: (Functor x, DoC (FCon x)) =>
+ Con x -> A2 (FCon x) -> A3 (FCon x)
+ at T4179.hs:26:1-17
+ NB: `A2' is a type function, and may not be injective
+ Expected type: A2 (FCon x) -> A3 (FCon x)
+ Actual type: A2 (x (A2 (FCon x) -> A3 (FCon x)))
+ -> A3 (x (A2 (FCon x) -> A3 (FCon x)))
+ Expected type: x (A2 (FCon x) -> A3 (FCon x))
+ -> A2 (FCon x) -> A3 (FCon x)
+ Actual type: x (A2 (FCon x) -> A3 (FCon x))
+ -> A2 (x (A2 (FCon x) -> A3 (FCon x)))
+ -> A3 (x (A2 (FCon x) -> A3 (FCon x)))
+ In the first argument of `foldDoC', namely `op'
+ In the expression: foldDoC op
diff --git a/testsuite/tests/indexed-types/should_fail/T4254.stderr b/testsuite/tests/indexed-types/should_fail/T4254.stderr index 03aa80bdac..e69de29bb2 100644 --- a/testsuite/tests/indexed-types/should_fail/T4254.stderr +++ b/testsuite/tests/indexed-types/should_fail/T4254.stderr @@ -1,18 +0,0 @@ - -T4254.hs:19:10: - Could not deduce (b ~ Bool) - from the context (a ~ Int, FD a b) - bound by the type signature for - fails :: (a ~ Int, FD a b) => a -> Bool - at T4254.hs:19:1-11 - `b' is a rigid type variable bound by - the type signature for fails :: (a ~ Int, FD a b) => a -> Bool - at T4254.hs:19:1 - When using functional dependencies to combine - FD Int b, - arising from the type signature for - fails :: (a ~ Int, FD a b) => a -> Bool - at T4254.hs:19:1-11 - FD Int Bool, arising from a use of `op' at T4254.hs:19:10-11 - In the expression: op - In an equation for `fails': fails = op diff --git a/testsuite/tests/indexed-types/should_fail/T4272.stderr b/testsuite/tests/indexed-types/should_fail/T4272.stderr index 792cde92b8..5c6e38f0ae 100644 --- a/testsuite/tests/indexed-types/should_fail/T4272.stderr +++ b/testsuite/tests/indexed-types/should_fail/T4272.stderr @@ -1,8 +1,8 @@ - -T4272.hs:11:16: - Occurs check: cannot construct the infinite type: - a0 = TermFamily a0 a0 - In the first argument of `prune', namely `t' - In the expression: prune t (terms (undefined :: TermFamily a a)) - In an equation for `laws': - laws t = prune t (terms (undefined :: TermFamily a a)) +
+T4272.hs:11:16:
+ Occurs check: cannot construct the infinite type:
+ a0 = TermFamily a0 a0
+ In the first argument of `prune', namely `t'
+ In the expression: prune t (terms (undefined :: TermFamily a a))
+ In an equation for `laws':
+ laws t = prune t (terms (undefined :: TermFamily a a))
diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index 15eefb6c09..4f0b077bdf 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -60,7 +60,7 @@ test('T3330a', reqlib('mtl'), compile_fail, ['']) test('T3330b', normal, compile_fail, ['']) test('T3330c', normal, compile_fail, ['']) test('T4179', normal, compile_fail, ['']) -test('T4254', normal, compile_fail, ['']) +test('T4254', normal, compile, ['']) test('T2239', normal, compile_fail, ['']) test('T3440', normal, compile_fail, ['']) test('T4485', normal, compile_fail, ['']) diff --git a/testsuite/tests/mdo/should_fail/mdofail001.stderr b/testsuite/tests/mdo/should_fail/mdofail001.stderr index 8660e167fe..f9516ad2b0 100644 --- a/testsuite/tests/mdo/should_fail/mdofail001.stderr +++ b/testsuite/tests/mdo/should_fail/mdofail001.stderr @@ -1,11 +1,11 @@ - -mdofail001.hs:1:12: - Warning: -XRecursiveDo is deprecated: use -XDoRec or pragma {-# LANGUAGE DoRec #-} instead - -mdofail001.hs:10:36: - No instance for (Num Char) - arising from the literal `3' - Possible fix: add an instance declaration for (Num Char) - In the expression: 3 - In the first argument of `l', namely `[1, 2, 3]' - In the expression: l [1, 2, 3] +
+mdofail001.hs:1:12:
+ Warning: -XRecursiveDo is deprecated: use -XDoRec or pragma {-# LANGUAGE DoRec #-} instead
+
+mdofail001.hs:10:32:
+ No instance for (Num Char)
+ arising from the literal `1'
+ Possible fix: add an instance declaration for (Num Char)
+ In the expression: 1
+ In the first argument of `l', namely `[1, 2, 3]'
+ In the expression: l [1, 2, 3]
diff --git a/testsuite/tests/parser/should_fail/readFail003.stderr b/testsuite/tests/parser/should_fail/readFail003.stderr index fe8ce00577..7ef9ce150e 100644 --- a/testsuite/tests/parser/should_fail/readFail003.stderr +++ b/testsuite/tests/parser/should_fail/readFail003.stderr @@ -1,36 +1,12 @@ - -readFail003.hs:4:27: - Occurs check: cannot construct the infinite type: - t0 = (t0, [a0], [a1]) - In the expression: a - In a pattern binding: - ~(a, b, c) - | nullity b = a - | nullity c = a - | otherwise = a - where - nullity = null - -readFail003.hs:5:27: - Occurs check: cannot construct the infinite type: - t0 = (t0, [a0], [a1]) - In the expression: a - In a pattern binding: - ~(a, b, c) - | nullity b = a - | nullity c = a - | otherwise = a - where - nullity = null - -readFail003.hs:6:27: - Occurs check: cannot construct the infinite type: - t0 = (t0, [a0], [a1]) - In the expression: a - In a pattern binding: - ~(a, b, c) - | nullity b = a - | nullity c = a - | otherwise = a - where - nullity = null +
+readFail003.hs:4:27:
+ Occurs check: cannot construct the infinite type:
+ t0 = (t0, [a0], [a1])
+ In the expression: a
+ In a pattern binding:
+ ~(a, b, c)
+ | nullity b = a
+ | nullity c = a
+ | otherwise = a
+ where
+ nullity = null
diff --git a/testsuite/tests/simplCore/should_compile/spec-inline.stderr b/testsuite/tests/simplCore/should_compile/spec-inline.stderr index eba8a4d696..94e5ca11f2 100644 --- a/testsuite/tests/simplCore/should_compile/spec-inline.stderr +++ b/testsuite/tests/simplCore/should_compile/spec-inline.stderr @@ -1,154 +1,154 @@ - -==================== Tidy Core ==================== -Result size = 155 - -Roman.foo3 :: GHC.Types.Int -[GblId, Str=DmdType b] -Roman.foo3 = - Control.Exception.Base.patError - @ GHC.Types.Int "spec-inline.hs:(19,5)-(29,25)|function go" - -Rec { -Roman.foo_$s$wgo [Occ=LoopBreaker] - :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# -[GblId, Arity=2, Caf=NoCafRefs, Str=DmdType LL] -Roman.foo_$s$wgo = - \ (sc :: GHC.Prim.Int#) (sc1 :: GHC.Prim.Int#) -> - let { - a [Dmd=Just L] :: GHC.Prim.Int# - [LclId, Str=DmdType] - a = - GHC.Prim.+# - (GHC.Prim.+# - (GHC.Prim.+# - (GHC.Prim.+# (GHC.Prim.+# (GHC.Prim.+# sc1 sc1) sc1) sc1) sc1) - sc1) - sc1 } in - case GHC.Prim.<=# sc 0 of _ { - GHC.Types.False -> - case GHC.Prim.<# sc 100 of _ { - GHC.Types.False -> - case GHC.Prim.<# sc 500 of _ { - GHC.Types.False -> - Roman.foo_$s$wgo (GHC.Prim.-# sc 1) (GHC.Prim.+# a a); - GHC.Types.True -> Roman.foo_$s$wgo (GHC.Prim.-# sc 3) a - }; - GHC.Types.True -> Roman.foo_$s$wgo (GHC.Prim.-# sc 2) sc1 - }; - GHC.Types.True -> 0 - } -end Rec } - -Roman.$wgo - :: Data.Maybe.Maybe GHC.Types.Int - -> Data.Maybe.Maybe GHC.Types.Int -> GHC.Prim.Int# -[GblId, - Arity=2, - Str=DmdType SS, - Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=2, Value=True, - ConLike=True, Cheap=True, Expandable=True, - Guidance=IF_ARGS [60 30] 253 0}] -Roman.$wgo = - \ (w :: Data.Maybe.Maybe GHC.Types.Int) - (w1 :: Data.Maybe.Maybe GHC.Types.Int) -> - case w1 of _ { - Data.Maybe.Nothing -> - Roman.foo3 - `cast` (UnsafeCo GHC.Types.Int GHC.Prim.Int# - :: GHC.Types.Int ~ GHC.Prim.Int#); - Data.Maybe.Just x -> - case x of _ { GHC.Types.I# ipv -> - let { - a [Dmd=Just L] :: GHC.Prim.Int# - [LclId, Str=DmdType] - a = - GHC.Prim.+# - (GHC.Prim.+# - (GHC.Prim.+# - (GHC.Prim.+# (GHC.Prim.+# (GHC.Prim.+# ipv ipv) ipv) ipv) ipv) - ipv) - ipv } in - case w of _ { - Data.Maybe.Nothing -> Roman.foo_$s$wgo 10 a; - Data.Maybe.Just n -> - case n of _ { GHC.Types.I# x2 -> - case GHC.Prim.<=# x2 0 of _ { - GHC.Types.False -> - case GHC.Prim.<# x2 100 of _ { - GHC.Types.False -> - case GHC.Prim.<# x2 500 of _ { - GHC.Types.False -> - Roman.foo_$s$wgo (GHC.Prim.-# x2 1) (GHC.Prim.+# a a); - GHC.Types.True -> Roman.foo_$s$wgo (GHC.Prim.-# x2 3) a - }; - GHC.Types.True -> Roman.foo_$s$wgo (GHC.Prim.-# x2 2) ipv - }; - GHC.Types.True -> 0 - } - } - } - } - } - -Roman.foo_go [InlPrag=INLINE[0]] - :: Data.Maybe.Maybe GHC.Types.Int - -> Data.Maybe.Maybe GHC.Types.Int -> GHC.Types.Int -[GblId, - Arity=2, - Str=DmdType SSm, - Unf=Unf{Src=Worker=Roman.$wgo, TopLvl=True, Arity=2, Value=True, - ConLike=True, Cheap=True, Expandable=True, - Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) - Tmpl= \ (w [Occ=Once] :: Data.Maybe.Maybe GHC.Types.Int) - (w1 [Occ=Once] :: Data.Maybe.Maybe GHC.Types.Int) -> - case Roman.$wgo w w1 of ww { __DEFAULT -> GHC.Types.I# ww }}] -Roman.foo_go = - \ (w :: Data.Maybe.Maybe GHC.Types.Int) - (w1 :: Data.Maybe.Maybe GHC.Types.Int) -> - case Roman.$wgo w w1 of ww { __DEFAULT -> GHC.Types.I# ww } - -Roman.foo2 :: GHC.Types.Int -[GblId, - Caf=NoCafRefs, - Str=DmdType m, - Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=True, - ConLike=True, Cheap=True, Expandable=True, - Guidance=IF_ARGS [] 10 110}] -Roman.foo2 = GHC.Types.I# 6 - -Roman.foo1 :: Data.Maybe.Maybe GHC.Types.Int -[GblId, - Caf=NoCafRefs, - Str=DmdType, - Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=True, - ConLike=True, Cheap=True, Expandable=True, - Guidance=IF_ARGS [] 10 110}] -Roman.foo1 = Data.Maybe.Just @ GHC.Types.Int Roman.foo2 - -Roman.foo :: GHC.Types.Int -> GHC.Types.Int -[GblId, - Arity=1, - Caf=NoCafRefs, - Str=DmdType S(A)m, - Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, - ConLike=True, Cheap=True, Expandable=True, - Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) - Tmpl= \ (n [Occ=Once!] :: GHC.Types.Int) -> - case n of n1 { GHC.Types.I# _ -> - Roman.foo_go (Data.Maybe.Just @ GHC.Types.Int n1) Roman.foo1 - }}] -Roman.foo = - \ (n :: GHC.Types.Int) -> - case n of _ { GHC.Types.I# ipv -> - case Roman.foo_$s$wgo ipv 6 of ww { __DEFAULT -> GHC.Types.I# ww } - } - - ------- Local rules for imported ids -------- -"SC:$wgo0" [ALWAYS] - forall (sc :: GHC.Prim.Int#) (sc1 :: GHC.Prim.Int#). - Roman.$wgo (Data.Maybe.Just @ GHC.Types.Int (GHC.Types.I# sc)) - (Data.Maybe.Just @ GHC.Types.Int (GHC.Types.I# sc1)) - = Roman.foo_$s$wgo sc sc1 - - +
+==================== Tidy Core ====================
+Result size = 155
+
+Roman.foo3 :: GHC.Types.Int
+[GblId, Str=DmdType b]
+Roman.foo3 =
+ Control.Exception.Base.patError
+ @ GHC.Types.Int "spec-inline.hs:(19,5)-(29,25)|function go"
+
+Rec {
+Roman.foo_$s$wgo [Occ=LoopBreaker]
+ :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int#
+[GblId, Arity=2, Caf=NoCafRefs, Str=DmdType LL]
+Roman.foo_$s$wgo =
+ \ (sc :: GHC.Prim.Int#) (sc1 :: GHC.Prim.Int#) ->
+ let {
+ a [Dmd=Just L] :: GHC.Prim.Int#
+ [LclId, Str=DmdType]
+ a =
+ GHC.Prim.+#
+ (GHC.Prim.+#
+ (GHC.Prim.+#
+ (GHC.Prim.+# (GHC.Prim.+# (GHC.Prim.+# sc1 sc1) sc1) sc1) sc1)
+ sc1)
+ sc1 } in
+ case GHC.Prim.<=# sc 0 of _ {
+ GHC.Types.False ->
+ case GHC.Prim.<# sc 100 of _ {
+ GHC.Types.False ->
+ case GHC.Prim.<# sc 500 of _ {
+ GHC.Types.False ->
+ Roman.foo_$s$wgo (GHC.Prim.-# sc 1) (GHC.Prim.+# a a);
+ GHC.Types.True -> Roman.foo_$s$wgo (GHC.Prim.-# sc 3) a
+ };
+ GHC.Types.True -> Roman.foo_$s$wgo (GHC.Prim.-# sc 2) sc1
+ };
+ GHC.Types.True -> 0
+ }
+end Rec }
+
+Roman.$wgo
+ :: Data.Maybe.Maybe GHC.Types.Int
+ -> Data.Maybe.Maybe GHC.Types.Int -> GHC.Prim.Int#
+[GblId,
+ Arity=2,
+ Str=DmdType SS,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=2, Value=True,
+ ConLike=True, Cheap=True, Expandable=True,
+ Guidance=IF_ARGS [60 30] 253 0}]
+Roman.$wgo =
+ \ (w :: Data.Maybe.Maybe GHC.Types.Int)
+ (w1 :: Data.Maybe.Maybe GHC.Types.Int) ->
+ case w1 of _ {
+ Data.Maybe.Nothing ->
+ Roman.foo3
+ `cast` (UnsafeCo GHC.Types.Int GHC.Prim.Int#
+ :: GHC.Types.Int ~# GHC.Prim.Int#);
+ Data.Maybe.Just x ->
+ case x of _ { GHC.Types.I# ipv ->
+ let {
+ a [Dmd=Just L] :: GHC.Prim.Int#
+ [LclId, Str=DmdType]
+ a =
+ GHC.Prim.+#
+ (GHC.Prim.+#
+ (GHC.Prim.+#
+ (GHC.Prim.+# (GHC.Prim.+# (GHC.Prim.+# ipv ipv) ipv) ipv) ipv)
+ ipv)
+ ipv } in
+ case w of _ {
+ Data.Maybe.Nothing -> Roman.foo_$s$wgo 10 a;
+ Data.Maybe.Just n ->
+ case n of _ { GHC.Types.I# x2 ->
+ case GHC.Prim.<=# x2 0 of _ {
+ GHC.Types.False ->
+ case GHC.Prim.<# x2 100 of _ {
+ GHC.Types.False ->
+ case GHC.Prim.<# x2 500 of _ {
+ GHC.Types.False ->
+ Roman.foo_$s$wgo (GHC.Prim.-# x2 1) (GHC.Prim.+# a a);
+ GHC.Types.True -> Roman.foo_$s$wgo (GHC.Prim.-# x2 3) a
+ };
+ GHC.Types.True -> Roman.foo_$s$wgo (GHC.Prim.-# x2 2) ipv
+ };
+ GHC.Types.True -> 0
+ }
+ }
+ }
+ }
+ }
+
+Roman.foo_go [InlPrag=INLINE[0]]
+ :: Data.Maybe.Maybe GHC.Types.Int
+ -> Data.Maybe.Maybe GHC.Types.Int -> GHC.Types.Int
+[GblId,
+ Arity=2,
+ Str=DmdType SSm,
+ Unf=Unf{Src=Worker=Roman.$wgo, TopLvl=True, Arity=2, Value=True,
+ ConLike=True, Cheap=True, Expandable=True,
+ Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
+ Tmpl= \ (w [Occ=Once] :: Data.Maybe.Maybe GHC.Types.Int)
+ (w1 [Occ=Once] :: Data.Maybe.Maybe GHC.Types.Int) ->
+ case Roman.$wgo w w1 of ww { __DEFAULT -> GHC.Types.I# ww }}]
+Roman.foo_go =
+ \ (w :: Data.Maybe.Maybe GHC.Types.Int)
+ (w1 :: Data.Maybe.Maybe GHC.Types.Int) ->
+ case Roman.$wgo w w1 of ww { __DEFAULT -> GHC.Types.I# ww }
+
+Roman.foo2 :: GHC.Types.Int
+[GblId,
+ Caf=NoCafRefs,
+ Str=DmdType m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=True,
+ ConLike=True, Cheap=True, Expandable=True,
+ Guidance=IF_ARGS [] 10 110}]
+Roman.foo2 = GHC.Types.I# 6
+
+Roman.foo1 :: Data.Maybe.Maybe GHC.Types.Int
+[GblId,
+ Caf=NoCafRefs,
+ Str=DmdType,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=True,
+ ConLike=True, Cheap=True, Expandable=True,
+ Guidance=IF_ARGS [] 10 110}]
+Roman.foo1 = Data.Maybe.Just @ GHC.Types.Int Roman.foo2
+
+Roman.foo :: GHC.Types.Int -> GHC.Types.Int
+[GblId,
+ Arity=1,
+ Caf=NoCafRefs,
+ Str=DmdType S(A)m,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
+ ConLike=True, Cheap=True, Expandable=True,
+ Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
+ Tmpl= \ (n [Occ=Once!] :: GHC.Types.Int) ->
+ case n of n1 { GHC.Types.I# _ ->
+ Roman.foo_go (Data.Maybe.Just @ GHC.Types.Int n1) Roman.foo1
+ }}]
+Roman.foo =
+ \ (n :: GHC.Types.Int) ->
+ case n of _ { GHC.Types.I# ipv ->
+ case Roman.foo_$s$wgo ipv 6 of ww { __DEFAULT -> GHC.Types.I# ww }
+ }
+
+
+------ Local rules for imported ids --------
+"SC:$wgo0" [ALWAYS]
+ forall (sc :: GHC.Prim.Int#) (sc1 :: GHC.Prim.Int#).
+ Roman.$wgo (Data.Maybe.Just @ GHC.Types.Int (GHC.Types.I# sc))
+ (Data.Maybe.Just @ GHC.Types.Int (GHC.Types.I# sc1))
+ = Roman.foo_$s$wgo sc sc1
+
+
diff --git a/testsuite/tests/typecheck/should_compile/FD2.stderr b/testsuite/tests/typecheck/should_compile/FD2.stderr index 618c361f49..4dd98e2c77 100644 --- a/testsuite/tests/typecheck/should_compile/FD2.stderr +++ b/testsuite/tests/typecheck/should_compile/FD2.stderr @@ -1,25 +1,25 @@ - -FD2.hs:26:38: - Could not deduce (e1 ~ e) - from the context (Foldable a) - bound by the class declaration for `Foldable' - at FD2.hs:(17,1)-(26,39) - or from (Elem a e) - bound by the type signature for - foldr1 :: Elem a e => (e -> e -> e) -> a -> e - at FD2.hs:(22,3)-(26,39) - or from (Elem a e1) - bound by the type signature for - mf :: Elem a e1 => e1 -> Maybe e1 -> Maybe e1 - at FD2.hs:(25,12)-(26,39) - `e1' is a rigid type variable bound by - the type signature for - mf :: Elem a e1 => e1 -> Maybe e1 -> Maybe e1 - at FD2.hs:25:12 - `e' is a rigid type variable bound by - the type signature for - foldr1 :: Elem a e => (e -> e -> e) -> a -> e - at FD2.hs:22:3 - In the second argument of `f', namely `y' - In the first argument of `Just', namely `(f x y)' - In the expression: Just (f x y) +
+FD2.hs:26:36:
+ Could not deduce (e1 ~ e)
+ from the context (Foldable a)
+ bound by the class declaration for `Foldable'
+ at FD2.hs:(17,1)-(26,39)
+ or from (Elem a e)
+ bound by the type signature for
+ foldr1 :: Elem a e => (e -> e -> e) -> a -> e
+ at FD2.hs:(22,3)-(26,39)
+ or from (Elem a e1)
+ bound by the type signature for
+ mf :: Elem a e1 => e1 -> Maybe e1 -> Maybe e1
+ at FD2.hs:(25,12)-(26,39)
+ `e1' is a rigid type variable bound by
+ the type signature for
+ mf :: Elem a e1 => e1 -> Maybe e1 -> Maybe e1
+ at FD2.hs:25:12
+ `e' is a rigid type variable bound by
+ the type signature for
+ foldr1 :: Elem a e => (e -> e -> e) -> a -> e
+ at FD2.hs:22:3
+ In the first argument of `f', namely `x'
+ In the first argument of `Just', namely `(f x y)'
+ In the expression: Just (f x y)
diff --git a/testsuite/tests/typecheck/should_compile/T2494.stderr b/testsuite/tests/typecheck/should_compile/T2494.stderr index b522833af2..5e5661e74a 100644 --- a/testsuite/tests/typecheck/should_compile/T2494.stderr +++ b/testsuite/tests/typecheck/should_compile/T2494.stderr @@ -1,22 +1,22 @@ - -T2494.hs:15:7: - Couldn't match type `a' with `b' - `a' is a rigid type variable bound by - the RULE "foo/foo" at T2494.hs:13:46 - `b' is a rigid type variable bound by - the RULE "foo/foo" at T2494.hs:14:46 - Expected type: Maybe (m b) -> Maybe (m b) - Actual type: Maybe (m a) -> Maybe (m a) - In the first argument of `foo', namely `f' - In the expression: foo f (foo g x) - -T2494.hs:15:30: - Couldn't match type `b' with `a' - `b' is a rigid type variable bound by - the RULE "foo/foo" at T2494.hs:14:46 - `a' is a rigid type variable bound by - the RULE "foo/foo" at T2494.hs:13:46 - Expected type: Maybe (m b) -> Maybe (m a) - Actual type: Maybe (m b) -> Maybe (m b) - In the second argument of `(.)', namely `g' - In the first argument of `foo', namely `(f . g)' +
+T2494.hs:15:7:
+ Couldn't match type `b' with `a'
+ `b' is a rigid type variable bound by
+ the RULE "foo/foo" at T2494.hs:14:46
+ `a' is a rigid type variable bound by
+ the RULE "foo/foo" at T2494.hs:13:46
+ Expected type: Maybe (m b) -> Maybe (m b)
+ Actual type: Maybe (m a) -> Maybe (m a)
+ In the first argument of `foo', namely `f'
+ In the expression: foo f (foo g x)
+
+T2494.hs:15:30:
+ Couldn't match type `b' with `a'
+ `b' is a rigid type variable bound by
+ the RULE "foo/foo" at T2494.hs:14:46
+ `a' is a rigid type variable bound by
+ the RULE "foo/foo" at T2494.hs:13:46
+ Expected type: Maybe (m b) -> Maybe (m a)
+ Actual type: Maybe (m b) -> Maybe (m b)
+ In the second argument of `(.)', namely `g'
+ In the first argument of `foo', namely `(f . g)'
diff --git a/testsuite/tests/typecheck/should_compile/tc231.stderr b/testsuite/tests/typecheck/should_compile/tc231.stderr index bf92dac850..9647f34fef 100644 --- a/testsuite/tests/typecheck/should_compile/tc231.stderr +++ b/testsuite/tests/typecheck/should_compile/tc231.stderr @@ -1,23 +1,23 @@ -TYPE SIGNATURES - foo :: forall s b chain. - Zork s (Z [Char]) b => - Q s (Z [Char]) chain -> ST s () - s :: forall t t1. Q t (Z [Char]) t1 -> Q t (Z [Char]) t1 -TYPE CONSTRUCTORS - data Q s a chain - RecFlag NonRecursive - = Node :: forall s a chain. s -> a -> chain -> Q s a chain - Stricts: _ _ _ - FamilyInstance: none - data Z a - RecFlag NonRecursive - = Z :: forall a. a -> Z a Stricts: _ - FamilyInstance: none - class Zork s a b | a -> b - RecFlag NonRecursive - huh :: forall chain. Q s a chain -> ST s () -COERCION AXIOMS - axiom ShouldCompile.NTCo:Zork [s, a, b] - :: Zork s a b ~ (forall chain. Q s a chain -> ST s ()) -Dependent modules: [] -Dependent packages: [base, ghc-prim, integer-gmp] +TYPE SIGNATURES
+ foo :: forall s b chain.
+ Zork s (Z [Char]) b =>
+ Q s (Z [Char]) chain -> ST s ()
+ s :: forall t t1. Q t (Z [Char]) t1 -> Q t (Z [Char]) t1
+TYPE CONSTRUCTORS
+ data Q s a chain
+ RecFlag NonRecursive
+ = Node :: forall s a chain. s -> a -> chain -> Q s a chain
+ Stricts: _ _ _
+ FamilyInstance: none
+ data Z a
+ RecFlag NonRecursive
+ = Z :: forall a. a -> Z a Stricts: _
+ FamilyInstance: none
+ class Zork s a b | a -> b
+ RecFlag NonRecursive
+ huh :: forall chain. Q s a chain -> ST s ()
+COERCION AXIOMS
+ axiom ShouldCompile.NTCo:Zork [s, a, b]
+ :: Zork s a b ~# (forall chain. Q s a chain -> ST s ())
+Dependent modules: []
+Dependent packages: [base, ghc-prim, integer-gmp]
diff --git a/testsuite/tests/typecheck/should_fail/FrozenErrorTests.stderr b/testsuite/tests/typecheck/should_fail/FrozenErrorTests.stderr index de552764d1..193d356190 100644 --- a/testsuite/tests/typecheck/should_fail/FrozenErrorTests.stderr +++ b/testsuite/tests/typecheck/should_fail/FrozenErrorTests.stderr @@ -1,73 +1,73 @@ - -FrozenErrorTests.hs:11:1: - 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:11:1 - Inaccessible code in - the type signature for foo :: a ~ T a => a -> a - -FrozenErrorTests.hs:14:12: - Couldn't match type `b' with `T b' - `b' is a rigid type variable bound by - a pattern with constructor - MkT2 :: forall a b. b ~ T b => b -> T a, - in a case alternative - at FrozenErrorTests.hs:14:12 - Inaccessible code in - a pattern with constructor - MkT2 :: forall a b. b ~ T b => b -> T a, - in a case alternative - In the pattern: MkT2 y - In a case alternative: MkT2 y -> () - In the expression: case x of { MkT2 y -> () } - -FrozenErrorTests.hs:19: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:33:9: - Occurs check: cannot construct the infinite type: a0 = [a0] - In the expression: goo1 False undefined - In an equation for `test1': test1 = goo1 False undefined - -FrozenErrorTests.hs:36:15: - Couldn't match type `[Int]' with `[[Int]]' - 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:37:9: - Couldn't match type `Int' with `[Int]' - In the expression: goo1 False (goo2 undefined) - In an equation for `test3': test3 = goo1 False (goo2 undefined) - -FrozenErrorTests.hs:52:15: - Couldn't match type `T2 (T2 c0 c0) c0' - with `T2 (M (T2 (T2 c0 c0) c0)) (T2 (T2 c0 c0) c0)' - 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:53:9: - Occurs check: cannot construct the infinite type: - c0 = T2 (T2 c0 c0) c0 - In the expression: goo3 False (goo4 undefined) - In an equation for `test5': test5 = goo3 False (goo4 undefined) - -FrozenErrorTests.hs:53:9: - Occurs check: cannot construct the infinite type: - c0 = T2 (T2 c0 c0) c0 - In the expression: goo3 False (goo4 undefined) - In an equation for `test5': test5 = goo3 False (goo4 undefined) - -FrozenErrorTests.hs:53:9: - Couldn't match type `T2 c0' with `M' - In the expression: goo3 False (goo4 undefined) - In an equation for `test5': test5 = goo3 False (goo4 undefined) +
+FrozenErrorTests.hs:11:1:
+ 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:11:1
+ Inaccessible code in
+ the type signature for foo :: a ~ T a => a -> a
+
+FrozenErrorTests.hs:14:12:
+ Couldn't match type `b' with `T b'
+ `b' is a rigid type variable bound by
+ a pattern with constructor
+ MkT2 :: forall a b. b ~ T b => b -> T a,
+ in a case alternative
+ at FrozenErrorTests.hs:14:12
+ Inaccessible code in
+ a pattern with constructor
+ MkT2 :: forall a b. b ~ T b => b -> T a,
+ in a case alternative
+ In the pattern: MkT2 y
+ In a case alternative: MkT2 y -> ()
+ In the expression: case x of { MkT2 y -> () }
+
+FrozenErrorTests.hs:19: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:33:9:
+ Occurs check: cannot construct the infinite type: a0 = [a0]
+ In the expression: goo1 False undefined
+ In an equation for `test1': test1 = goo1 False undefined
+
+FrozenErrorTests.hs:36:15:
+ Couldn't match type `[Int]' with `Int'
+ 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:37:9:
+ Couldn't match type `Int' with `[Int]'
+ In the expression: goo1 False (goo2 undefined)
+ In an equation for `test3': test3 = goo1 False (goo2 undefined)
+
+FrozenErrorTests.hs:52:15:
+ Occurs check: cannot construct the infinite type:
+ c0 = T2 (T2 c0 c0) c0
+ 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:52:15:
+ Couldn't match type `T2 c0' with `M'
+ 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:53:9:
+ Occurs check: cannot construct the infinite type:
+ c0 = T2 (T2 c0 c0) c0
+ In the expression: goo3 False (goo4 undefined)
+ In an equation for `test5': test5 = goo3 False (goo4 undefined)
+
+FrozenErrorTests.hs:53:9:
+ Couldn't match type `T2 c0' with `M'
+ 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/T1899.stderr b/testsuite/tests/typecheck/should_fail/T1899.stderr index 4769b2d96c..b0c017351a 100644 --- a/testsuite/tests/typecheck/should_fail/T1899.stderr +++ b/testsuite/tests/typecheck/should_fail/T1899.stderr @@ -1,15 +1,10 @@ - -T1899.hs:13:13: - Couldn't match type `a' with `Proposition a0' - `a' is a rigid type variable bound by - the type signature for transRHS :: [a] -> Int -> Constraint a - at T1899.hs:10:2 - Expected type: Constraint a - Actual type: Constraint (Proposition a0) - In the expression: - Formula $ [[Prop (Auxiliary varSet), Prop (Auxiliary varSet)]] - In the expression: - if b < 0 then - Formula [[Prop (Auxiliary undefined)]] - else Formula - $ [[Prop (Auxiliary varSet), Prop (Auxiliary varSet)]] +
+T1899.hs:14:36:
+ Couldn't match type `a' with `Proposition a0'
+ `a' is a rigid type variable bound by
+ the type signature for transRHS :: [a] -> Int -> Constraint a
+ at T1899.hs:10:2
+ Expected type: [Proposition a0]
+ Actual type: [a]
+ In the first argument of `Auxiliary', namely `varSet'
+ In the first argument of `Prop', namely `(Auxiliary varSet)'
diff --git a/testsuite/tests/typecheck/should_fail/T2688.stderr b/testsuite/tests/typecheck/should_fail/T2688.stderr index f7215b7abd..817c7202e5 100644 --- a/testsuite/tests/typecheck/should_fail/T2688.stderr +++ b/testsuite/tests/typecheck/should_fail/T2688.stderr @@ -1,12 +1,12 @@ - -T2688.hs:8:14: - Could not deduce (v ~ s) - from the context (VectorSpace v s) - bound by the class declaration for `VectorSpace' - at T2688.hs:(5,1)-(8,23) - `v' is a rigid type variable bound by - the class declaration for `VectorSpace' at T2688.hs:5:19 - `s' is a rigid type variable bound by - the class declaration for `VectorSpace' at T2688.hs:5:21 - In the expression: v *^ (1 / s) - In an equation for `^/': v ^/ s = v *^ (1 / s) +
+T2688.hs:8:14:
+ Could not deduce (s ~ v)
+ from the context (VectorSpace v s)
+ bound by the class declaration for `VectorSpace'
+ at T2688.hs:(5,1)-(8,23)
+ `s' is a rigid type variable bound by
+ the class declaration for `VectorSpace' at T2688.hs:5:21
+ `v' is a rigid type variable bound by
+ the class declaration for `VectorSpace' at T2688.hs:5:19
+ In the expression: v *^ (1 / s)
+ In an equation for `^/': v ^/ s = v *^ (1 / s)
diff --git a/testsuite/tests/typecheck/should_fail/T5236.stderr b/testsuite/tests/typecheck/should_fail/T5236.stderr index 8ec3544f6a..76f6de2353 100644 --- a/testsuite/tests/typecheck/should_fail/T5236.stderr +++ b/testsuite/tests/typecheck/should_fail/T5236.stderr @@ -1,20 +1,20 @@ T5236.hs:17:5:
- Couldn't match type `B' with `A'
+ Couldn't match type `A' with `B'
When using functional dependencies to combine
- Id B B,
- arising from the dependency `b -> a'
- in the instance declaration at T5236.hs:11:10
+ 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:17:5:
- Couldn't match type `A' with `B'
+ Couldn't match type `B' with `A'
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 B B,
+ arising from the dependency `b -> a'
+ in the instance declaration at T5236.hs:11: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
diff --git a/testsuite/tests/typecheck/should_fail/tcfail006.stderr b/testsuite/tests/typecheck/should_fail/tcfail006.stderr index b2a3f5b04a..d9ab68bcda 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail006.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail006.stderr @@ -1,8 +1,8 @@ - -tcfail006.hs:5:20: - No instance for (Num Bool) - arising from the literal `1' - Possible fix: add an instance declaration for (Num Bool) - In the expression: 1 - In the expression: (1, True) - In a case alternative: False -> (1, True) +
+tcfail006.hs:4:24:
+ No instance for (Num Bool)
+ arising from the literal `1'
+ Possible fix: add an instance declaration for (Num Bool)
+ In the expression: 1
+ In the expression: (True, 1)
+ In a case alternative: True -> (True, 1)
diff --git a/testsuite/tests/typecheck/should_fail/tcfail007.stderr b/testsuite/tests/typecheck/should_fail/tcfail007.stderr index 3545f8644f..6f93a462a2 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail007.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail007.stderr @@ -1,11 +1,10 @@ - -tcfail007.hs:3:16: - No instance for (Num Bool) - arising from the literal `1' - Possible fix: add an instance declaration for (Num Bool) - In the second argument of `(+)', namely `1' - In the expression: x + 1 - In an equation for `n': - n x - | True = x + 1 - | False = True +
+tcfail007.hs:3:15:
+ No instance for (Num Bool)
+ arising from a use of `+'
+ Possible fix: add an instance declaration for (Num Bool)
+ In the expression: x + 1
+ In an equation for `n':
+ n x
+ | True = x + 1
+ | False = True
diff --git a/testsuite/tests/typecheck/should_fail/tcfail010.stderr b/testsuite/tests/typecheck/should_fail/tcfail010.stderr index 34a52ed1d2..20a6d222a7 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail010.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail010.stderr @@ -1,8 +1,8 @@ - -tcfail010.hs:3:18: - No instance for (Num [t0]) - arising from the literal `2' - Possible fix: add an instance declaration for (Num [t0]) - In the second argument of `(+)', namely `2' - In the expression: z + 2 - In the expression: \ (y : z) -> z + 2 +
+tcfail010.hs:3:17:
+ No instance for (Num [t0])
+ arising from a use of `+'
+ Possible fix: add an instance declaration for (Num [t0])
+ In the expression: z + 2
+ In the expression: \ (y : z) -> z + 2
+ In an equation for `q': q = \ (y : z) -> z + 2
diff --git a/testsuite/tests/typecheck/should_fail/tcfail015.stderr b/testsuite/tests/typecheck/should_fail/tcfail015.stderr index 52dc7956cd..24affd76d9 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail015.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail015.stderr @@ -1,10 +1,7 @@ - -tcfail015.hs:9:39: - No instance for (Num Bool) - arising from the literal `4' - Possible fix: add an instance declaration for (Num Bool) - In the expression: 4 - In an equation for `g': - g (ANode b (ANode c d)) - | b = c + 1 - | otherwise = 4 +
+tcfail015.hs:7:13:
+ No instance for (Num Bool)
+ arising from the literal `2'
+ Possible fix: add an instance declaration for (Num Bool)
+ In the expression: 2
+ In an equation for `g': g (ANull) = 2
diff --git a/testsuite/tests/typecheck/should_fail/tcfail040.stderr b/testsuite/tests/typecheck/should_fail/tcfail040.stderr index 8d30ec57a2..19020b609d 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail040.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail040.stderr @@ -1,8 +1,8 @@ - -tcfail040.hs:19:14: - Ambiguous type variable `a0' in the constraint: - (ORD a0) arising from a use of `<<' - Probable fix: add a type signature that fixes these type variable(s) - In the second argument of `(===)', namely `(<<)' - In the expression: (<<) === (<<) - In an equation for `f': f = (<<) === (<<) +
+tcfail040.hs:19:5:
+ Ambiguous type variable `a0' in the constraint:
+ (ORD a0) arising from a use of `<<'
+ Probable fix: add a type signature that fixes these type variable(s)
+ In the first argument of `(===)', namely `(<<)'
+ In the expression: (<<) === (<<)
+ In an equation for `f': f = (<<) === (<<)
diff --git a/testsuite/tests/typecheck/should_fail/tcfail065.stderr b/testsuite/tests/typecheck/should_fail/tcfail065.stderr index 637ebcaabc..da855d3e6f 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail065.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail065.stderr @@ -1,12 +1,12 @@ - -tcfail065.hs:29:18: - Couldn't match type `x' with `x1' - `x' is a rigid type variable bound by - the instance declaration at tcfail065.hs:28:18 - `x1' is a rigid type variable bound by - the type signature for setX :: x1 -> X x -> X x - at tcfail065.hs:29:3 - Expected type: X x1 - Actual type: X x - In the return type of a call of `X' - In the expression: X x +
+tcfail065.hs:29:18:
+ Couldn't match type `x1' with `x'
+ `x1' is a rigid type variable bound by
+ the type signature for setX :: x1 -> X x -> X x
+ at tcfail065.hs:29:3
+ `x' is a rigid type variable bound by
+ the instance declaration at tcfail065.hs:28:18
+ Expected type: X x1
+ Actual type: X x
+ In the return type of a call of `X'
+ In the expression: X x
diff --git a/testsuite/tests/typecheck/should_fail/tcfail068.stderr b/testsuite/tests/typecheck/should_fail/tcfail068.stderr index afc8a3cc7b..52adc6c582 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail068.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail068.stderr @@ -1,92 +1,92 @@ - -tcfail068.hs:14:9: - Could not deduce (s1 ~ s) - from the context (Constructed a) - bound by the type signature for - itgen :: Constructed a => (Int, Int) -> a -> IndTree s a - at tcfail068.hs:(12,1)-(14,31) - `s1' is a rigid type variable bound by - a type expected by the context: GHC.ST.ST s1 (IndTree s a) - at tcfail068.hs:13:9 - `s' is a rigid type variable bound by - the type signature for - itgen :: Constructed a => (Int, Int) -> a -> IndTree s a - at tcfail068.hs:12:1 - Expected type: GHC.ST.ST s1 (IndTree s a) - Actual type: GHC.ST.ST s (STArray s (Int, Int) a) - In the return type of a call of `newSTArray' - In the first argument of `runST', namely - `(newSTArray ((1, 1), n) x)' - -tcfail068.hs:20:9: - Could not deduce (s1 ~ s) - from the context (Constructed a) - bound by the type signature for - itiap :: Constructed a => - (Int, Int) -> (a -> a) -> IndTree s a -> IndTree s a - at tcfail068.hs:(17,1)-(21,19) - `s1' is a rigid type variable bound by - a type expected by the context: GHC.ST.ST s1 (IndTree s a) - at tcfail068.hs:18:9 - `s' is a rigid type variable bound by - the type signature for - itiap :: Constructed a => - (Int, Int) -> (a -> a) -> IndTree s a -> IndTree s a - at tcfail068.hs:17:1 - Expected type: GHC.ST.ST s1 () - Actual type: GHC.ST.ST s () - In the return type of a call of `writeSTArray' - In the first argument of `(>>)', namely - `writeSTArray arr i (f val)' - -tcfail068.hs:24:35: - Could not deduce (s ~ s1) - from the context (Constructed a) - bound by the type signature for - itrap :: Constructed a => - ((Int, Int), (Int, Int)) -> (a -> a) -> IndTree s a -> IndTree s a - at tcfail068.hs:(24,1)-(32,41) - `s' is a rigid type variable bound by - the type signature for - itrap :: Constructed a => - ((Int, Int), (Int, Int)) -> (a -> a) -> IndTree s a -> IndTree s a - at tcfail068.hs:24:1 - `s1' is a rigid type variable bound by - a type expected by the context: GHC.ST.ST s1 (IndTree s a) - at tcfail068.hs:24:29 - Expected type: GHC.ST.ST s1 (IndTree s a) - Actual type: GHC.ST.ST s (IndTree s a) - In the return type of a call of itrap' - In the first argument of `runST', namely `(itrap' i k)' - -tcfail068.hs:36:46: - Could not deduce (s ~ s1) - from the context (Constructed b) - bound by the type signature for - itrapstate :: Constructed b => - ((Int, Int), (Int, Int)) - -> (a -> b -> (a, b)) - -> ((Int, Int) -> c -> a) - -> (a -> c) - -> c - -> IndTree s b - -> (c, IndTree s b) - at tcfail068.hs:(36,1)-(45,66) - `s' is a rigid type variable bound by - the type signature for - itrapstate :: Constructed b => - ((Int, Int), (Int, Int)) - -> (a -> b -> (a, b)) - -> ((Int, Int) -> c -> a) - -> (a -> c) - -> c - -> IndTree s b - -> (c, IndTree s b) - at tcfail068.hs:36:1 - `s1' is a rigid type variable bound by - a type expected by the context: GHC.ST.ST s1 (c, IndTree s b) - at tcfail068.hs:36:40 - Expected type: GHC.ST.ST s1 (c, IndTree s b) - Actual type: GHC.ST.ST s (c, IndTree s b) - In the return type of a call of itrapstate' - In the first argument of `runST', namely `(itrapstate' i k s)' +
+tcfail068.hs:14:9:
+ Could not deduce (s ~ s1)
+ from the context (Constructed a)
+ bound by the type signature for
+ itgen :: Constructed a => (Int, Int) -> a -> IndTree s a
+ at tcfail068.hs:(12,1)-(14,31)
+ `s' is a rigid type variable bound by
+ the type signature for
+ itgen :: Constructed a => (Int, Int) -> a -> IndTree s a
+ at tcfail068.hs:12:1
+ `s1' is a rigid type variable bound by
+ a type expected by the context: GHC.ST.ST s1 (IndTree s a)
+ at tcfail068.hs:13:9
+ Expected type: GHC.ST.ST s1 (IndTree s a)
+ Actual type: GHC.ST.ST s (STArray s (Int, Int) a)
+ In the return type of a call of `newSTArray'
+ In the first argument of `runST', namely
+ `(newSTArray ((1, 1), n) x)'
+
+tcfail068.hs:20:9:
+ Could not deduce (s ~ s1)
+ from the context (Constructed a)
+ bound by the type signature for
+ itiap :: Constructed a =>
+ (Int, Int) -> (a -> a) -> IndTree s a -> IndTree s a
+ at tcfail068.hs:(17,1)-(21,19)
+ `s' is a rigid type variable bound by
+ the type signature for
+ itiap :: Constructed a =>
+ (Int, Int) -> (a -> a) -> IndTree s a -> IndTree s a
+ at tcfail068.hs:17:1
+ `s1' is a rigid type variable bound by
+ a type expected by the context: GHC.ST.ST s1 (IndTree s a)
+ at tcfail068.hs:18:9
+ Expected type: GHC.ST.ST s1 ()
+ Actual type: GHC.ST.ST s ()
+ In the return type of a call of `writeSTArray'
+ In the first argument of `(>>)', namely
+ `writeSTArray arr i (f val)'
+
+tcfail068.hs:24:35:
+ Could not deduce (s ~ s1)
+ from the context (Constructed a)
+ bound by the type signature for
+ itrap :: Constructed a =>
+ ((Int, Int), (Int, Int)) -> (a -> a) -> IndTree s a -> IndTree s a
+ at tcfail068.hs:(24,1)-(32,41)
+ `s' is a rigid type variable bound by
+ the type signature for
+ itrap :: Constructed a =>
+ ((Int, Int), (Int, Int)) -> (a -> a) -> IndTree s a -> IndTree s a
+ at tcfail068.hs:24:1
+ `s1' is a rigid type variable bound by
+ a type expected by the context: GHC.ST.ST s1 (IndTree s a)
+ at tcfail068.hs:24:29
+ Expected type: GHC.ST.ST s1 (IndTree s a)
+ Actual type: GHC.ST.ST s (IndTree s a)
+ In the return type of a call of itrap'
+ In the first argument of `runST', namely `(itrap' i k)'
+
+tcfail068.hs:36:46:
+ Could not deduce (s ~ s1)
+ from the context (Constructed b)
+ bound by the type signature for
+ itrapstate :: Constructed b =>
+ ((Int, Int), (Int, Int))
+ -> (a -> b -> (a, b))
+ -> ((Int, Int) -> c -> a)
+ -> (a -> c)
+ -> c
+ -> IndTree s b
+ -> (c, IndTree s b)
+ at tcfail068.hs:(36,1)-(45,66)
+ `s' is a rigid type variable bound by
+ the type signature for
+ itrapstate :: Constructed b =>
+ ((Int, Int), (Int, Int))
+ -> (a -> b -> (a, b))
+ -> ((Int, Int) -> c -> a)
+ -> (a -> c)
+ -> c
+ -> IndTree s b
+ -> (c, IndTree s b)
+ at tcfail068.hs:36:1
+ `s1' is a rigid type variable bound by
+ a type expected by the context: GHC.ST.ST s1 (c, IndTree s b)
+ at tcfail068.hs:36:40
+ Expected type: GHC.ST.ST s1 (c, IndTree s b)
+ Actual type: GHC.ST.ST s (c, IndTree s b)
+ In the return type of a call of itrapstate'
+ In the first argument of `runST', namely `(itrapstate' i k s)'
diff --git a/testsuite/tests/typecheck/should_fail/tcfail102.stderr b/testsuite/tests/typecheck/should_fail/tcfail102.stderr index af047e5dce..792c941081 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail102.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail102.stderr @@ -1,17 +1,18 @@ - -tcfail102.hs:1:14: - Warning: -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language. - -tcfail102.hs:9:7: - Could not deduce (Integral (Ratio a)) arising from a record update - from the context (Integral a) - bound by the type signature for - f :: Integral a => P (Ratio a) -> P (Ratio a) - at tcfail102.hs:9:1-19 - Possible fix: - add (Integral (Ratio a)) to the context of - the type signature for - f :: Integral a => P (Ratio a) -> P (Ratio a) - or add an instance declaration for (Integral (Ratio a)) - In the expression: x {p = p x} - In an equation for `f': f x = x {p = p x} +
+tcfail102.hs:1:14:
+ Warning: -XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
+
+tcfail102.hs:9:15:
+ Could not deduce (Integral (Ratio a)) arising from a use of `p'
+ from the context (Integral a)
+ bound by the type signature for
+ f :: Integral a => P (Ratio a) -> P (Ratio a)
+ at tcfail102.hs:9:1-19
+ Possible fix:
+ add (Integral (Ratio a)) to the context of
+ the type signature for
+ f :: Integral a => P (Ratio a) -> P (Ratio a)
+ or add an instance declaration for (Integral (Ratio a))
+ In the `p' field of a record
+ In the expression: x {p = p x}
+ In an equation for `f': f x = x {p = p x}
diff --git a/testsuite/tests/typecheck/should_fail/tcfail103.stderr b/testsuite/tests/typecheck/should_fail/tcfail103.stderr index a892b23c43..17fea5cada 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail103.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail103.stderr @@ -1,11 +1,11 @@ - -tcfail103.hs:15:13: - Couldn't match type `s' with `t' - `s' is a rigid type variable bound by - the type signature for g :: ST s Int at tcfail103.hs:15:9 - `t' is a rigid type variable bound by - the type signature for f :: ST t Int at tcfail103.hs:11:1 - Expected type: ST s Int - Actual type: ST t Int - In the return type of a call of `readSTRef' - In the expression: readSTRef v +
+tcfail103.hs:15:13:
+ Couldn't match type `t' with `s'
+ `t' is a rigid type variable bound by
+ the type signature for f :: ST t Int at tcfail103.hs:11:1
+ `s' is a rigid type variable bound by
+ the type signature for g :: ST s Int at tcfail103.hs:15:9
+ Expected type: ST s Int
+ Actual type: ST t Int
+ In the return type of a call of `readSTRef'
+ In the expression: readSTRef v
diff --git a/testsuite/tests/typecheck/should_fail/tcfail131.stderr b/testsuite/tests/typecheck/should_fail/tcfail131.stderr index 134b76ffb3..548e063929 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail131.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail131.stderr @@ -1,11 +1,11 @@ - -tcfail131.hs:7:13: - Could not deduce (b ~ Integer) - from the context (Num b) - bound by the type signature for g :: Num b => b -> b - at tcfail131.hs:7:3-13 - `b' is a rigid type variable bound by - the type signature for g :: Num b => b -> b at tcfail131.hs:7:3 - In the second argument of `f', namely `x' - In the expression: f x x - In an equation for `g': g x = f x x +
+tcfail131.hs:7:9:
+ Could not deduce (b ~ Integer)
+ from the context (Num b)
+ bound by the type signature for g :: Num b => b -> b
+ at tcfail131.hs:7:3-13
+ `b' is a rigid type variable bound by
+ the type signature for g :: Num b => b -> b at tcfail131.hs:7:3
+ In the return type of a call of `f'
+ In the expression: f x x
+ In an equation for `g': g x = f x x
diff --git a/testsuite/tests/typecheck/should_fail/tcfail143.stderr b/testsuite/tests/typecheck/should_fail/tcfail143.stderr index 846f8c0252..2c3857e0ee 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail143.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail143.stderr @@ -1,11 +1,22 @@ - -tcfail143.hs:29:9: - Couldn't match type `S Z' with `Z' - When using functional dependencies to combine - MinMax a Z Z a, - arising from the dependency `a b -> c d' - in the instance declaration at tcfail143.hs:11:10 - MinMax (S Z) Z Z Z, - arising from a use of `extend' at tcfail143.hs:29:9-16 - In the expression: n1 `extend` n0 - In an equation for `t2': t2 = n1 `extend` n0 +
+tcfail143.hs:29:9:
+ Couldn't match type `S Z' with `Z'
+ When using functional dependencies to combine
+ MinMax a Z Z a,
+ arising from the dependency `a b -> c d'
+ in the instance declaration at tcfail143.hs:11:10
+ MinMax (S Z) Z Z Z,
+ arising from a use of `extend' at tcfail143.hs:29:9-16
+ In the expression: n1 `extend` n0
+ In an equation for `t2': t2 = n1 `extend` n0
+
+tcfail143.hs:29:9:
+ Couldn't match type `Z' with `S Z'
+ When using functional dependencies to combine
+ MinMax Z Z Z Z,
+ arising from the dependency `b c d -> a'
+ in the instance declaration at tcfail143.hs:10:10
+ MinMax (S Z) Z Z Z,
+ arising from a use of `extend' at tcfail143.hs:29:9-16
+ In the expression: n1 `extend` n0
+ In an equation for `t2': t2 = n1 `extend` n0
diff --git a/testsuite/tests/typecheck/should_fail/tcfail179.stderr b/testsuite/tests/typecheck/should_fail/tcfail179.stderr index d9b4538a17..48f5e26d78 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail179.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail179.stderr @@ -1,14 +1,14 @@ - -tcfail179.hs:14:37: - Couldn't match type `x' with `s' - `x' is a rigid type variable bound by - a pattern with constructor - T :: forall s x. (s -> (x -> s) -> (x, s, Int)) -> T s, - in a case alternative - at tcfail179.hs:14:14 - `s' is a rigid type variable bound by - the type signature for run :: T s -> Int at tcfail179.hs:13:1 - Expected type: (s, s, Int) - Actual type: (x, s, Int) - In the return type of a call of `g' - In the expression: g x id +
+tcfail179.hs:14:37:
+ Couldn't match type `s' with `x'
+ `s' is a rigid type variable bound by
+ the type signature for run :: T s -> Int at tcfail179.hs:13:1
+ `x' is a rigid type variable bound by
+ a pattern with constructor
+ T :: forall s x. (s -> (x -> s) -> (x, s, Int)) -> T s,
+ in a case alternative
+ at tcfail179.hs:14:14
+ Expected type: (s, x, Int)
+ Actual type: (x, s, Int)
+ In the return type of a call of `g'
+ In the expression: g x id
diff --git a/testsuite/tests/typecheck/should_fail/tcfail192.stderr b/testsuite/tests/typecheck/should_fail/tcfail192.stderr index 400671b684..a957fba52a 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail192.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail192.stderr @@ -1,18 +1,19 @@ - -tcfail192.hs:8:13: - No instance for (Num [[Char]]) - arising from the literal `1' - Possible fix: add an instance declaration for (Num [[Char]]) - In the second argument of `(+)', namely `1' - In the expression: x + 1 - In the expression: - [x + 1 | x <- ["Hello", "World"], then group using take 5] - -tcfail192.hs:10:26: - Couldn't match type `a' with `[a]' - `a' is a rigid type variable bound by - a type expected by the context: [a] -> [[a]] at tcfail192.hs:10:9 - Expected type: [a] -> [[a]] - Actual type: [[a]] -> [[a]] - In the return type of a call of `take' - In the expression: take 5 +
+tcfail192.hs:8:11:
+ No instance for (Num [[Char]])
+ arising from a use of `+'
+ Possible fix: add an instance declaration for (Num [[Char]])
+ In the expression: x + 1
+ In the expression:
+ [x + 1 | x <- ["Hello", "World"], then group using take 5]
+ In an equation for `foo':
+ foo = [x + 1 | x <- ["Hello", "World"], then group using take 5]
+
+tcfail192.hs:10:26:
+ Couldn't match type `a' with `[a]'
+ `a' is a rigid type variable bound by
+ a type expected by the context: [a] -> [[a]] at tcfail192.hs:10:9
+ Expected type: [a] -> [[a]]
+ Actual type: [[a]] -> [[a]]
+ In the return type of a call of `take'
+ In the expression: take 5
diff --git a/testsuite/tests/typecheck/should_fail/tcfail201.stderr b/testsuite/tests/typecheck/should_fail/tcfail201.stderr index 5efb129a45..23dd02614b 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail201.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail201.stderr @@ -1,13 +1,15 @@ - -tcfail201.hs:18:56: - Couldn't match type `a' with `HsDoc t0' - `a' is a rigid type variable bound by - the type signature for - gfoldl' :: (forall a1 b. c (a1 -> b) -> a1 -> c b) - -> (forall g. g -> c g) -> a -> c a - at tcfail201.hs:16:1 - Expected type: c a - Actual type: c (HsDoc t0) - In the expression: z DocParagraph `k` hsDoc - In a case alternative: - (DocParagraph hsDoc) -> z DocParagraph `k` hsDoc +
+tcfail201.hs:18:28:
+ Couldn't match type `a' with `HsDoc id0'
+ `a' is a rigid type variable bound by
+ the type signature for
+ gfoldl' :: (forall a1 b. c (a1 -> b) -> a1 -> c b)
+ -> (forall g. g -> c g) -> a -> c a
+ at tcfail201.hs:16:1
+ In the pattern: DocParagraph hsDoc
+ In a case alternative:
+ (DocParagraph hsDoc) -> z DocParagraph `k` hsDoc
+ In the expression:
+ case hsDoc of {
+ DocEmpty -> z DocEmpty
+ (DocParagraph hsDoc) -> z DocParagraph `k` hsDoc }
diff --git a/testsuite/tests/typecheck/should_fail/tcfail206.stderr b/testsuite/tests/typecheck/should_fail/tcfail206.stderr index 4cb3172926..fb812f1cbf 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail206.stderr +++ b/testsuite/tests/typecheck/should_fail/tcfail206.stderr @@ -1,47 +1,48 @@ - -tcfail206.hs:5:5: - Couldn't match expected type `Int' with actual type `Bool' - Expected type: Bool -> (Int, Bool) - Actual type: Bool -> (Bool, t0) - In the expression: (, True) - In an equation for `a': a = (, True) - -tcfail206.hs:8:5: - Couldn't match expected type `Bool -> (Int, Bool)' - with actual type `(t0, Int)' - Expected type: Int -> Bool -> (Int, Bool) - Actual type: Int -> (t0, Int) - In the expression: (1,) - In an equation for `b': b = (1,) - -tcfail206.hs:11:5: - Couldn't match type `a' with `Bool' - `a' is a rigid type variable bound by - the type signature for c :: a -> (a, Bool) at tcfail206.hs:11:1 - Expected type: a -> (a, Bool) - Actual type: Bool -> (Bool, Bool) - In the expression: (True || False,) - In an equation for `c': c = (True || False,) - -tcfail206.hs:14:5: - Couldn't match expected type `Int' with actual type `Bool' - Expected type: Bool -> (# Int, Bool #) - Actual type: Bool -> (# Bool, t0 #) - In the expression: (# , True #) - In an equation for `d': d = (# , True #) - -tcfail206.hs:17:5: - Couldn't match expected type `Bool -> (# Int, Bool #)' - with actual type `(# t0, Int #)' - Expected type: Int -> Bool -> (# Int, Bool #) - Actual type: Int -> (# t0, Int #) - In the expression: (# 1, #) - In an equation for `e': e = (# 1, #) - -tcfail206.hs:20:7: - Couldn't match type `a' with `Bool' - `a' is a rigid type variable bound by - the type signature for f :: a -> (# a, Bool #) at tcfail206.hs:20:1 - In the expression: True || False - In the expression: (# True || False, #) - In an equation for `f': f = (# True || False, #) +
+tcfail206.hs:5:5:
+ Couldn't match expected type `Int' with actual type `Bool'
+ Expected type: Bool -> (Int, Bool)
+ Actual type: Bool -> (Bool, t0)
+ In the expression: (, True)
+ In an equation for `a': a = (, True)
+
+tcfail206.hs:8:5:
+ Couldn't match expected type `Bool -> (Int, Bool)'
+ with actual type `(t0, Int)'
+ Expected type: Int -> Bool -> (Int, Bool)
+ Actual type: Int -> (t0, Int)
+ In the expression: (1,)
+ In an equation for `b': b = (1,)
+
+tcfail206.hs:11:5:
+ Couldn't match type `a' with `Bool'
+ `a' is a rigid type variable bound by
+ the type signature for c :: a -> (a, Bool) at tcfail206.hs:11:1
+ Expected type: a -> (a, Bool)
+ Actual type: Bool -> (Bool, Bool)
+ In the expression: (True || False,)
+ In an equation for `c': c = (True || False,)
+
+tcfail206.hs:14:5:
+ Couldn't match expected type `Int' with actual type `Bool'
+ Expected type: Bool -> (# Int, Bool #)
+ Actual type: Bool -> (# Bool, t0 #)
+ In the expression: (# , True #)
+ In an equation for `d': d = (# , True #)
+
+tcfail206.hs:17:5:
+ Couldn't match expected type `Bool -> (# Int, Bool #)'
+ with actual type `(# t0, Int #)'
+ Expected type: Int -> Bool -> (# Int, Bool #)
+ Actual type: Int -> (# t0, Int #)
+ In the expression: (# 1, #)
+ In an equation for `e': e = (# 1, #)
+
+tcfail206.hs:20:5:
+ Couldn't match type `a' with `Bool'
+ `a' is a rigid type variable bound by
+ the type signature for f :: a -> (# a, Bool #) at tcfail206.hs:20:1
+ Expected type: a -> (# a, Bool #)
+ Actual type: a -> (# a, a #)
+ In the expression: (# True || False, #)
+ In an equation for `f': f = (# True || False, #)
|