Skip to content
GitLab
Menu
Projects
Groups
Snippets
Loading...
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
GHC
Commits
b82410ab
Commit
b82410ab
authored
Nov 21, 2014
by
Simon Peyton Jones
Browse files
Trac
#9222
is actually an ambiguous type, now detected
parent
5760eb59
Changes
3
Show whitespace changes
Inline
Side-by-side
testsuite/tests/polykinds/T9222.hs
View file @
b82410ab
...
...
@@ -3,5 +3,11 @@ module T9222 where
import
Data.Proxy
-- Nov 2014: actually the type of Want is ambiguous if we
-- do the full co/contra thing for subtyping,
-- which we now do
-- So this program is erroneous. (But the original ticket was
-- a crash, and that's still fixed!)
data
Want
::
(
i
,
j
)
->
*
where
Want
::
(
a
~
'
(
b
,
c
)
=>
Proxy
b
)
->
Want
a
testsuite/tests/polykinds/T9222.stderr
0 → 100644
View file @
b82410ab
T9222.hs:13:3:
Couldn't match type ‘b0’ with ‘b’
‘b0’ is untouchable
inside the constraints (a ~ '(b0, c0))
bound by the type of the constructor ‘Want’:
(a ~ '(b0, c0)) => Proxy b0
at T9222.hs:13:3
‘b’ is a rigid type variable bound by
the type of the constructor ‘Want’:
((a ~ '(b, c)) => Proxy b) -> Want a
at T9222.hs:13:3
Expected type: '(b, c)
Actual type: a
In the ambiguity check for the type of the constructor ‘Want’:
Want :: forall (k :: BOX)
(k1 :: BOX)
(a :: (,) k k1)
(b :: k)
(c :: k1).
((a ~ '(b, c)) => Proxy b) -> Want a
To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
In the definition of data constructor ‘Want’
In the data declaration for ‘Want’
testsuite/tests/polykinds/all.T
View file @
b82410ab
...
...
@@ -102,7 +102,7 @@ test('T8705', normal, compile, [''])
test
('
T8985
',
normal
,
compile
,
[''])
test
('
T9106
',
normal
,
compile_fail
,
[''])
test
('
T9144
',
normal
,
compile_fail
,
[''])
test
('
T9222
',
normal
,
compile
,
[''])
test
('
T9222
',
normal
,
compile
_fail
,
[''])
test
('
T9264
',
normal
,
compile
,
[''])
test
('
T9263
',
normal
,
run_command
,
['
$MAKE -s --no-print-directory T9263
'])
test
('
T9063
',
normal
,
compile
,
[''])
...
...
Write
Preview
Markdown
is supported
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