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
Fumiaki Kinoshita
GHC
Commits
a6786319
Commit
a6786319
authored
Sep 03, 2008
by
simonpj
Browse files
Follow error message changes
parent
7a116d7d
Changes
17
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/ghc-regress/deriving/should_fail/drvfail006.stderr
View file @
a6786319
drvfail006.hs:9:
0
:
drvfail006.hs:9:
44
:
Can't make a derived instance of `MonadState T'
(even with cunning newtype deriving:
`MonadState' does not have arity 1)
...
...
testsuite/tests/ghc-regress/deriving/should_fail/drvfail008.stderr
View file @
a6786319
drvfail008.hs:10:
0
:
drvfail008.hs:10:
42
:
Can't make a derived instance of `Monad M'
(`Monad' is not a derivable class
Try -XGeneralizedNewtypeDeriving for GHC's newtype-deriving extension)
...
...
testsuite/tests/ghc-regress/deriving/should_fail/drvfail011.stderr
View file @
a6786319
drvfail011.hs:8:0:
Could not deduce (Eq a) from the context (
Eq (T a)
)
Could not deduce (Eq a) from the context ()
arising from a use of `==' at drvfail011.hs:8:0-25
Possible fix:
add (Eq a) to the context of the type signature for `=='
In the expression: ((a1 == b1))
In the definition of `==': == (T1 a1) (T1 b1) = ((a1 == b1))
In the
definition for method `==
'
In the
instance declaration for `Eq (T a)
'
testsuite/tests/ghc-regress/typecheck/should_compile/T2494.stderr
View file @
a6786319
...
...
@@ -30,4 +30,4 @@ T2494.hs:15:32:
Expected type: Maybe b
Inferred type: Maybe a
In the second argument of `foo', namely `x'
When checking the transformation rule "foo/foo"
In the expression: foo (f . g) x
testsuite/tests/ghc-regress/typecheck/should_compile/all.T
View file @
a6786319
...
...
@@ -187,7 +187,7 @@ test('tc173',
test
('
tc174
',
only_compiler_types
(['
ghc
']),
compile
,
[''])
test
('
tc175
',
normal
,
compile
,
[''])
test
('
tc176
',
normal
,
compile
,
[''])
test
('
tc176
',
normal
,
compile
_fail
,
[''])
test
('
tc177
',
normal
,
compile
,
[''])
test
('
tc178
',
normal
,
compile
,
[''])
test
('
tc179
',
normal
,
compile
,
[''])
...
...
testsuite/tests/ghc-regress/typecheck/should_compile/tc176.hs
View file @
a6786319
...
...
@@ -14,6 +14,9 @@
/Bjorn Bringert -}
-- August 08: on reflection I think a complaint about overlapping
-- insances for line 8 is absolutely right, so I've changed this to
-- expected-failure
module
ShouldCompile
where
...
...
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail001.stderr
View file @
a6786319
...
...
@@ -2,5 +2,4 @@
tcfail001.hs:9:1:
The equation(s) for `op' have one argument,
but its type `[a]' has none
In the definition for method `op'
In the instance declaration for `A [a]'
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail031.stderr
View file @
a6786319
tcfail031.hs:3:9:
Couldn't match expected type `Bool' against inferred type `Char'
In the
predicate
expression: 'a'
In the expression: 'a'
In the expression: if 'a' then 1 else 2
In the definition of `f': f x = if 'a' then 1 else 2
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail042.stderr
View file @
a6786319
...
...
@@ -6,3 +6,17 @@ tcfail042.hs:15:9:
Possible fix:
add (Num a) to the context of the instance declaration
In the instance declaration for `Bar [a]'
tcfail042.hs:17:17:
Could not deduce (Num a) from the context (Eq a, Show a)
arising from a use of `foo' at tcfail042.hs:17:17-22
Possible fix:
add (Num a) to the context of the type signature for `bar'
In the expression: foo xs
In the definition of `bar':
bar (x : xs)
= foo xs
where
u = x == x
v = show x
In the instance declaration for `Bar [a]'
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail065.stderr
View file @
a6786319
tcfail065.hs:29:19:
Couldn't match expected type `x1' against inferred type `x'
`x1' is a rigid type variable bound by
the instance declaration at tcfail065.hs:28:17
Couldn't match expected type `x' against inferred type `x1'
`x' is a rigid type variable bound by
the type signature for `setX' at tcfail065.hs:25:10
the type signature for `setX' at tcfail065.hs:28:17
`x1' is a rigid type variable bound by
the type signature for `setX' at tcfail065.hs:25:10
In the first argument of `X', namely `x'
In the expression: X x
In the definition of `setX': setX x (X _) = X x
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail067.stderr
View file @
a6786319
...
...
@@ -37,24 +37,16 @@ tcfail067.hs:60:9:
In the instance declaration for `Num (SubRange a)'
tcfail067.hs:61:11:
Could not deduce (Ord a)
from the context (Num (SubRange a),
Num a,
Eq (SubRange a),
Show (SubRange a))
Could not deduce (Ord a) from the context (Num a)
arising from a use of `numSubRangeNegate' at tcfail067.hs:61:11-27
Possible fix:
add (Ord a) to the context of the type signature for `negate'
In the expression: numSubRangeNegate
In the definition of `negate': negate = numSubRangeNegate
In the
definition for method `negate
'
In the
instance declaration for `Num (SubRange a)
'
tcfail067.hs:65:18:
Could not deduce (Ord a)
from the context (Num (SubRange a),
Num a,
Eq (SubRange a),
Show (SubRange a))
Could not deduce (Ord a) from the context (Num a)
arising from a use of `SubRange' at tcfail067.hs:65:18-72
Possible fix:
add (Ord a) to the context of the type signature for `fromInteger'
...
...
@@ -63,7 +55,7 @@ tcfail067.hs:65:18:
In the definition of `fromInteger':
fromInteger a = SubRange
(fromInteger a, fromInteger a) (fromInteger a)
In the
definition for method `fromInteger
'
In the
instance declaration for `Num (SubRange a)
'
tcfail067.hs:74:4:
Could not deduce (Ord a) from the context (Num a)
...
...
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail104.stderr
View file @
a6786319
tcfail104.hs:11:6:
Cannot match a monotype with `forall a. a -> a'
In the expression: (\ x -> x)
In the expression:
(if v then (\ (x :: forall a. a -> a) -> x) else (\ x -> x)) id 'c'
(if v then (\ (x :: forall a. a -> a) -> x) else (\ x -> x)) id 'c'
In the definition of `f':
f v = (if v then (\ (x :: forall a. a -> a) -> x) else (\ x -> x))
id 'c'
f v = (if v then (\ (x :: forall a. a -> a) -> x) else (\ x -> x))
id 'c'
tcfail104.hs:17:6:
Cannot match a monotype with `forall a. a -> a'
In the expression: (\ x -> x)
In the expression:
(if v then (\ (x :: forall a. a -> a) -> x) else (\ x -> x)) id 'c'
(if v then (\ (x :: forall a. a -> a) -> x) else (\ x -> x)) id 'c'
In the definition of `g':
g v = (if v then (\ (x :: forall a. a -> a) -> x) else (\ x -> x))
id 'c'
g v = (if v then (\ (x :: forall a. a -> a) -> x) else (\ x -> x))
id 'c'
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail119.stderr
View file @
a6786319
...
...
@@ -3,4 +3,3 @@ tcfail119.hs:11:7:
Couldn't match expected type `Bool' against inferred type `[Char]'
In the pattern: "Foo"
In the definition of `b': b x "Foo" = ()
In the definition for method `b'
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail164.stderr
View file @
a6786319
...
...
@@ -12,5 +12,5 @@ tcfail164.hs:17:33:
e.g. (tagToEnum# x) :: Bool
In the expression: tagToEnum# value#
In the definition of `readUnboxable':
readUnboxable (I# value#) = tagToEnum# value#
In the
definition for method `read
Unboxable'
readUnboxable (I# value#) = tagToEnum# value#
In the
instance declaration for `
Unboxable
Int
'
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail185.stderr
View file @
a6786319
tcfail185.hs:7:31:
Couldn't match expected type `Int -> Int'
against inferred type `Bool'
against inferred type `Bool'
In the expression: x
In the expression:
let
y1 = y
y2 = y1
y3 = y2
....
in x
let
y1 = y
y2 = y1
y3 = y2
....
in x
In the expression:
\ x y
-> let
y1 = ...
....
in x
In the definition of `f': f a b = \ x y -> let ... in x
\ x y
-> let
y1 = ...
....
in x
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail198.stderr
View file @
a6786319
...
...
@@ -2,7 +2,7 @@
tcfail198.hs:6:37:
Couldn't match expected type `a1' against inferred type `a'
`a1' is a rigid type variable bound by
the polymorphic type `forall a1. a1'
at tcfail198.hs:6:
37
an expression type signature
at tcfail198.hs:6:
42
`a' is a rigid type variable bound by
the polymorphic type `forall a. [a] -> [a]' at tcfail198.hs:6:18
In the expression: x :: a
...
...
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail199.stderr
View file @
a6786319
tcfail199.hs:5:0:
Couldn't match expected type `IO t' against inferred type `[Char]'
In the expression: main
When checking the type of the function `main'
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