Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
GHC
Commits
c22af4a5
Commit
c22af4a5
authored
Sep 28, 2012
by
Simon Peyton Jones
Browse files
Tons of error message wibbles
parent
77193177
Changes
44
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/arrows/should_fail/T5380.stderr
View file @
c22af4a5
T5380.hs:7:27:
Couldn't match expected type `
not_b
ool' with actual type `
B
ool'
Couldn't match expected type `
B
ool' with actual type `
not_b
ool'
`not_bool' is a rigid type variable bound by
the type signature for
testB :: not_bool -> (() -> ()) -> () -> not_unit
...
...
testsuite/tests/arrows/should_fail/arrowfail001.stderr
View file @
c22af4a5
arrowfail001.hs:16:27:
Couldn't match expected type `a0' with actual type `a'
because type variable `a' would escape its scope
This (rigid, skolem) type variable is bound by
a pattern with constructor
Bar :: forall a. Foo a => a -> Bar,
in a case alternative
In the pattern: Bar a
In a case alternative: Bar a -> foo -< a
In the command: case x of { Bar a -> foo -< a }
arrowfail001.hs:16:36:
No instance for (Foo a
0
) arising from a use of `foo'
No instance for (Foo a) arising from a use of `foo'
In the expression: foo
In the expression: proc x -> case x of { Bar a -> foo -< a }
In an equation for `get':
...
...
testsuite/tests/deriving/should_fail/T5287.hs
View file @
c22af4a5
...
...
@@ -4,5 +4,6 @@ class A a oops
data
D
d
=
D
d
instance
A
a
oops
=>
Read
(
D
a
)
data
E
e
=
E
(
D
e
)
deriving
Read
instance
A
Int
Bool
testsuite/tests/deriving/should_fail/T5287.stderr
View file @
c22af4a5
...
...
@@ -4,6 +4,8 @@ T5287.hs:6:29:
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
...
...
testsuite/tests/deriving/should_fail/drvfail002.stderr
View file @
c22af4a5
...
...
@@ -2,8 +2,6 @@
drvfail002.hs:19:23:
No instance for (X T c)
arising from the 'deriving' clause of a data type declaration
The type variable `c' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Possible fix:
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
...
...
testsuite/tests/gadt/T3169.stderr
View file @
c22af4a5
T3169.hs:13:22:
Could not deduce (Map a ~ MP a b)
from the context (Key a, Key b)
bound by the instance declaration at T3169.hs:10:10-36
Expected type: Map a (Map b elt)
Actual type: Map (a, b) elt
Relevant bindings include
lookup :: (a, b) -> Map (a, b) elt -> Maybe elt
(bound at T3169.hs:12:3)
a :: a (bound at T3169.hs:12:11)
b :: b (bound at T3169.hs:12:13)
m :: Map (a, b) elt (bound at T3169.hs:12:17)
In the second argument of `lookup', namely `m'
In the expression: lookup a m :: Maybe (Map b elt)
In the expression:
case lookup a m :: Maybe (Map b elt) of {
Just (m2 :: Map b elt) -> lookup b m2 :: Maybe elt }
T3169.hs:13:22:
Could not deduce (elt ~ Map b elt)
from the context (Key a, Key b)
...
...
testsuite/tests/generics/GenCannotDoRep0.stderr
View file @
c22af4a5
...
...
@@ -9,7 +9,7 @@ GenCannotDoRep0.hs:13:45:
GenCannotDoRep0.hs:17:1:
Can't make a derived instance of `Generic (P Int)':
P must not be instantiated; try deriving `P
a
' instead
P must not be instantiated; try deriving `P
Int
' instead
In the stand-alone deriving instance for `Generic (P Int)'
GenCannotDoRep0.hs:26:1:
...
...
testsuite/tests/ghci/scripts/Defer02.stderr
View file @
c22af4a5
...
...
@@ -12,58 +12,37 @@
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 `=='
Possible fix: add an instance declaration for (Eq B)
In the expression: x == x
In an equation for `b': b x = x == x
../../typecheck/should_run/Defer01.hs:28:5: Warning:
No instance for (Num (a -> a)) arising from the literal `1'
Possible fix: add an instance declaration for (Num (a -> a))
In the expression: 1
In an equation for `d': d = 1
../../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: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 `a' with actual type `Char'
`a' is a rigid type variable bound by
the type signature for h :: a -> (Char, Char)
at ../../typecheck/should_run/Defer01.hs:33:6
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'
...
...
@@ -91,7 +70,6 @@
(deferred type error)
*** Exception: ../../typecheck/should_run/Defer01.hs:18:9:
No instance for (Eq B) arising from a use of `=='
Possible fix: add an instance declaration for (Eq B)
In the expression: x == x
In an equation for `b': b x = x == x
(deferred type error)
...
...
@@ -105,28 +83,36 @@
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'
Possible fix: add an instance declaration for (Num (a -> a))
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 `
a
' with actual type `
Char
'
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))
...
...
testsuite/tests/indexed-types/should_fail/GADTwrong1.stderr
View file @
c22af4a5
GADTwrong1.hs:12:19:
Could not deduce (
b
~
a1
)
Could not deduce (
a1
~
b
)
from the context (() ~ Const a1)
bound by a pattern with constructor
T :: forall a. a -> T (Const a),
in a case alternative
at GADTwrong1.hs:12:12-14
`b' is a rigid type variable bound by
the type signature for coerce :: a -> b at GADTwrong1.hs:10:20
`a1' is a rigid type variable bound by
a pattern with constructor
T :: forall a. a -> T (Const a),
in a case alternative
at GADTwrong1.hs:12:12
`b' is a rigid type variable bound by
the type signature for coerce :: a -> b at GADTwrong1.hs:10:20
Relevant bindings include
coerce :: a -> b (bound at GADTwrong1.hs:11:1)
y :: a1 (bound at GADTwrong1.hs:12:14)
...
...
testsuite/tests/indexed-types/should_fail/T1900.stderr
View file @
c22af4a5
...
...
@@ -6,7 +6,7 @@ T1900.hs:11:12:
In the instance declaration for `Bug Int'
T1900.hs:14:16:
Could not deduce (Depend s ~ Depend s
0
)
Could not deduce (Depend s
0
~ 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
...
...
testsuite/tests/indexed-types/should_fail/T2627b.stderr
View file @
c22af4a5
T2627b.hs:20:24:
Couldn't match expected type `a0' with actual type `
Dual (Dual
a0
)
'
Couldn't match expected type `
Dual (Dual
a0
)
' with actual type `a0'
`a0' is untouchable
inside the constraints (b ~ W a2 b2)
bound by a pattern with constructor
...
...
testsuite/tests/indexed-types/should_fail/T3330c.stderr
View file @
c22af4a5
T3330c.hs:23:43:
Couldn't match kind `*' with `* -> *'
Expected type: Der ((->) x) (f1 x)
Actual type: R f1
Kind incompatibility when matching types:
When matching types
Der ((->) x) :: * -> *
R :: (* -> *) -> *
Expected type: Der ((->) x) (f1 x)
Actual type: R f1
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)
testsuite/tests/indexed-types/should_fail/T3440.stderr
View file @
c22af4a5
T3440.hs:11:22:
Could not deduce (a ~ a
1
)
Could not deduce (a
1
~ a)
from the context (Fam a ~ Fam a1)
bound by a pattern with constructor
GADT :: forall a. a -> Fam a -> GADT (Fam a),
in an equation for `unwrap'
at T3440.hs:11:9-16
`a' is a rigid type variable bound by
the type signature for unwrap :: GADT (Fam a) -> (a, Fam a)
at T3440.hs:10:11
`a1' is a rigid type variable bound by
a pattern with constructor
GADT :: forall a. a -> Fam a -> GADT (Fam a),
in an equation for `unwrap'
at T3440.hs:11:9
`a' is a rigid type variable bound by
the type signature for unwrap :: GADT (Fam a) -> (a, Fam a)
at T3440.hs:10:11
Relevant bindings include
unwrap :: GADT (Fam a) -> (a, Fam a) (bound at T3440.hs:11:1)
x :: a1 (bound at T3440.hs:11:14)
...
...
testsuite/tests/module/mod54.stderr
View file @
c22af4a5
...
...
@@ -3,7 +3,6 @@ mod54.hs:3:22:
No instance for (Eq T)
arising from the 'deriving' clause of a data type declaration
Possible fix:
add an instance declaration for (Eq T)
or use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Ord T)
testsuite/tests/polykinds/T6054.stderr
View file @
c22af4a5
...
...
@@ -2,8 +2,6 @@
T6054.hs:7:14:
No instance for (Bar () '() a0)
arising from an expression type signature
The type variable `a0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
In the first argument of `print', namely
`(Proxy :: Bar () a => Proxy a)'
In the expression: print (Proxy :: Bar () a => Proxy a)
...
...
testsuite/tests/simplCore/should_run/T3591.stderr
View file @
c22af4a5
...
...
@@ -51,9 +51,17 @@ fmap await
fmap await
fmap await
liftOut
liftOut
inject suspend
liftFunctor id
calling fmap
fmap Either
poking a
fmap RightF
fmap Either
fmap RightF
fmap await
fmap await
bounce start
bounce end
liftOut
...
...
@@ -177,9 +185,17 @@ fmap await
fmap await
fmap await
liftOut
liftOut
inject suspend
liftFunctor id
calling fmap
fmap Either
poking a
fmap RightF
fmap Either
fmap RightF
fmap await
fmap await
bounce start
bounce end
bounce start
...
...
testsuite/tests/th/T5358.stderr
View file @
c22af4a5
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package array-0.4.0.1 ... linking ... done.
Loading package deepseq-1.3.0.1 ... linking ... done.
Loading package containers-0.5.0.0 ... linking ... done.
Loading package pretty-1.1.1.0 ... linking ... done.
Loading package template-haskell ... linking ... done.
T5358.hs:7:1:
Couldn't match expected type `t1 -> t1' with actual type `Int'
...
...
@@ -10,15 +18,34 @@ T5358.hs:8:1:
but its type `Int' has none
T5358.hs:10:13:
Couldn't match expected type `t0 -> a0' with actual type `Int'
Couldn't match expected type `t -> a0' with actual type `Int'
Relevant bindings include
prop_x1 :: t -> Bool (bound at T5358.hs:10:1)
x :: t (bound at T5358.hs:10:9)
The function `t1' is applied to one argument,
but its type `Int' has none
In the first argument of `(==)', namely `t1 x'
In the expression: t1 x == t2 x
T5358.hs:10:21:
Couldn't match expected type `t0 -> a0' with actual type `Int'
Couldn't match expected type `t -> a0' with actual type `Int'
Relevant bindings include
prop_x1 :: t -> Bool (bound at T5358.hs:10:1)
x :: t (bound at T5358.hs:10:9)
The function `t2' is applied to one argument,
but its type `Int' has none
In the second argument of `(==)', namely `t2 x'
In the expression: t1 x == t2 x
T5358.hs:12:15:
Exception when trying to run compile-time code:
runTest called error: forall t_0 . t_0 -> GHC.Types.Bool
Code: do { VarI _ t _ _ <- reify (mkName "prop_x1");
($) error ((++) "runTest called error: " pprint t) }
In the expression:
$(do { VarI _ t _ _ <- reify (mkName "prop_x1");
error $ ("runTest called error: " ++ pprint t) })
In an equation for `runTests':
runTests
= $(do { VarI _ t _ _ <- reify (mkName "prop_x1");
error $ ("runTest called error: " ++ pprint t) })
testsuite/tests/typecheck/should_compile/FD2.stderr
View file @
c22af4a5
FD2.hs:26:34:
Could not deduce (e
1
~ e)
Could not deduce (e ~ e
1
)
from the context (Foldable a)
bound by the class declaration for `Foldable'
at FD2.hs:(17,1)-(26,39)
...
...
@@ -12,14 +12,14 @@ FD2.hs:26:34:
bound by the type signature for
mf :: Elem a e1 => e1 -> Maybe e1 -> Maybe e1
at FD2.hs:24:18-54
`e1' is a rigid type variable bound by
the type signature for
mf :: Elem a e1 => e1 -> Maybe e1 -> Maybe e1
at FD2.hs:24:18
`e' is a rigid type variable bound by
the type signature for
foldr1 :: Elem a e => (e -> e -> e) -> a -> e
at FD2.hs:21:13
`e1' is a rigid type variable bound by
the type signature for
mf :: Elem a e1 => e1 -> Maybe e1 -> Maybe e1
at FD2.hs:24:18
Relevant bindings include
foldr1 :: (e -> e -> e) -> a -> e (bound at FD2.hs:22:3)
f :: e -> e -> e (bound at FD2.hs:22:10)
...
...
testsuite/tests/typecheck/should_compile/FD3.stderr
View file @
c22af4a5
...
...
@@ -4,6 +4,9 @@ FD3.hs:15:15:
`a' is a rigid type variable bound by
the type signature for translate :: (String, a) -> A a
at FD3.hs:14:14
Relevant bindings include
translate :: (String, a) -> A a (bound at FD3.hs:15:1)
a :: (String, a) (bound at FD3.hs:15:11)
When using functional dependencies to combine
MkA a a,
arising from the dependency `a -> b'
...
...
testsuite/tests/typecheck/should_compile/tc141.stderr
View file @
c22af4a5
...
...
@@ -8,10 +8,10 @@ tc141.hs:11:12:
tc141.hs:11:31:
Couldn't match expected type `a1' with actual type `a'
`a1' is a rigid
type variable
b
ou
n
d
by
an expression type signature: a1 at tc141.hs:11:31
`a' is a rigid type variable bound by
the inferred type of f :: (a, a) -> (t, a)
at tc141.hs:11:
1
because
type variable
`a1' w
ou
l
d
escape its scope
This (rigid, skolem) type variable is bound by
an expression type signature: a1
at tc141.hs:11:
31-34
Relevant bindings include
f :: (a, a) -> (t, a) (bound at tc141.hs:11:1)
x :: (a, a) (bound at tc141.hs:11:3)
...
...
@@ -35,10 +35,10 @@ tc141.hs:13:13:
tc141.hs:15:18:
Couldn't match expected type `a2' with actual type `t'
`a2' is a rigid
type variable
b
ou
n
d
by
the type signature for v :: a2 at tc141.hs:14:19
`t' is a rigid type variable bound by
the inferred type of g :: a -> t -> a1
at tc141.hs:1
3
:1
because
type variable
`a2' w
ou
l
d
escape its scope
This (rigid, skolem) type variable is bound by
the type signature for v :: a2
at tc141.hs:1
4
:1
9
Relevant bindings include
g :: a -> t -> a1 (bound at tc141.hs:13:1)
b :: t (bound at tc141.hs:13:5)
...
...
Prev
1
2
3
Next
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment