Skip to content
GitLab
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
4c68c2f9
Commit
4c68c2f9
authored
Jan 12, 2012
by
Simon Peyton Jones
Browse files
Lots of error message wibbling, following the
major TcErrors refactoring
parent
ad0e1c9c
Changes
136
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/annotations/should_fail/annfail08.stderr
View file @
4c68c2f9
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) #-}
annfail08.hs:9:1:
No instance for (Data.Data.Data (a0 -> a0))
arising from an annotation
The type variable `a0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
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 `+'
The type variable `a0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Possible fix: add an instance declaration for (Num (a0 -> a0))
In the expression: (id + 1)
In the annotation: {-# ANN f (id + 1) #-}
testsuite/tests/annotations/should_fail/annfail10.stderr
View file @
4c68c2f9
annfail10.hs:9:1:
Ambiguous type variable `a0' in the constraints:
(Data.Data.Data a0) arising from an annotation
at annfail10.hs:9:1-15
(Num a0) arising from the literal `1' at annfail10.hs:9:11
Probable fix: add a type signature that fixes these type variable(s)
No instance for (Data.Data.Data a0)
arising from an annotation
The type variable `a0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
In the expression: 1
In the annotation: {-# ANN f 1 #-}
annfail10.hs:9:11:
No instance for (Num a0)
arising from the literal `1'
The type variable `a0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
In the expression: 1
In the annotation: {-# ANN f 1 #-}
testsuite/tests/arrows/should_fail/T5380.stderr
View file @
4c68c2f9
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 -< ()
T5380.hs:7:27:
Couldn't match expected type `not_bool' with actual type `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 -< ()
In an equation for `testB':
testB b f = proc () -> if b then f -< () else f -< ()
testsuite/tests/deriving/should_fail/T5287.stderr
View file @
4c68c2f9
T5287.hs:6:29:
Ambiguous type variable `oops' in the constraint:
(A e oops)
arising from the 'deriving' clause of a data type declaration
Probable fix: use a 'standalone deriving' declaration instead
When deriving the instance for (Read (E e))
T5287.hs:6:29:
No instance for (A e oops)
arising from the 'deriving' clause of a data type declaration
The type variable `oops' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Possible fix:
use a standalone 'deriving instance' declaration,
so you can specify the instance context yourself
When deriving the instance for (Read (E e))
testsuite/tests/gadt/T3169.stderr
View file @
4c68c2f9
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:
Could not deduce (elt ~ Map b elt)
from the context (Key a, Key b)
bound by the instance declaration at T3169.hs:10:10-36
`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)
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 (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 elt
Actual type: Map (a, b) elt
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 }
testsuite/tests/gadt/rw.stderr
View file @
4c68c2f9
rw.hs:14:47:
Couldn't match type `a' with `Int'
`a' is a rigid type variable bound by
the type signature for writeInt :: T a -> IORef a -> IO ()
at rw.hs:13:1
In the second argument of `writeIORef', namely `(1 :: Int)'
In the expression: writeIORef ref (1 :: Int)
In a case alternative: ~(Li x) -> writeIORef ref (1 :: Int)
rw.hs:19:51:
Couldn't match type `a' with `Bool'
`a' is a rigid type variable bound by
the type signature for readBool :: T a -> IORef a -> IO ()
at rw.hs:17:1
Expected type: a -> Bool
Actual type: Bool -> Bool
In the second argument of `(.)', namely `not'
In the second argument of `(>>=)', namely `(print . not)'
rw.hs:14:47:
Couldn't match expected type `a' with actual type `Int'
`a' is a rigid type variable bound by
the type signature for writeInt :: T a -> IORef a -> IO ()
at rw.hs:13:1
In the second argument of `writeIORef', namely `(1 :: Int)'
In the expression: writeIORef ref (1 :: Int)
In a case alternative: ~(Li x) -> writeIORef ref (1 :: Int)
rw.hs:19:51:
Couldn't match type `a' with `Bool'
`a' is a rigid type variable bound by
the type signature for readBool :: T a -> IORef a -> IO ()
at rw.hs:17:1
Expected type: a -> Bool
Actual type: Bool -> Bool
In the second argument of `(.)', namely `not'
In the second argument of `(>>=)', namely `(print . not)'
In the expression: readIORef ref >>= (print . not)
testsuite/tests/ghci.debugger/scripts/break003.stderr
View file @
4c68c2f9
...
...
@@ -2,5 +2,7 @@
<interactive>:5:1:
No instance for (Show (t -> a))
arising from a use of `print'
Cannot resolve unknown runtime types `t', `a'
Use :print or :force to determine these types
Possible fix: add an instance declaration for (Show (t -> a))
In a stmt of an interactive GHCi command: print it
testsuite/tests/ghci.debugger/scripts/break006.stderr
View file @
4c68c2f9
<interactive>:6:1:
Ambiguous type variable `a' in the constraint:
(Show a)
arising from a use of `print'
Cannot resolve unknown runtime type
s: a
No instance for (Show a)
arising from a use of `print'
Cannot resolve unknown runtime type
`a'
Use :print or :force to determine these types
In a stmt of an interactive GHCi command: print it
<interactive>:8:1:
Ambiguous type variable `a' in the constraint:
(Show a)
arising from a use of `print'
Cannot resolve unknown runtime type
s: a
No instance for (Show a)
arising from a use of `print'
Cannot resolve unknown runtime type
`a'
Use :print or :force to determine these types
In a stmt of an interactive GHCi command: print it
testsuite/tests/ghci.debugger/scripts/break018.stderr
View file @
4c68c2f9
<no location info>:
Warning:
-XRecursiveDo is deprecated: use -XDoRec or pragma {-# LANGUAGE DoRec #-} instead
<no location info>:
Warning:
-XRecursiveDo is deprecated: use -XDoRec or pragma {-# LANGUAGE DoRec #-} instead
testsuite/tests/ghci.debugger/scripts/dynbrk004.stderr
View file @
4c68c2f9
<no location info>:
Warning:
-XRecursiveDo is deprecated: use -XDoRec or pragma {-# LANGUAGE DoRec #-} instead
<no location info>:
Warning:
-XRecursiveDo is deprecated: use -XDoRec or pragma {-# LANGUAGE DoRec #-} instead
testsuite/tests/ghci.debugger/scripts/print006.stdout
View file @
4c68c2f9
...
...
@@ -2,7 +2,7 @@ t = O (_t1::a)
()
t = O ((_t2::a1) : (_t3::[a1]))
()
t = O ((_t4::a
2
) : (_t5::a
2
) : (_t6::[a
2
]))
t = O ((_t4::a
1
) : (_t5::a
1
) : (_t6::[a
1
]))
()
t = O ((_t7::Maybe [Integer]) : Just [2,2] :
(_t8::[Maybe [Integer]]))
...
...
testsuite/tests/ghci.debugger/scripts/print007.stderr
View file @
4c68c2f9
<no location info>:
Warning:
-O conflicts with --interactive; -O ignored.
<no location info>:
Warning:
-O conflicts with --interactive; -O ignored.
testsuite/tests/ghci.debugger/scripts/print019.stderr
View file @
4c68c2f9
<interactive>:11:1:
Ambiguous type variable `a1' in the constraint:
(Show a1)
arising from a use of `print'
Cannot resolve unknown runtime type
s:
a1
No instance for (Show a1)
arising from a use of `print'
Cannot resolve unknown runtime type
`
a1
'
Use :print or :force to determine these types
In a stmt of an interactive GHCi command: print it
testsuite/tests/ghci/scripts/Defer02.script
0 → 100755
View file @
4c68c2f9
-- Test -fwarn-type-errors
-- This test shows how each error is printed at runtime
:l ../../typecheck/should_run/Defer01
t5624
print a
print (b B)
print (c (C2 True))
print (d ())
print f
print (h ())
print (i ())
print j
print (k 2)
l
\ No newline at end of file
testsuite/tests/ghci/scripts/Defer02.stderr
0 → 100644
View file @
4c68c2f9
../../typecheck/should_run/Defer01.hs:11:40: Warning:
Couldn't match type `Char' with `[Char]'
Expected type: String
Actual type: Char
In the first argument of `putStr', namely ','
In the second argument of `(>>)', namely putStr ','
In the expression: putStr "Hello World" >> putStr ','
../../typecheck/should_run/Defer01.hs:14:5: Warning:
Couldn't match expected type `Int' with actual type `Char'
In the expression: 'p'
In an equation for `a': a = 'p'
../../typecheck/should_run/Defer01.hs:18:9: Warning:
No instance for (Eq B)
arising from a use of `=='
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:31:5: Warning:
Couldn't match expected type `Char -> t' with actual type `Char'
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:34:1
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'
In the return type of a call of `K'
In the first argument of `not', namely `(K a)'
In the first argument of `seq', namely `(not (K a))'
../../typecheck/should_run/Defer01.hs:43:5: Warning:
No instance for (MyClass a1)
arising from a use of `myOp'
The type variable `a1' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
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)
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:46:7: Warning:
Couldn't match expected type `Bool' with actual type `Int'
In the expression: x
In an equation for `k': k x = x
../../typecheck/should_run/Defer01.hs:49:5: Warning:
Couldn't match expected type `IO a0'
with actual type `Char -> IO ()'
In the first argument of `(>>)', namely `putChar'
In the expression: putChar >> putChar 'p'
In an equation for `l': l = putChar >> putChar 'p'
<interactive>:8:11:
Couldn't match type `Bool' with `Int'
Expected type: C Int
Actual type: C Bool
In the return type of a call of `C2'
In the first argument of `c', namely `(C2 True)'
In the first argument of `print', namely `(c (C2 True))'
<interactive>:14:8:
Couldn't match expected type `Bool' with actual type `Int'
In the first argument of `print', namely `(k 2)'
In the expression: print (k 2)
In an equation for `it': it = print (k 2)
testsuite/tests/ghci/scripts/T3263.stderr
View file @
4c68c2f9
T3263.hs:8:12:
Warning:
A do-notation statement discarded a result of type Char.
Suppress this warning by saying "_ <- getChar",
or by using the flag -fno-warn-unused-do-bind
T3263.hs:8:12:
Warning:
A do-notation statement discarded a result of type Char.
Suppress this warning by saying "_ <- getChar",
or by using the flag -fno-warn-unused-do-bind
testsuite/tests/ghci/scripts/T5130.stderr
View file @
4c68c2f9
<interactive>:3:27:
Couldn't match type `a' with `[Char]'
Couldn't match
expected
type `a' with
actual type
`[Char]'
In the expression: "hi"
In the expression: [x, "hi"]
In the expression: (\ (x :: a, y :: a) -> [x, "hi"])
testsuite/tests/ghci/scripts/all.T
100644 → 100755
View file @
4c68c2f9
...
...
@@ -108,3 +108,4 @@ test('T5557', normal, ghci_script, ['T5557.script'])
test
('
T5566
',
normal
,
ghci_script
,
['
T5566.script
'])
test
('
GhciKinds
',
normal
,
ghci_script
,
['
GhciKinds.script
'])
test
('
T5564
',
normal
,
ghci_script
,
['
T5564.script
'])
test
('
Defer02
',
normal
,
ghci_script
,
['
Defer02.script
'])
\ No newline at end of file
testsuite/tests/ghci/scripts/ghci031.stderr
View file @
4c68c2f9
ghci031.hs:1:14:
Warning:
-XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
ghci031.hs:1:14:
Warning:
-XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
testsuite/tests/ghci/scripts/ghci047.stderr
View file @
4c68c2f9
<interactive>:38:1:
Couldn't match type `HFalse' with `HTrue'
Expected type: HTrue
Actual type: Or HFalse HFalse
In the expression: f
In the expression: f $ Baz 'a'
In an equation for `it': it = f $ Baz 'a'
<interactive>:39:1:
Couldn't match type `HFalse' with `HTrue'
Expected type: HTrue
Actual type: Or HFalse HFalse
In the expression: f
In the expression: f $ Quz
In an equation for `it': it = f $ Quz
Prev
1
2
3
4
5
…
7
Next
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new 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