Stefan Holdermans reports: I am almost sure this is a known issue, but I noticed some erroneous (?) interaction between datatype promotion and existential quantification. Consider the following program:
{-# LANGUAGE DataKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} module Test where data K = forall a. T a -- promotion gives 'T :: * -> K data G :: K -> * where D :: G (T []) -- kind error!
I would expect the type checker to reject it, but GHC (version 7.6.1) compiles it happily
Trac metadata
Trac field
Value
Version
7.6.1
Type
Bug
TypeOfFailure
OtherFailure
Priority
normal
Resolution
Unresolved
Component
Compiler
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Child items
0
Show closed items
No child items are currently assigned. Use child items to break down this issue into smaller parts.
Linked items
0
Link issues together to show that they're related or that one is blocking others.
Learn more.
If we promote existentials, people will want to pattern match on them to take them apart; we will need to deal with skolem-escape checks; etc. I don't know what the consequences are. I'd be happy to be told they are fine, but for now the implementation definitely isn't up to it, so better to exclude them now and allow them later.
It seems that all that GHC 7.6.1 currently allows is to promote existentially quantified variables of kind *. Such constructors, if promoted, lead to simply kinded datatypes. No polymorphism, no existentials on that level. So why not keep allowing them? There's no danger of escaping variables even for type families, afaics.
The bug Stefan reports seems to be a missing check whether the type is used according to its inferred kind.
As far as I know, we don't currently have a mechanism for pattern matching on an existential data constructor at the type level. I'm pretty sure that 7.6.1 is broken in this respect.
The point is still that if the kind of the promoted constructor is
MkEx :: * -> Ex
then there's no actual existential on the type level. We've just created a wrapper for values of kind *. I'm not arguing that we should promote constructors that would get polymorphic kinds of the form
MkStrange :: forall k. k -> Ex
AFAIK, Pedro makes use of promoted existentials in at least one of his generic universe encodings. So it'd be nice if they keep working, unless there's actually a problem with them.
should give an existential escape error, but it doesn't. Instead it somehow fixes the kind to *.
You are arguing for this in general. If we promote a data constructor, such as Just, whose type is
Just :: forall a. a -> Maybe a
then we get poly-kinded type constructor
'Just :: forlal k. k -> 'Maybe k
You are arguing for some different type-promotion rule for existentials. Maybe, but I have never thought about that and I don't know what the details would be.
If you want something that isn't kind-polymorphic, you don't need an existential at all. Wha you want is something like
data kind Ex = MkEx *
a perfectly ordinary non-existential data type with an argument of kind *. Now, as Pedro points out in his ICFP paper we don't have a way to say that, but that is quite a separate matter; existntials are a total red herring. Maybe we should have
data Ex = MkEx STAR
where STAR is an uninhabited type whose promotion to the kind level is *.
I'm sorry. I was confused by the fact that if I load a file containing
data Ex = forall a. MkEx a
into GHCi, I get this:
*Main> :kind 'MkEx'MkEx :: * -> Ex
But I note now that this is because I didn't say PolyKinds in GHCi. Indeed, then I get:
*Main> :set -XPolyKinds *Main> :kind 'MkEx'MkEx :: k -> Ex
So I thought GHC would not promote to an existential quantification on the type level, but it actually does. So yes, I was wrong, and this is indeed problematic.
Stephanie and I thought about this issue this morning, and we believe that promoting existentials is sound.
Consider this:
{-# LANGUAGE ExistentialQuantification, PolyKinds, DataKinds #-}data Ex = forall a. MkEx atype family UnEx (ex :: Ex) :: ktype instance UnEx (MkEx x) = x
This compiles in GHC 7.6.1, and it should.
First off, let's look at the type of 'MkEx, which is forall (k::BOX). k -> Ex. Now, let's look at the elaboration of UnEx in FC:
UnEx :: forall (k::BOX). Ex -> kaxUnEx :: forall k. forall (x::k). (UnEx k (MkEx k x) ~ x)
So, the elaboration of UnEx simply contains a non-linear pattern in k. But, because k is a parameter to UnEx, the kind of x is not really escaping. As proof, here is an excerpt of the output from -ddump-tc:
TYPE CONSTRUCTORS Ex :: * data Ex No C type associated RecFlag NonRecursive = MkEx :: forall a. a -> Ex Stricts: _ FamilyInstance: none UnEx :: forall (k :: BOX). Ex -> k type family UnEx (k::BOX) (ex::Ex) :: kCOERCION AXIOMS axiom Scratch.TFCo:R:UnExkMkEx (k :: BOX) (x :: k) :: UnEx k ('MkEx k x) ~# x
One comment above says that UnEx would default to a result kind of *. This would only happen in the absence of an explicit kind signature for the return kind; all un-annotated types involved in a type family default to *.
What's different about the type level is that there is no phase separation between kinds and types. Unpacking a type-level existential happens at compile time, so the type checker can incorporate what it learns in simplifying the call to UnEx.
data KEx :: * where MkKEx :: forall (a::k). Proxy a -> KEx
Now the kind variable k as well as the type variable a is existentially quantified, and NOW we will have to worry about existential escape, notwithstanding your comment about "no phase separation". Indeed I can't give a kind to UnKEx:
type family UnKEx :: KEx -> ???
So maybe what saves us here is that type families have user-specified kind signatures, and that in turn means we don't need to check for existential escape.
So I think I agree with your point, but I don't know how urgent/important it is, nor how hard it would be to implement. At its easiest it might mean just removing a restriction, but I'm not certain.
If you declare KEx as above, something weird happens when you promote (in 7.6.1): the type KEx gets promoted to a kind, but the kind-polymorphic data constructor MkKEx does not get promoted to a type. So, KEx becomes an uninhabited kind. This behavior is weird, but it seems not to violate any description of promotion: kind-polymorphic things are not promoted, and other (suitable) things are.
So, one cannot write an UnKEx type instance, and thus there is no problem.
I agree that this is far from urgent. But, if the checks you added to fix this bug added complexity, they could perhaps be removed. I believe the original implementation of naive promotion of existentials is the right one.
If another change is desirable, then I think it would be best to open a fresh ticket for it, so people looking at it don't have to trawl through so much history. Hence closing this one.