GHC 9.2 and TypeApplications

I’ve recently seen that GHC 9.2.8 no longer accepts TypeApplications with DataKinds as it used to in say, 8.6.5;

let a = SomeConstructor @'SomeKind ... 

GHC tells me:

Expected a type, but ''SomeKind' has kind 'SomeKind' 
... 

What is the expected workaround here?
Are there any changelogs etc. pointing this out?

My apologies for posting this, I couldn’t find any reference to this change online.

Can you give a complete file so that I can try to reproduce it?

This works for me:

{-# LANGUAGE DataKinds #-}
data SomeKind = SomeKind
data SomeType (a :: SomeKind) = SomeConstructor

a = SomeConstructor @'SomeKind
1 Like

As well as posting a complete example that demonstrates a difference between 9.2.8 and an earlier version, you might like to try :i SomeConstructor in GHCi. I think it’s quite likely it’s picked up a type argument that wasn’t there before (perhaps because of PolyKinds?).

1 Like

(Having said that I can’t persuade ghci's :i or :k to give me information about type arguments. I can’t remember what you have to do to get them …)

I couldn’t reproduce this on a minimal module:

data Foo = Foo | Bar
data SomeCons (k :: Foo) = SomeCons 

a = SomeCons @'Foo 
b = SomeCons @'Bar

But I can reproduce this on Constants.hs · GitHub

Which is fairly involved.

I can see that constructing values like:

a = AConstantVia @('DropLeft 3)

results in the error.

-fprint-explicit-foralls

or perhaps also -fprint-explicit-kinds

1 Like

Fixed. For posterity, the compiler required us to provide a type application for the kind as well as the type. e.g. for the type definition

data NormalEnum = FooBar | FooBarBaz
data Drop = DropLeft Nat | DropRight Nat
newtype AConstantVia (mods :: k) a = AConstantVia {unAConstant :: a}

the value definition needs to be

a = AConstantVia @Drop @('DropLeft 3) FooBarBaz
                  ^k     ^mods

Alternatively, using type annotations:

a = AConstantVia FooBarBaz :: AConstantVia ('DropLeft 3) NormalEnum
                                            ^mods        ^a
3 Likes

If you wanted to preserve the previous behavior, could introduce an explicit kind signature via -XStandaloneKindSignatures and use an inferred type variable for k in the signature:

type AConstantVia :: forall {k}. k -> Type -> Type
newtype AConstantVia mods a = AConstantVia {unAConstant :: a}

a = AConstantVia @('DropLeft 3) FooBarBaz

By marking the k type variable as inferred, it’s now hidden from type application.

4 Likes

Even more elegant, thanks!

I think the right way forward is to be provide a kind signature for every datatype for which type-application is expected. Otherwise the inferred kind could change between the GHC versions, but you also need to guess the correct parameterisation. I also think they make more complicated types easier to parse and you improve readability. I got quickly used to them.

1 Like

I also do think we should have this documented somewhere. I know ours is a bit of an esoteric use-case, but other people might also stumble upon the same issue.

The GHC migration guides might have coverage on this issue. I’m not sure what version past 8.6.5 introduced the breakage, but it’s probably worth skimming over the guides to see if it’s covered already. Going from 8.6 to 9.2 is a pretty big jump!