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
a1128bf9
Commit
a1128bf9
authored
Jul 04, 2007
by
Simon Marlow
Browse files
accept output
parent
1706e777
Changes
13
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/ghc-regress/gadt/lazypat.stderr
View file @
a1128bf9
lazypat.hs:7:2:
A lazy (~) pattern cannot bind existential type variables
`a' is bound by the constructor `T' at lazypat.hs:7:4
`a' is a rigid type variable bound by
the constructor `T' at lazypat.hs:7:4
In the pattern: ~(T x f)
In the definition of `f': f ~(T x f) = f x
testsuite/tests/ghc-regress/gadt/rw.stderr
View file @
a1128bf9
rw.hs:14:32:
Couldn't match expected type `a'
(a rigid variable)
against inferred type `Int'
`a' is bound by
the type signature for `writeInt' at rw.hs:12:13
Couldn't match expected type `a'
against inferred type `Int'
`a' is a rigid type variable bound by
the type signature for `writeInt' at rw.hs:12:13
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:36:
Couldn't match expected type `a'
(a rigid variable)
against inferred type `Bool'
`a' is bound by
the type signature for `readBool' at rw.hs:16:13
Couldn't match expected type `a'
against inferred type `Bool'
`a' is a rigid type variable bound by
the type signature for `readBool' at rw.hs:16:13
Expected type: a -> b
Inferred type: Bool -> Bool
In the second argument of `(.)', namely `not'
...
...
testsuite/tests/ghc-regress/indexed-types/should_fail/Simple12.stderr
View file @
a1128bf9
Simple12.hs:
6
:0:
Simple12.hs:
7
:0:
Illegal polymorphic type in type instance: forall a. [a]
testsuite/tests/ghc-regress/indexed-types/should_fail/Simple5a.stderr
View file @
a1128bf9
Simple5a.hs:31:10:
Couldn't match expected type `a' (a rigid variable)
against inferred type `Int'
`a' is bound by the type signature for `bar3wrong'
at Simple5a.hs:30:16
Couldn't match expected type `a' against inferred type `Int'
`a' is a rigid type variable bound by
the type signature for `bar3wrong' at Simple5a.hs:30:16
In the pattern: D3Int
In the definition of `bar3wrong': bar3wrong D3Int = 1
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail037.stderr
View file @
a1128bf9
tcfail037.hs:7:10:
Ambiguous occurrence `+'
It could refer to either `+', defined at tcfail037.hs:10:4
or `+', imported from Prelude
It could refer to either `
ShouldFail.
+', defined at tcfail037.hs:10:4
or `
Prelude.
+', imported from Prelude
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail065.stderr
View file @
a1128bf9
tcfail065.hs:29:19:
Couldn't match expected type `x'
(a rigid variable)
against inferred type
`x
1
'
(
a rigid variable
)
`x' is bound by
the instance declaration at tcfail065.hs:28:17
`x1' is
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
tcfail065.hs:29:19:
Couldn't match expected type `x'
against inferred type `x1'
`x'
is
a rigid
type
variable
bound by
the instance declaration 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/tcfail068.stderr
View file @
a1128bf9
tcfail068.hs:13:1:
Inferred type is less polymorphic than expected
Quantified type variable `s' escapes
In the first argument of `runST', namely
`(newSTArray ((1, 1), n) x)'
In the expression: runST (newSTArray ((1, 1), n) x)
In the definition of `itgen':
itgen n x = runST (newSTArray ((1, 1), n) x)
tcfail068.hs:19:13:
Couldn't match expected type `s' (a rigid variable)
against inferred type `s1' (a rigid variable)
`s' is bound by the polymorphic type `forall s. GHC.ST.ST s a'
at tcfail068.hs:18:1
`s1' is bound by the type signature for `itiap'
at tcfail068.hs:16:57
Expected type: STArray s i a1
Inferred type: IndTree s1 a2
In the first argument of `readSTArray', namely `arr'
In the first argument of `(>>=)', namely `readSTArray arr i'
tcfail068.hs:24:34:
Couldn't match expected type `s' (a rigid variable)
against inferred type `s1' (a rigid variable)
`s' is bound by the polymorphic type `forall s. GHC.ST.ST s a'
at tcfail068.hs:24:28
`s1' is bound by the type signature for `itrap'
at tcfail068.hs:23:69
Expected type: GHC.ST.ST s a
Inferred type: GHC.ST.ST s1 (IndTree s1 a1)
In the first argument of `runST', namely `(itrap' i k)'
In the expression: runST (itrap' i k)
tcfail068.hs:36:45:
Couldn't match expected type `s' (a rigid variable)
against inferred type `s1' (a rigid variable)
`s' is bound by the polymorphic type `forall s. GHC.ST.ST s a'
at tcfail068.hs:36:39
`s1' is bound by the type signature for `itrapstate'
at tcfail068.hs:35:25
Expected type: GHC.ST.ST s a
Inferred type: GHC.ST.ST s1 (c, IndTree s1 b)
In the first argument of `runST', namely `(itrapstate' i k s)'
In the expression: runST (itrapstate' i k s)
tcfail068.hs:13:1:
Inferred type is less polymorphic than expected
Quantified type variable `s' escapes
In the first argument of `runST', namely
`(newSTArray ((1, 1), n) x)'
In the expression: runST (newSTArray ((1, 1), n) x)
In the definition of `itgen':
itgen n x = runST (newSTArray ((1, 1), n) x)
tcfail068.hs:19:13:
Couldn't match expected type `s' against inferred type `s1'
`s' is a rigid type variable bound by
the polymorphic type `forall s. GHC.ST.ST s a' at tcfail068.hs:18:1
`s1' is a rigid type variable bound by
the type signature for `itiap' at tcfail068.hs:16:57
Expected type: STArray s i a1
Inferred type: IndTree s1 a2
In the first argument of `readSTArray', namely `arr'
In the first argument of `(>>=)', namely `readSTArray arr i'
tcfail068.hs:24:34:
Couldn't match expected type `s' against inferred type `s1'
`s' is a rigid type variable bound by
the polymorphic type `forall s. GHC.ST.ST s a'
at tcfail068.hs:24:28
`s1' is a rigid type variable bound by
the type signature for `itrap' at tcfail068.hs:23:69
Expected type: GHC.ST.ST s a
Inferred type: GHC.ST.ST s1 (IndTree s1 a1)
In the first argument of `runST', namely `(itrap' i k)'
In the expression: runST (itrap' i k)
tcfail068.hs:36:45:
Couldn't match expected type `s' against inferred type `s1'
`s' is a rigid type variable bound by
the polymorphic type `forall s. GHC.ST.ST s a'
at tcfail068.hs:36:39
`s1' is a rigid type variable bound by
the type signature for `itrapstate' at tcfail068.hs:35:25
Expected type: GHC.ST.ST s a
Inferred type: GHC.ST.ST s1 (c, IndTree s1 b)
In the first argument of `runST', namely `(itrapstate' i k s)'
In the expression: runST (itrapstate' i k s)
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail071.stderr
View file @
a1128bf9
...
...
@@ -10,8 +10,9 @@ tcfail071.hs:9:0:
tcfail071.hs:10:19:
Couldn't match expected type `a -> b -> b'
against inferred type `e' (a rigid variable)
`e' is bound by the type signature for `g' at tcfail071.hs:8:5
against inferred type `e'
`e' is a rigid type variable bound by
the type signature for `g' at tcfail071.hs:8:5
In the first argument of `foldr', namely `(f c)'
In the expression: foldr (f c) [] []
In the definition of `p': p = foldr (f c) [] []
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail076.stderr
View file @
a1128bf9
tcfail076.hs:18:67:
Couldn't match expected type `res' (a rigid variable)
against inferred type `res1' (a rigid variable)
`res' is bound by the polymorphic type
`forall res. (b -> m res) -> m res'
at tcfail076.hs:18:49
`res1' is bound by the polymorphic type
`forall res1. (a -> m res1) -> m res1'
at tcfail076.hs:18:13
Expected type: m res
Inferred type: m res1
In the expression: cont a
In a lambda abstraction: \ cont' -> cont a
tcfail076.hs:18:67:
Couldn't match expected type `res' against inferred type `res1'
`res' is a rigid type variable bound by
the polymorphic type `forall res. (b -> m res) -> m res'
at tcfail076.hs:18:49
`res1' is a rigid type variable bound by
the polymorphic type `forall res1. (a -> m res1) -> m res1'
at tcfail076.hs:18:13
Expected type: m res
Inferred type: m res1
In the expression: cont a
In a lambda abstraction: \ cont' -> cont a
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail103.stderr
View file @
a1128bf9
tcfail103.hs:15:22:
Couldn't match expected type `s' (a rigid variable)
against inferred type `t' (a rigid variable)
`s' is bound by the type signature for `g' at tcfail103.hs:13:16
`t' is bound by the type signature for `f' at tcfail103.hs:10:7
Couldn't match expected type `s' against inferred type `t'
`s' is a rigid type variable bound by
the type signature for `g' at tcfail103.hs:13:16
`t' is a rigid type variable bound by
the type signature for `f' at tcfail103.hs:10:7
Expected type: STRef s Int
Inferred type: STRef t t1
In the first argument of `readSTRef', namely `v'
...
...
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail153.stderr
View file @
a1128bf9
tcfail153.hs:6:8:
Couldn't match expected type `Bool'
against inferred type
`a'
(
a rigid variable
)
`a' is bound by
the type signature for `f' at tcfail153.hs:5:5
In the first argument of `g', namely `x'
In the expression: g x
In the definition of `f':
f x = g x
where
g y = if y then [] else [y]
tcfail153.hs:6:8:
Couldn't match expected type `Bool'
against inferred type `a'
`a'
is
a rigid
type
variable
bound by
the type signature for `f' at tcfail153.hs:5:5
In the first argument of `g', namely `x'
In the expression: g x
In the definition of `f':
f x = g x
where
g y = if y then [] else [y]
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail174.stderr
View file @
a1128bf9
...
...
@@ -9,9 +9,10 @@ tcfail174.hs:13:13:
In the first argument of `Capture', namely `g'
tcfail174.hs:16:13:
Couldn't match expected type `b' (a rigid variable)
against inferred type `a' (a rigid variable)
`b' is bound by the type signature for `h2' at tcfail174.hs:15:14
Couldn't match expected type `b' against inferred type `a'
`b' is a rigid type variable bound by
the type signature for `h2' at tcfail174.hs:15:14
`a'
When matching `forall a. a -> a'
and `forall a. a -> b'
Expected type: Capture (forall x. x -> b)
...
...
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail179.stderr
View file @
a1128bf9
tcfail179.hs:14:40:
Couldn't match expected type `s' (a rigid variable)
against inferred type `x' (a rigid variable)
`s' is bound by the type signature for `run' at tcfail179.hs:12:9
`x' is bound by the constructor `T' at tcfail179.hs:14:13
Couldn't match expected type `s' against inferred type `x'
`s' is a rigid type variable bound by
the type signature for `run' at tcfail179.hs:12:9
`x' is a rigid type variable bound by
the constructor `T' at tcfail179.hs:14:13
In the second argument of `g', namely `id'
In the expression: g x id
In a pattern binding: (x, _, b) = g x id
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