Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
What's new
10
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Open sidebar
Alex D
GHC
Commits
f861fc6a
Commit
f861fc6a
authored
Oct 30, 2014
by
Simon Peyton Jones
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
Test Trac #9708
parent
4723a0e3
Changes
3
Hide whitespace changes
Inline
Side-by-side
Showing
3 changed files
with
28 additions
and
0 deletions
+28
-0
testsuite/tests/typecheck/should_compile/T9708.hs
testsuite/tests/typecheck/should_compile/T9708.hs
+10
-0
testsuite/tests/typecheck/should_compile/T9708.stderr
testsuite/tests/typecheck/should_compile/T9708.stderr
+17
-0
testsuite/tests/typecheck/should_compile/all.T
testsuite/tests/typecheck/should_compile/all.T
+1
-0
No files found.
testsuite/tests/typecheck/should_compile/T9708.hs
0 → 100644
View file @
f861fc6a
{-# LANGUAGE DataKinds, TypeOperators, TypeFamilies #-}
module
TcTypeNatSimple
where
import
GHC.TypeLits
import
Data.Proxy
type
family
SomeFun
(
n
::
Nat
)
ti7
::
(
x
<=
y
,
y
<=
x
)
=>
Proxy
(
SomeFun
x
)
->
Proxy
y
->
()
ti7
_
_
=
()
testsuite/tests/typecheck/should_compile/T9708.stderr
0 → 100644
View file @
f861fc6a
T9708.hs:9:8:
Could not deduce (SomeFun x ~ SomeFun y)
from the context (x <= y, y <= x)
bound by the type signature for
ti7 :: (x <= y, y <= x) => Proxy (SomeFun x) -> Proxy y -> ()
at T9708.hs:9:8-61
NB: ‘SomeFun’ is a type function, and may not be injective
Expected type: Proxy (SomeFun x) -> Proxy y -> ()
Actual type: Proxy (SomeFun y) -> Proxy y -> ()
In the ambiguity check for:
forall (x :: Nat) (y :: Nat).
(x <= y, y <= x) =>
Proxy (SomeFun x) -> Proxy y -> ()
To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
In the type signature for ‘ti7’:
ti7 :: (x <= y, y <= x) => Proxy (SomeFun x) -> Proxy y -> ()
testsuite/tests/typecheck/should_compile/all.T
View file @
f861fc6a
...
...
@@ -421,3 +421,4 @@ test('MutRec', normal, compile, [''])
test
('
T8856
',
normal
,
compile
,
[''])
test
('
T9117
',
normal
,
compile
,
[''])
test
('
T9117_2
',
expect_broken
('
9117
'),
compile
,
[''])
test
('
T9708
',
normal
,
compile_fail
,
[''])
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