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
ac2d9213
Commit
ac2d9213
authored
Sep 07, 2006
by
simonpj
Browse files
Revise tc103, in the light of the story for result type signatures
parent
6b2a0a0a
Changes
2
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail103.hs
View file @
ac2d9213
{-# OPTIONS -fglasgow-exts #-}
-- !!! Scoped type variables in result signatures
-- This one is a bit crafty
module
ShouldCompile
where
import
GHC.ST
import
GHC.STRef
import
GHC.Arr
-- Note the *pattern* type sig on f, which forces it
-- to be monomorphic; but the separate type sig makes
-- it polymorphic; hence the error.
-- Another 'escape' example
f
::
ST
t
Int
f
::
ST
s
Int
=
do
f
=
do
v
<-
newSTRef
5
let
g
::
ST
s
Int
-- ^ should be in scope
-- Implicitly forall a. ST s Int
g
=
readSTRef
v
g
testsuite/tests/ghc-regress/typecheck/should_fail/tcfail103.stderr
View file @
ac2d9213
tcfail103.hs:15:
0:
Inferred type is less polymorphic than expected
Quantified type variable `t' is mentioned in the environment:
Scoped type variable `s' = t (bound
at
:
tcfail103.hs:1
5:7)
When trying to generalise
the type
infer
re
d
for `f'
Signature type: forall t. ST t
Int
Type to generalise: ST t Int
In the
type signature for `f'
When generalising the type(s) for `f'
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:1
3:16
`t' is bound by
the type
signatu
re 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'
In the expression: readSTRef v
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