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
9ed7e8d6
Commit
9ed7e8d6
authored
May 26, 2018
by
Ryan Scott
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
Add regression test for #14246
parent
00f7e285
Changes
3
Hide whitespace changes
Inline
Side-by-side
Showing
3 changed files
with
48 additions
and
0 deletions
+48
-0
testsuite/tests/indexed-types/should_fail/T14246.hs
testsuite/tests/indexed-types/should_fail/T14246.hs
+23
-0
testsuite/tests/indexed-types/should_fail/T14246.stderr
testsuite/tests/indexed-types/should_fail/T14246.stderr
+24
-0
testsuite/tests/indexed-types/should_fail/all.T
testsuite/tests/indexed-types/should_fail/all.T
+1
-0
No files found.
testsuite/tests/indexed-types/should_fail/T14246.hs
0 → 100644
View file @
9ed7e8d6
{-# LANGUAGE RankNTypes, GADTs, TypeOperators, PolyKinds, DataKinds, TypeFamilies, AllowAmbiguousTypes, UndecidableInstances, TypeInType #-}
module
T14246
where
import
Data.Kind
-- necessary for *
data
Nat
=
Z
|
S
Nat
data
Vect
::
Nat
->
Type
->
Type
where
Nil
::
Vect
Z
a
Cons
::
a
->
Vect
n
a
->
Vect
(
S
n
)
a
data
Label
a
=
Label
a
data
L
type
family
KLN
(
n
::
k
)
::
Nat
where
KLN
(
f
::
v
->
k
)
=
S
(
KLN
(
forall
t
.
f
t
))
KLN
(
f
::
*
)
=
Z
type
family
Reveal
(
n
::
k
)
(
l
::
Vect
(
KLN
n
)
L
)
::
*
where
Reveal
(
f
::
v
->
k
)
(
Cons
(
Label
(
t
::
v
))
l
)
=
Reveal
(
f
t
)
l
Reveal
(
a
::
*
)
Nil
=
a
testsuite/tests/indexed-types/should_fail/T14246.stderr
0 → 100644
View file @
9ed7e8d6
T14246.hs:18:5: error:
• Illegal polymorphic type: forall (t :: v). f t
• In the equations for closed type family ‘KLN’
In the type family declaration for ‘KLN’
T14246.hs:22:27: error:
• Expected kind ‘Vect (KLN f) L’,
but ‘Cons (Label (t :: v)) l’ has kind ‘Vect ('S (KLN (f t))) *’
• In the second argument of ‘Reveal’, namely
‘(Cons (Label (t :: v)) l)’
In the type family declaration for ‘Reveal’
T14246.hs:22:67: error:
• Expected kind ‘Vect (KLN (f t)) L’,
but ‘l’ has kind ‘Vect (KLN (f t)) *’
• In the second argument of ‘Reveal’, namely ‘l’
In the type ‘Reveal (f t) l’
In the type family declaration for ‘Reveal’
T14246.hs:23:21: error:
• Expected kind ‘Vect (KLN a) L’, but ‘Nil’ has kind ‘Vect 'Z L’
• In the second argument of ‘Reveal’, namely ‘Nil’
In the type family declaration for ‘Reveal’
testsuite/tests/indexed-types/should_fail/all.T
View file @
9ed7e8d6
...
...
@@ -141,5 +141,6 @@ test('T14033', normal, compile_fail, [''])
test
('
T14045a
',
normal
,
compile_fail
,
[''])
test
('
T14175
',
normal
,
compile_fail
,
[''])
test
('
T14179
',
normal
,
compile_fail
,
[''])
test
('
T14246
',
normal
,
compile_fail
,
[''])
test
('
T14369
',
normal
,
compile_fail
,
[''])
test
('
T15172
',
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