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
4f093d68
Commit
4f093d68
authored
Oct 26, 2012
by
Simon Peyton Jones
Browse files
Wibbles to type error messages
parent
2db1733a
Changes
5
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/indexed-types/should_compile/T3208b.stderr
View file @
4f093d68
T3208b.hs:15:10:
Could not deduce (STerm o0 ~ STerm a)
from the context (OTerm a ~ STerm a, OBJECT a, SUBST a)
bound by the type signature for
fce' :: (OTerm a ~ STerm a, OBJECT a, SUBST a) => a -> c
at T3208b.hs:14:9-56
NB: `STerm' is a type function, and may not be injective
The type variable `o0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Expected type: STerm o0
Actual type: OTerm o0
Relevant bindings include
fce' :: a -> c (bound at T3208b.hs:15:1)
f :: a (bound at T3208b.hs:15:6)
In the expression: fce (apply f)
In an equation for fce': fce' f = fce (apply f)
T3208b.hs:15:10:
Could not deduce (STerm o0 ~ STerm a)
from the context (OTerm a ~ STerm a, OBJECT a, SUBST a)
bound by the type signature for
fce' :: (OTerm a ~ STerm a, OBJECT a, SUBST a) => a -> c
at T3208b.hs:14:9-56
NB: `STerm' is a type function, and may not be injective
The type variable `o0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Expected type: STerm o0
Actual type: OTerm o0
Relevant bindings include
fce' :: a -> c (bound at T3208b.hs:15:1)
f :: a (bound at T3208b.hs:15:6)
In the expression: fce (apply f)
In an equation for fce': fce' f = fce (apply f)
T3208b.hs:15:15:
Could not deduce (OTerm o0 ~ STerm a)
from the context (OTerm a ~ STerm a, OBJECT a, SUBST a)
bound by the type signature for
fce' :: (OTerm a ~ STerm a, OBJECT a, SUBST a) => a -> c
at T3208b.hs:14:9-56
The type variable `o0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Relevant bindings include
fce' :: a -> c (bound at T3208b.hs:15:1)
f :: a (bound at T3208b.hs:15:6)
In the first argument of `fce', namely `(apply f)'
In the expression: fce (apply f)
In an equation for fce': fce' f = fce (apply f)
testsuite/tests/indexed-types/should_fail/GADTwrong1.stderr
View file @
4f093d68
GADTwrong1.hs:12:19:
Could not deduce (a1 ~ b)
from the context (
Const b
~ 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
`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)
In the expression: y
In a case alternative: T y -> y
In the expression: case T x :: T (Const b) of { T y -> y }
GADTwrong1.hs:12:19:
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
`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)
In the expression: y
In a case alternative: T y -> y
In the expression: case T x :: T (Const b) of { T y -> y }
testsuite/tests/indexed-types/should_fail/T2664.stderr
View file @
4f093d68
T2664.hs:31:52:
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-12
`b' is a rigid type variable bound by
the instance declaration at T2664.hs:22:10
`a' is a rigid type variable bound by
the instance declaration at T2664.hs:22:10
Expected type:
IO (PChan b, PChan
(Dual a)
)
Actual type:
IO (PChan (Dual (Dual a)), PChan (Dual a))
Relevant bindings include
newPChan :: IO (PChan (a :*: b), PChan c) (bound at T2664.hs:23:5)
v :: MVar (Either (PChan a) (PChan b)) (bound at T2664.hs:24:9)
In the third argument of `pchoose', namely `newPChan'
In the first argument of `E', namely `(pchoose Right v newPChan)'
In the expression:
E (pchoose Right v newPChan) (pchoose Left v newPChan)
T2664.hs:31:52:
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-12
`b' is a rigid type variable bound by
the instance declaration at T2664.hs:22:10
`a' is a rigid type variable bound by
the instance declaration at T2664.hs:22:10
Expected type:
Dual
(Dual a)
Actual type:
b
Relevant bindings include
newPChan :: IO (PChan (a :*: b), PChan c) (bound at T2664.hs:23:5)
v :: MVar (Either (PChan a) (PChan b)) (bound at T2664.hs:24:9)
In the third argument of `pchoose', namely `newPChan'
In the first argument of `E', namely `(pchoose Right v newPChan)'
In the expression:
E (pchoose Right v newPChan) (pchoose Left v newPChan)
testsuite/tests/indexed-types/should_fail/T2693.stderr
View file @
4f093d68
T2693.hs:10:7:
Couldn't match expected type `TFn a' with actual type `TFn a0'
NB: `TFn' is a type function, and may not be injective
The type variable `a0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
When checking that `x' has the inferred type `forall a. TFn a'
Probable cause: the inferred type is ambiguous
In the expression:
do { let Just x = ...;
let n = fst x + fst x;
return () }
In an equation for `f':
f = do { let Just x = ...;
let n = ...;
return () }
T2693.hs:18:15:
Couldn't match expected type `(a2, b0)' with actual type `TFn a3'
The type variables `a2', `b0', `a3' are ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Relevant bindings include n :: a2 (bound at T2693.hs:18:7)
In the first argument of `fst', namely `x'
In the first argument of `(+)', namely `fst x'
In the expression: fst x + snd x
T2693.hs:18:23:
Couldn't match expected type `(a4, a2)' with actual type `TFn a5'
The type variables `a2', `a4', `a5' are ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Relevant bindings include n :: a2 (bound at T2693.hs:18:7)
In the first argument of `snd', namely `x'
In the second argument of `(+)', namely `snd x'
In the expression: fst x + snd x
T2693.hs:29:26:
Couldn't match type `TFn a0' with `PVR a1'
The type variables `a0', `a1' are ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Expected type: [PVR a1]
Actual type: [TFn a0]
Relevant bindings include pvs :: [TFn a0] (bound at T2693.hs:28:8)
In the second argument of `map', namely `pvs'
In the first argument of `min', namely `(map pvrX pvs)'
In the expression: (map pvrX pvs) `min` (map pvrX pvs)
T2693.hs:10:7:
Couldn't match expected type `TFn a' with actual type `TFn a0'
NB: `TFn' is a type function, and may not be injective
The type variable `a0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
When checking that `x' has the inferred type `forall a. TFn a'
Probable cause: the inferred type is ambiguous
In the expression:
do { let Just x = ...;
let n = fst x + fst x;
return () }
In an equation for `f':
f = do { let Just x = ...;
let n = ...;
return () }
T2693.hs:18:15:
Couldn't match expected type `(a2, b0)' with actual type `TFn a3'
The type variables `a2', `b0', `a3' are ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Relevant bindings include n :: a2 (bound at T2693.hs:18:7)
In the first argument of `fst', namely `x'
In the first argument of `(+)', namely `fst x'
In the expression: fst x + snd x
T2693.hs:18:23:
Couldn't match expected type `(a4, a2)' with actual type `TFn a5'
The type variables `a2', `a4', `a5' are ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Relevant bindings include n :: a2 (bound at T2693.hs:18:7)
In the first argument of `snd', namely `x'
In the second argument of `(+)', namely `snd x'
In the expression: fst x + snd x
T2693.hs:28:20:
Couldn't match type `TFn a0' with `PVR a1'
The type variables `a0', `a1' are ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Expected type: () -> Maybe (PVR a1)
Actual type: () -> Maybe (TFn a0)
In the first argument of `mapM', namely `g'
In a stmt of a 'do' block: pvs <- mapM g undefined
In the expression:
do { pvs <- mapM g undefined;
let n = (map pvrX pvs) `min` (map pvrX pvs);
undefined }
testsuite/tests/indexed-types/should_fail/T5439.stderr
View file @
4f093d68
T5439.hs:83:33:
Couldn't match expected type `Attempt (WaitOpResult (WaitOps rs))'
with actual type `Attempt (HNth n0 l0) -> Attempt (HElemOf l0)'
Relevant bindings include
registerWaitOp :: WaitOps rs
-> f (Attempt (WaitOpResult (WaitOps rs))) -> IO Bool
(bound at T5439.hs:62:3)
ops :: WaitOps rs (bound at T5439.hs:62:18)
ev :: f (Attempt (WaitOpResult (WaitOps rs)))
(bound at T5439.hs:62:22)
register :: Bool -> Peano n -> WaitOps (HDrop n rs) -> IO Bool
(bound at T5439.hs:65:9)
In the second argument of `($)', namely
`inj $ Failure (e :: SomeException)'
In a stmt of a 'do' block:
c <- complete ev $ inj $ Failure (e :: SomeException)
In the expression:
do { c <- complete ev $ inj $ Failure (e :: SomeException);
return $ c || not first }
T5439.hs:83:39:
Couldn't match expected type `Peano n0'
with actual type `Attempt α0'
In the return type of a call of `Failure'
In the second argument of `($)', namely
`Failure (e :: SomeException)'
In the second argument of `($)', namely
`inj $ Failure (e :: SomeException)'
T5439.hs:83:28:
Couldn't match type `Attempt t0 -> Attempt (HElemOf l0)'
with `Attempt (HElemOf rs)'
Expected type: f (Attempt (HNth n0 l0) -> Attempt (HElemOf l0))
Actual type: f (Attempt (WaitOpResult (WaitOps rs)))
Relevant bindings include
registerWaitOp :: WaitOps rs
-> f (Attempt (WaitOpResult (WaitOps rs))) -> IO Bool
(bound at T5439.hs:62:3)
ops :: WaitOps rs (bound at T5439.hs:62:18)
ev :: f (Attempt (WaitOpResult (WaitOps rs)))
(bound at T5439.hs:62:22)
register :: Bool -> Peano n -> WaitOps (HDrop n rs) -> IO Bool
(bound at T5439.hs:65:9)
In the first argument of `complete', namely `ev'
In the expression: complete ev
In a stmt of a 'do' block:
c <- complete ev $ inj $ Failure (e :: SomeException)
T5439.hs:83:39:
Couldn't match expected type `Peano n0'
with actual type `Attempt α0'
In the return type of a call of `Failure'
In the second argument of `($)', namely
`Failure (e :: SomeException)'
In the second argument of `($)', namely
`inj $ Failure (e :: SomeException)'
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