Consider the following program and GHCi session which uses it:
{-# LANGUAGE PolyKinds #-}{-# LANGUAGE TypeFamilies #-}module Foo whereimport Data.Kindtype family T1 (x :: Type) (y :: a) :: Type where {}type family T2 x (y :: a) :: Type where {}
$ ghc2/inplace/bin/ghc-stage2 --interactive Foo.hs -fprint-explicit-forallsGHCi, version 8.7.20180831: http://www.haskell.org/ghc/ :? for helpLoaded GHCi configuration from /home/rgscott/.ghci[1 of 1] Compiling Foo ( Foo.hs, interpreted )Ok, one module loaded.λ> :kind T1T1 :: forall a. * -> a -> *λ> :kind T2T2 :: forall {k} {a}. k -> a -> *
Note that T1 quantifies a visibly whereas T2 does not. I find this somewhat surprising, since both T1 and T2 explicitly mention a in their respective definitions. The only difference between the two is that T1 has a CUSK while T2 does not.
This isn't of much importance at the moment, but it will be once visible kind application lands, as this will prevent anyone from instantiating the a in T2 using a kind application.
It's unclear to me whether this is intended behavior or not. I suppose there might be an unwritten rule that you can't use visible kind application on anything that doesn't have a CUSK, but if this really is the case, we should be upfront about it.
Trac metadata
Trac field
Value
Version
8.4.3
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.
I agree with ticket:15592#comment:159535. If a user writes the name of the variable, it is Specified. Thus, a is specified (in both declarations). k, unmentioned, is Inferred.
The constraint in meth1 looks like it's redundantly specifying that D should be instantiated at j and k. I say "redundantly" because D, without a CUSK, cannot be polymorphically recursive. However, we discover in meth2 that j actually depends on k. So (assuming inference succeeds at all, which I don't wish to debate here), we will get D :: forall (k :: Type) (j :: k). Proxy j -> Proxy k -> Type -> Constraint. (The Type in the third required argument to D comes from z's kind in meth1.)
Bottom line: any use of visible kind application should be considered to be an instance of polymorphic recursion, and thus should be banned in a mutually recursive group on a CUSK-less type. This is true even if the visible kind application is redundant.
Bottom line: any use of visible kind application should be considered to be an instance of polymorphic recursion.
Yes, and we (presumably) have exactly same at the term level
reverse (xs :: [a]) = ...(reverse @a ys)....
This is illegal. When type checking reverse's RHS we have reverse :: alpha in the envt, and you can't type-apply that to anything. If we had a signature
Ah, I now understand why non-CUSKed declarations seem to have totally different behavior with respect to visibility than CUSKed ones: their visibilities are determined in a completely different part of the code! In particular, in kcTyClGroup (as opposed to kcLHsQTyVars, which was the case for #15591 (closed)). These lines is quite relevant:
It appears that all kind variables are simply made invisible, which is clearly not what we want. Now we just need to figure out how to bend this code to our will...
That is: k2 is Inferred but k1 is Specified. But neither is among
the tc_binders of the TcTyCon that we make before kind-generalisation!
Those tc_binders are only the Required ones, positionally written by the user.
(It took me a while to work this out; we should write it down.)
OK so kindGeneralize will now generalise over both k1 and k1, in some
random order. We must
Mark the Inferred ones as Inferred and similarly Specified.
Put the former before the latter
How can we distinguish? Well, the Specified ones are among the tcScopedTyVars of the TcTyCon,
but the Inferred ones are not.
So I did this, in kcTyClGroup:
That looks quite sensible and is independent from what I've done. (I was thinking we might have to put these into the tc_binders, but that's hard to get right for a non-CUSK.) If what you have works, feel free to commit. It won't get in my way.
By a series of strange coincidences, I ended up with almost exactly the same code as in ticket:15592#comment:160968 while working on this this morning. (Don't worry, I won't work on this any further until the dust has settled on #14880 (closed).) There's one thing I haven't worked out, though: how to make this work for associated types (in light of #15591 (closed)). Consider:
classCawheretypeT(x::fa)
Ideally, the kind of T would be:
T::forall{k}(a::k)(f::k->Type).fa->Type
Alas, the code in ticket:15592#comment:160968 is not enough to accomplish this. It will instead give this as the kind for T:
T::forall{k}{a::k}(f::k->Type).fa->Type
Note that a is now invisible. Ack.
In order to fix this, we'd need to be aware of the fact that a is mentioned explicitly in C within kcTyClGroup. Currently, kcTyClGroup doesn't have access to this information, however.
Another gotcha is that if you only use the code in ticket:15592#comment:160968, it'll cause some programs to no longer typecheck. In particular, this program:
classCawheretypeT(x::(f::k->Type)a)
Bug.hs:8:3: error: • These kind and type variables: (x :: (f :: k -> Type) a) are out of dependency order. Perhaps try this ordering: k (a :: k) (f :: k -> *) (x :: f a) NB: Implicitly declared variables come before others. • In the associated type family declaration for ‘T’ |8 | type T (x :: (f :: k -> Type) a) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
In order to fix this, we'd need to be aware of the fact that a is mentioned explicitly in C within kcTyClGroup. Currently, kcTyClGroup doesn't have access to this information, however.
Hmm. I wonder if we should simply add a to the tyConScopedTyVars of T? And that info is available in kcLHsTQTVars which builds the TcTyCon. Richard?
Hmm. I wonder if we should simply add a to the tyConScopedTyVars of T? And that info is available in kcLHsTQTVars which builds the TcTyCon.
I too am a bit confused as to why we don't add a (or any kind variables, for that matter) to tcTyConScopedTyVars in the non-CUSK case of kcLHsQTyVars. The only reasoning I could find for this design choice is this terse comment:
;let-- NB: Don't add scoped_kvs to tyConTyVars, because they-- must remain lined up with the binderstc_binders=zipWithmk_tc_binderhs_tvstc_tvstycon=mkTcTyConname(ppruser_tyvars)tc_bindersres_kind(mkTyVarNamePairs(scoped_kvs++tc_tvs))flav
(Here, they call tcTyConScopedTyVars "tyConTyVars".)
I discovered that this bug fix has a visible effect! Consider this in GHC.Records:
-- | Constraint representing the fact that the field @x@ belongs to-- the record type @r@ and has field type @a@. This will be solved-- automatically, but manual instances may be provided as well.class HasField (x :: k) r a | x r -> a where -- | Selector function to extract the field from the record. getField :: r -> a
What is the kind of HasField and type of getField? As of today, GHC says
HasField :: forall {k}. k -> * -> * -> ConstraintgetField :: forall {k] (x::k) r a. HasField x r a => r -> a
But actually, because of the (x :: k) in the class decl, the k is Specified. So the correct kind and type are:
HasField :: forall k. k -> * -> * -> ConstraintgetField :: forall k (x::k) r a. HasField x r a => r -> a
So in a visible type application of getField you'd have to write getField @Symbol @x.
But that is not what Adam intended. We don't want to be forced to write that kind, even in a visible type application. We want k to be Inferred.
I can achieve this for now by changing the decl to
class HasField x r a | x r -> a where getField :: r -> a
so removing the :: k from the decl. But that is rather subtle. I'm looking forward to explicit kind signatures... but NB: they need to be able to express the Inferred/Specified distinction.
We certainly have C :: forall {k}. k -> Constraint. So k is Inferred and a is Required.
Now look at T. I think we want
T :: forall k (a::k) (f :: k->Type). f a -> Type
That is: k must be Specified (because the user wrote it); but it must precede the a which comes from the class. On the other hand, if T didn't mention k it'd be Inferred.
What about this?
class D (a::k) where type S a
Here k is Specified for D, but is it Specified or Inferred for S? The notes in Note [Required, Specified, and Inferred for types] do not really answer this question.
This business of thinking about how the class header affects the Inferred/Specified/Required spec for the associated type is desperately tricky. I still wonder if we should instead look at the type declaration alone.
An improvement would be this:
Whether the tyvar is Inferred or Specified is determined by looking at the associated type (alone)
But the order in which the Specified variables appear is affected by the class header.
Richard and I talked more about this. We worried about
class C a b where type T (x :: b a)
In what order do T's Specified variables show up?
We got as far as a detailed proposal for associated types:
Which vars are Specified and which Inferred is determined by type decl alone (Specified = explicitly mentioned in the type decl)
• For the Specified variables:
Start with lexical order from type decl
Do a stable partition, moving the ones from the class decl to the front
Use ScopedSort to put them in dependency order.
But it all seemed terribly complicated. We ended up thinking that it'd be
better to ingnore the class header, and just do the normal thing:
Start with the lexical order from the type decl
Use ScopedSort
This simplifies the spec, and simplifies the code.
It is a bit unlike what happens for class methods (where the class variables all show up at the front, but
we have no idea how to do make associated types really behave like class methods. Eg
class C a where type F a
Then perhaps F :: forall a -> C a => Type, which is not ery nice. And it gets worse
class C a b where type F a
then perhaps F :: forall {b}. forall a -> C a b => Type. Ugh. But if b depends on a we'd have to put
it later in the telescope.
So we decided to keep it simple! (This is a small change from the commit in #15592 (closed)).
Just to chime in agreement with ticket:15592#comment:163104. I'm sympathetic to the desire to put class variables first, but it gets ugly quickly. Here's another example:
classCawheretypeF(x::(f::k->Type)a)
Here, k is actually a class variable, even though that's highly non-obvious. So k should go in the first clump of variables. But it would be easy to assume that k, not mentioned in the class header, goes with the second clump of variables.
In the end, I agreed that there are just too many wrinkles in the "class variables come first" design, and went with "infer variable order / visibility locally" instead.
Author: mynguyen <mnguyen1@brynmawr.edu>Date: Tue Dec 18 11:52:26 2018 -0500 Visible kind application Summary: This patch implements visible kind application (GHC Proposal 15/#12045), as well as #15360 and #15362. It also refactors unnamed wildcard handling, and requires that type equations in type families in Template Haskell be written with full type on lhs. PartialTypeSignatures are on and warnings are off automatically with visible kind application, just like in term-level. There are a few remaining issues with this patch, as documented in ticket #16082. Includes a submodule update for Haddock. Test Plan: Tests T12045a/b/c/TH1/TH2, T15362, T15592a Reviewers: simonpj, goldfire, bgamari, alanz, RyanGlScott, Iceland_jack Subscribers: ningning, Iceland_jack, RyanGlScott, int-index, rwbarton, mpickering, carter GHC Trac Issues: `#12045`, `#15362`, `#15592`, `#15788`, `#15793`, `#15795`, `#15797`, `#15799`, `#15801`, `#15807`, `#15816` Differential Revision: https://phabricator.haskell.org/D5229