Skip to content

Draft: Add StandaloneKindSignatures. Kind arguments to polykinded types marked "specified" (forall.)

Icelandjack requested to merge Icelandjack/ghc:sks into master

Adds StandaloneKindSignatures to all of base given the latest style guide consensus.

For several polykinded types this goes from implicitly marking their invisible type argument as "inferred" (forall{}.) to "specified" (forall.) meaning we can now pass kind arguments to them Functor (Compose @Type @Type f g). I believe this is desirable as they are already polykinded, this just allows us to instantiate them explicitly.

  • Compose, Const, Product, Sum, Proxy
  • Ap, Alt
  • Coercion, (:~:)
  • If, TypeError

The documentation should reflect this change but I struggle finding the right description.

I took care not to change inferred arguments to specified in the data constructors:

type Proxy :: forall k. k -> Type
data Proxy a where
  Proxy :: forall {k} a. Proxy @k a

Type class declarations can not be given a specified quantifier since it will change previously inferred arguments in the type class methods as well

  • Category
  • TestCoercion, TestEquality
  • Datatype, Constructor, Selector
  • HasField

If we added a specified quantifier to Category we would involuntarily add an additional specified argument to id and (.)

type  Category :: forall ob. (ob -> ob -> Type) -> Constraint
class Category cat where
  id :: cat a a

-- id :: forall (ob :: Type) (cat :: ob -> ob -> Type) (a :: ob). Category cat => cat a a

In those cases I conservatively opt for specifying an inferred quantifier explicitly

type  Category :: forall {ob}. (ob -> ob -> Type) -> Constraint
class Category cat where
  id :: cat a a

-- id :: forall {ob :: Type} (cat :: ob -> ob -> Type) (a :: ob). Category cat => cat a a

which can then be evolve to forall ob. once we have more independent control over the inferrability of ob in class methods.

Edited by Andreas Klebinger

Merge request reports