The Glasgow Haskell Compiler

Dependent Types: Current Status

Page structure. This page is an overview of language features and implementation tasks that contribute, directly or indirectly, towards the goal of adding dependent types to Haskell. The tasks are organized into a graph. Edges point to prerequisites or subtasks. Completed tasks are highlighted with a purple border. Accepted proposals awaiting implementation are marked by an orange border. After the graph you will find a grid of cards with information about each node.

Target audience. The primary purpose of this page is to track current implementation progress and indicate the relationships between various tasks, thus helping implementors and enthusiasts to see the big picture. You may find it difficult to follow some of the task descriptions if you are new to Haskell or unfamiliar with dependent types, but you might be able to find some useful links and resources.

Common questions. Before we proceed to the current state of the project, here are answers to some questions regarding dependent types in the context of Haskell.

Dependent Haskell dependent types in GHC Dependent retained quantifiers types that refer to terms Universal promotion promote all terms Clean up the language preparations for dependent types Dependent products Π-types Dependent sums Σ-types Dependent Core language formalism and implementation Visible forall in types of terms Existential quantification first-class exists quantifier Promote literals numeric, char, string Promote unboxed types RuntimeRep ≠ LiftedRep Promote classes constraints and dictionaries Function promotion promote term-level functions Data family promotion promote data families Promote Char and character literals Promote Natural unify it with Nat Constrained type families constraints in kinds Homogeneous equality instead of heterogeneous Closed term evaluator using bytecode or native code Open term evaluator normalization by evaluation Type-level lambdas first-class functions in types Dependency analysis of top-level declarations Unsaturated type families partial application in types Deprecate CUSKs complete user-supplied kinds Invisible type arguments applications and abstractions Namespace management to resolve ambiguities Unify type and kind variables consistent quantification rules Modifiers syntax generalized modifiers Standalone kind signatures replacement for CUSKs Invisible binders in types @k-binders in type declarations Invisible binders in functions @a-binders in lambdas Invisible binders in constructors @a-binders in constructor patterns Visible type applications @t-applications in terms Visible kind applications @k-applications in types Syntactic unification type syntax in terms No star kind syntax resolve conflict with operators The forall keyword at the term level The tilde operator for equality constraints The dot type operator for function composition Pun warnings warn on puns and pun bindings Namespace-specified imports filter imported names No list or tuple puns remove ambiguous built-in syntax Embed types into expressions Visibility coercions in the Core language Nested quantification in GADTs interleave foralls in constructors Term variable capture mention term variables in types Unify types and kinds with the Type :: Type axiom Whitespace-sensitive operators prefix vs infix occurrences
Last updated: 2025-02-26

Attribution

GHC is an open source compiler, and its development is of inherently collaborative nature. While Serokell OÜ has been funding its own GHC team since 2018 with the goal of adding dependent types to Haskell, our company has designed and implemented only some of the features described on this page.

We want to acknowledge the numerous contributions by other companies, institutions, and individuals. All further uses of we are meant to include all relevant contributors. Please consult the referenced publications, proposals, issues, and commits to determine the authors of each contribution.

Dependent Haskell

dependent types in GHC

Dependent types are a language feature that enables development of correct-by-construction software. Its key ideas are dependent quantification and dependent pattern-matching. As a paradigm, dependently-typed programming also relies on type-level data and type-level computation.

To some degree, these ideas already took root in Haskell in the form of GADTs, TypeFamilies, PolyKinds and DataKinds, but the limitations of those language extensions preclude their widespread adoption. Our goal is to make dependently-typed programming in Haskell ergonomic and practical.

Examples

A typesafe list indexing operation:

index :: foreach (xs :: List a) -> Fin (length xs) -> a index (x : xs) FZ = x index (x : xs) (FS i) = index xs i

The bounds check is performed statically if the index is a statically known constant. Otherwise, the type checker will ensure that the caller of this function performs a runtime bounds check. Either way, index never throws a runtime exception unlike (!!).

References

Dependencies

Three unsatisfied prerequisites or remaining subtasks:

  • Dependent retained quantifiers
  • Universal promotion
  • Clean up the language

Dependent retained quantifiers

types that refer to terms

To count Haskell among dependently-typed programming languages, we need to add support for the canonical dependent types: Σ-types and Π-types.

Dependent sums and dependent products derive their names from the mathematical notation for summation (Σ) and product (Π) respectively, so it might be helpful to see how their algebraic interpretation compares to that of existing (non-dependent) types in Haskell:

Math notationHaskell syntax
0Void
1Unit
A+BEither A B
A×BTuple2 A B
BAA → B
a:AF(a)foreach (a ∷ A) → F a
a:AF(a)some (a ∷ A) | F a

For example, given a type family F:BoolType, the dependent sum a:BoolF(a) is equivalent to F(False)+F(True).

From the standpoint of logic, Π-types and Σ-types are closely related to universal and existential quantification respectively. However, an important aspect of foreach and some is the possibility of a dependent pattern match, which makes them different from forall and exists.

To enable pattern matching, foreach/some-quantified variables must be retained at runtime, unlike forall/exists-quantified variables that are erased shortly after type checking. Consequently, the values of Σ-types and Π-types all have a particular runtime representation. Dependent sums are represented as pairs, hence their alternative name: dependent pairs; dependent products are represented as functions, hence their alternative name: dependent functions.

References

Dependencies

Two unsatisfied prerequisites or remaining subtasks:

  • Dependent products
  • Dependent sums

Dependent products

Π-types

Π-types, also known as dependent products or dependent functions, are functions whose result type depends on the value of the argument.

A dependent function is a hybrid between a function A -> B and universal quantification forall (a :: A). F a, sharing some properties with the former and some with the latter.

The mathematical notation for a dependent function type is a:AF(a), and the planned Haskell notation is foreach (a :: A) -> F a.

Dependencies

One unsatisfied prerequisite or remaining subtask:

  • Dependent Core language

Dependent sums

Σ-types

Σ-types, also known as dependent sums or dependent pairs, are pairs in which the type of the second component depends on the value of the first component.

More generally, any n-tuple or record type is a Σ-type if the types of some of its components (fields) depend on the values of its other components (fields).

The mathematical notation for a dependent pair type is a:AF(a), while the Haskell notation we propose is some (a :: A) | F a.

Dependencies

Two unsatisfied prerequisites or remaining subtasks:

  • Dependent Core language
  • Existential quantification

Dependent Core language

formalism and implementation

As part of its compilation pipeline, GHC translates all Haskell programs to an internal language called Core.

To support dependent types in Haskell, we have two options: encode them using existing Core features or extend Core with dependent types too.

The Core language is the central part of the GHC pipeline that sits between the frontend (parser, renamer, type checker, desugarer) and the backend (STG, Cmm, code generator). The vast majority of optimizations that GHC performs are implemented as Core-to-Core transformations.

Core is a typed language whose type system is separate from that of Haskell. Its type checker is called Core Lint and is used as a sanity test for other parts of the compiler.

The current version of Core is based on System FC, a polymorphic lambda calculus with coercions. It has no support for dependent types, and known encodings based on singleton types are inefficient.

Changes to Core are rare and are not taken lightly. Developing a new formalism for Core that can accommodate both linear types and dependent types is a subject of ongoing research.

Universal promotion

promote all terms

The style of dependently-typed programming that we envision for Haskell assumes seamless integration of and significant code reuse across term- and type-level definitions.

Promotion is the idea of making term-level definitions available for use in type-level contexts, and our goal is to maximize the set of data types and functions that can be promoted.

With today's DataKinds, most ADTs can be promoted. For example, the boolean data constructor True can be directly used at the type level: there is no need to introduce a separate kind KBool for type-level booleans. We get to reuse the plain old Bool.

However, when we look beyond simple ADTs, promotion is often not available. Problematic examples include function types, unboxed types, constraints, and data families. In the singletons library, this issue manifests in the form of the Demote mapping, which does not fully solve the problem and introduces a great deal of complexity that we'd like to avoid.

Dependencies

Five unsatisfied prerequisites or remaining subtasks:

  • Promote literals
  • Promote unboxed types
  • Promote classes
  • Function promotion
  • Data family promotion

Promote literals

numeric, char, string

Overloaded literals that behave as closely as possible to the ones at the term level.

Dependencies

One unsatisfied prerequisite or remaining subtask:

  • Constrained type families
Completed

Promote Char

and character literals

Promote character literals 'x'.

References

  • Proposal #387 The Char kind
  • Issue #11342 Character kind
  • Issue #19535 CharToNat and NatToChar type families
  • Issue #22488 Pretty-printing of promotion quotes and char literals
  • Commit 7f3524e The Char kind
    • Commit f99407e type level characters support for haddock
  • Commit 3028541 Built-in type families: CharToNat, NatToChar
    • Commit d44e42a Add missing axiom exports for CharToNat/NatToChar
  • Commit 178c1fd Check if the SDoc starts with a single quote
Completed

Promote Natural

unify it with Nat

Promote numeric literals 42.

References

  • Proposal #364 Unify Nat and Natural
  • Commit 8f4f579 Unification of Nat and Naturals
    • Commit 34762e8 Changed tests due to unification of Nat and Natural

Promote unboxed types

RuntimeRep ≠ LiftedRep

At the moment, any data type that internally makes use of unboxed types cannot be promoted. This includes Integer, Text, ByteArray, and so on. The only exceptions are Char and Natural that have ad-hoc support in the compiler.

References

  • Issue #14180 Permit levity polymorphism in kinds

Dependencies

One unsatisfied prerequisite or remaining subtask:

  • Homogeneous equality

Homogeneous equality

instead of heterogeneous

Promote classes

constraints and dictionaries

Promote class methods for use at the type level.

Dependencies

Two unsatisfied prerequisites or remaining subtasks:

  • Function promotion
  • Constrained type families

Function promotion

promote term-level functions

Promote term-level functions for use at the type level.

References

  • Commit 300bcc1 Parse qualified terms in type signatures

Dependencies

Five unsatisfied prerequisites or remaining subtasks:

  • Closed term evaluator
  • Open term evaluator
  • Type-level lambdas
  • Dependency analysis
  • Unsaturated type families

Data family promotion

promote data families

Lift the restriction that data families cannot be promoted.

References

  • Proposal Discussion #456 Promotion of data families

Closed term evaluator

using bytecode or native code

Closed terms are terms that contain no free variables. Consider:

v :: Vec (length [1,2,3]) Bool v = True :. False :. True :. VNil

To typecheck this declaration, we need to reduce length [1,2,3] to 3.

GHC is already capable of evaluating closed terms at compile time by means of TemplateHaskell, so we only need to make this functionality available without explicit conversions to and from TH AST.

References

  • Proposal PR #509 Type functions

Open term evaluator

normalization by evaluation

Open terms are terms that contain free variables. Consider:

x :: forall a. Num a => id a x = 42

To typecheck this declaration, we need to reduce id a to a without instantiating a to a concrete type.

This requires an evaluator that can deal with free variables or other unknowns.

Type-level lambdas

first-class functions in types

Support anonymous functions \a b -> e at the type level.

Dependencies

Two unsatisfied prerequisites or remaining subtasks:

  • Dependent Core language
  • Open term evaluator

Clean up the language

preparations for dependent types

To ensure we are building on a solid foundation, we want to polish the existing type-level programming features in Haskell before we move on to dependent types.

This is a somewhat open-ended goal. The main criterion for including a task or a feature here is whether it would simplify the current practice of singletons-based programming.

We would also like to offer typing rules and a reference type checker implementation for modern Haskell, including all its type system extensions. See Typing rules for Haskell.

Dependencies

Six unsatisfied prerequisites or remaining subtasks:

  • Dependency analysis
  • Existential quantification
  • Unsaturated type families
  • Constrained type families
  • Deprecate CUSKs
  • Namespace management
Accepted

Dependency analysis

of top-level declarations

Declarations in a Haskell module may appear in any order, so the compiler needs to perform dependency analysis and arrange them in topological order before type checking.

At the moment, GHC partitions the module into type declarations and term declarations, and all type declarations are processed first. This will not work if our goal is to allow mixing types and terms freely.

Furthermore, the existing algorithm has trouble with type family instances.

We need to fix the current bugs in dependency analysis and then extend it to handle type declarations that depend on terms.

Existential quantification

first-class exists quantifier

Add first-class existential quantification exists a. C a /\ a to the language.

Accepted

Unsaturated type families

partial application in types

At the moment, GHC does not support partial application of type families or type synonyms. Type families must be fully applied (saturated) at use sites, restricting users to first-order programming.

Consider this definition of the map function for use at the type level:

type Map :: (a -> b) -> List a -> List b type family Map f xs where Map _ [] = [] Map f (x:xs) = f x : Map f xs

It is not possible to pass another type family as the first argument to Map because that would require partial (unsaturated) application of the function argument.

The singletons package offers a workaround in the form of defunctionalization. Direct support for unsaturated type families would eliminate the need for that workaround.

The key idea is to annotate the function arrow with matchability, so that generative and non-generative type constructors are assigned different kinds.

Current status

  • A proof-of-concept implementation is available in a branch.
  • The proposal needs to be amended to use the syntax of modifiers.

Constrained type families

constraints in kinds

Add class constraints to the kinds of associated type families.

Accepted

Modifiers syntax

generalized modifiers

One of the never-ending challenges of language design is to come up with user-facing syntax for new features. To ease this problem, we proposed modifiers: generic, multi-purpose syntax of the form %mod.

Modifiers can be attached to arrows, types, expressions, patterns, record fields, data constructors, type declarations, and so on.

For example, LinearTypes use the syntax of modifiers to specify multiplicity:

f :: (a -> b) %1 -> a -> b -- %1 marks a linear arrow let %1 y = g x -- %1 marks a linear let-binding

We intend to use modifiers for matchability annotations of unsaturated type families, as well as for other annotations that turn out necessary in the context of our work on dependent types.

Current status

In development, see the tracking issue for details.

References

  • Proposal #370 Syntax for Modifiers: a generalization of linear-types syntax
  • Issue #18459 Linear types syntax: multiplicity parametric arrow
  • Issue #22624 Modifiers syntax implementation tracking issue
  • Commit 5830a12 New linear types syntax: a %p -> b
    • Commit bca4d36 Improve error messages for (a %m) without LinearTypes
    • Commit a8018c1 Fix pretty-printing of the mult-polymorphic arrow
Completed

Standalone kind signatures

replacement for CUSKs

Standalone kind signatures make it possible to fully specify the kind of a type constructor:

type T :: (k -> Type) -> k -> Type -- signature data T m a = MkT (m a) (T Maybe (m a)) -- declaration

A standalone kind signature can accompany a data, newtype, type, class, type family, or data family declaration.

The kind checker enters either checking mode or inference mode depending on the presence or absence of a standalone kind signature. Polymorphic recursion is only supported in checking mode.

This feature is described in more detail in section 6.4.13.8. Standalone kind signatures and polymorphic recursion of the User's Guide.

Standalone kind signatures are modeled after term-level type signatures. They are the recommended replacement for CUSKs.

Current status

Done, except for known issues:

  • Issue #16754 Can't use multiple names in a standalone kind signature
  • Issue #17432 Wildcards in standalone kind signatures
  • Issue #25656 Scoped kind variables in standalone kind signatures

References

  • Proposal #54 Standalone kind signatures
  • Issue #16635 Scoped kind variables are broken
  • Issue #16794 Implement standalone kind signatures
  • Issue #16976 TemplateHaskell feature request: reifyType/reifyKind
  • Commit 0b5eede Standalone kind signatures
  • Commit 78cd113 Report scoped kind variables at the type-checking phase
  • Commit 00d9d28 TemplateHaskell: reifyType
Accepted

Deprecate CUSKs

complete user-supplied kinds

CUSKs (complete user-supplied kinds) are a syntactic heuristic to determine whether the kind checker should operate in checking mode or inference mode. The exact rules are laid out in section 6.4.13.7. Complete user-supplied kind signatures and polymorphic recursion of the User's Guide.

The main use case for CUSKs is to enable polymorphic recursion in type, data, and class declarations, as polymorphic recursion cannot be inferred.

Like any other heuristic, CUSKs can be fiddly. Standalone kind signatures offer a much better alternative: instead of a complicated set of rules, the choice between checking and inference is determined by the presence or absence of a signature.

The design of standalone kind signatures mirrors that of type signatures for term-level declarations, so we would like to deprecate CUSKs in their favor.

Current status

Impact analysis is needed, and a transitional warning is desirable before deprecation takes place. See MR !1602 Disable CUSKs by default.

References

  • Proposal #54 Standalone kind signatures
  • Issue #12928 Too easy to trigger CUSK condition using TH
  • Commit 1279428 Quantify unfixed kind variables in CUSKs
    • Commit c72c369 Add a minimized regression test for #12928
  • Commit a5fdd18 Guard CUSKs behind a language pragma
  • Commit bdba6ac Do not rely on CUSKs in base
  • Commit 679bbc9 testsuite: Do not require CUSKs
Completed

Invisible type arguments

applications and abstractions

One of the design aspects of dependent types that we envision for Haskell is that every quantifier must come in two variants: visible and invisible.

For example, universal quantification over an erased type is possible with either the invisible quantifier forall a. or the visible quantifier forall a ->.

Invisible quantification relies primarily on type inference to instantiate type variables behind the scenes. However, it may be occasionally useful to bind or supply an invisible type argument explicitly, and to do that, one must use a visibility override, spelled @ in the Haskell syntax.

At use sites, this is done with the TypeApplications extension, and with TypeAbstractions at binding sites.

To implement Π-types, we also plan to introduce two quantifiers: the invisible quantifier foreach a. and the visible quantifier foreach a ->. We expect to fully reuse the existing machinery to deal with visibility overrides.

References

  • Issue #23510 Implement the -Wimplicit-rhs-quantification warning
  • Commit bc12577 Introduce the TypeAbstractions language flag
  • Commit a71b60e Implement the -Wimplicit-rhs-quantification warning
  • Commit 2b1faea docs: Update info on TypeAbstractions
Completed

Invisible binders in types

@k-binders in type declarations

The type abstraction syntax can be used to bind type variables in data, newtype, type, class, type family, and data family declarations:

type C :: forall k. k -> Constraint class C @k a where ... -- @k binds the kind variable

Invisible binders also provide a mechanism to control the arity of type synonyms and type families.

Section 6.4.17.3. Invisible Binders in Type Declarations of the User's Guide describes this feature in more detail.

Current status

Feature preview is available since GHC 9.8, and the remaining work is tracked by the following tickets:

  • Issue #23500 GHC Proposal 425: Meta-ticket
  • Issue #23502 Kind inference for invisible binders in type declarations
  • Issue #23515 Type/data instances: require that the instantiation is determined by the LHS alone

References

  • Proposal #425 Invisible binders in type declarations
  • Issue #22560 Invisible binders in type declarations
  • Issue #23501 Wildcard binders in type declarations
  • Issue #23512 Type/data instances: require that variables on the RHS are mentioned on the LHS
  • Issue #23514 Remove arity inference in type declarations
  • Issue #24459 GHCi :info uses an outdated mechanism to show type synonym arity
  • Issue #24470 Implicit RHS quantification in type synonyms crashes GHC
  • Commit 4aea0a7 Invisible binders in type declarations
  • Commit 5745dbd Wildcard binders in type declarations
  • Commit 800aad7 Type/data instances: require that variables on the RHS are mentioned on the LHS
  • Commit e89aa07 Remove arity inference in type declarations
    • Commit a0c27ce Add standalone kind signatures for Code and TExp
    • Commit cf735db Add Note about why we need forall in Code to be on the right
  • Commit 7ea971d Fix compiler crash caused by implicit RHS quantification in type synonyms
  • Commit 0febf3a Add support for invisible binders in type declarations
    • Commit 5d267d4 Refactor: FreshOrReuse instead of addTyClTyVarBinds
  • Commit 9c53489 Update GHCi :info type declaration printing
Completed

Invisible binders in functions

@a-binders in lambdas

The type abstraction syntax can be used in lambdas and function left-hand sides to bring type variables into scope in the function body:

r = higherRank (\ @a x -> ...) -- @a binds a rank-2 type

Invisible binders in functions are the modern and more flexible alternative to ScopedTypeVariables, capable of handling higher-rank scenarios.

Section 6.4.17.2. Type Abstractions in Functions of the User's Guide describes this feature in more detail.

Current status

Feature preview is available since GHC 9.10, and the remaining work is tracked by the following tickets:

  • Issue #24722 Typecheck TypeAbstractions lambda expressions without explicit type ascriptions
  • Issue #25660 Type inference for type abstractions in functions

References

  • Proposal #155 Binding type variables in lambda-expressions
  • Proposal #448 Modern Scoped Type Variables
  • Issue #17594 Implement the Binding type variables in lambda-expressions proposal
  • Issue #24557 Support invisible type patterns in Template Haskell quotes (e.g., [t| @a |])
  • Commit f5d3e03 Lazy skolemisation for @a-binders
  • Commit 0dbd729 Parser, renamer, type checker for @a-binders
  • Commit 36a75b8 Change how invisible patterns represented in haskell syntax and TH AST
Completed

Invisible binders in constructors

@a-binders in constructor patterns

The type abstraction syntax can be used in patterns to bind existential type variables associated with a GADT data constructor:

data G where { MkG :: forall e. e -> e -> G } f (MkG @e a b) = ... -- @e binds the existential

Section 6.4.17.1. Type Abstractions in Patterns of the User's Guide describes this feature in more detail.

References

  • Proposal #126 Type Applications in Patterns
  • Proposal #448 Modern Scoped Type Variables
  • Issue #18986 Type applications in patterns fails in cases involving polymorphic/higher-order kinds
  • Issue #22478 Modern scoped type variables: type arguments in constructor patterns
  • Issue #24154 Type applications in constructor patterns will require the TypeAbstractions extension starting from GHC 9.12
  • Commit c696bb2 Implement type applications in patterns
  • Commit 2afbddb Type patterns
  • Commit 3ede659 Add name for -Wdeprecated-type-abstractions
Completed

Visible type applications

@t-applications in terms

Most of the time GHC is capable of inferring the instantiations of invisible type variables. For example, id True internally expands to id @Bool True.

However, there are also cases when the programmer might want to visibly supply a type argument to resolve an ambiguity. Consider show . read, where it is not clear what type should be used for the intermediate representation.

With the TypeApplications extension, it is possible to write f @t to instantiate type variables at use sites.

Section 6.4.16. Visible type application of the User's Guide describes this feature in more detail.

Currently this syntax works with polymorphic functions of type forall a. t, and we intend to reuse the same mechanism to visibly supply the arguments of dependent functions of type foreach a. t. Note the dot that denotes that the argument is normally invisible, inferred.

Completed

Visible kind applications

@k-applications in types

The original implementation of the TypeApplications extension only allowed to supply type arguments at the term level:

x = Nothing @Bool

It has been later generalized to allow supplying kind arguments at the type level:

type X = Nothing @Bool

In this example, the inferred kind of X is Maybe Bool.

References

  • Proposal #80 Type-level type applications
  • Issue #12045 Visible kind application
  • Commit 17bd163 Visible kind application
Accepted

Syntactic unification

type syntax in terms

The syntactic separation between terms and types comes apart at the seams when we allow data constructors in type-level contexts or unadorned types in term-level contexts:

a :: G (Just 10) -- terms in types (DataKinds) b = f (Int -> Bool) -- types in terms (RequiredTypeArguments)

To better adapt to the new demands of language design, we aim to fully unify the syntax of terms and types.

The goal is to use a single internal representation for terms and types in the compiler frontend (AST, parser, renamer, type checker) and to reuse as much of the grammar and name resolution logic as possible.

Current status

Type syntax is available in expressions since GHC 9.12. However:

  • in patterns, type syntax is not yet available
  • internal representations have not been unified
  • grammars have not been unified

References

  • Issue #18740 Fall back to types when looking up data constructors
  • Issue #19978 When name resolution falls back to the type-level, term-level alternatives should still be suggested
  • Issue #24159 The types-in-terms syntax (forall, ->, =>)
  • Issue #24226 Function type mistaken for ViewPatterns in T2T VDQ
  • Issue #24570 RequiredTypeArguments: unexpected parse error for infix type
  • Issue #24572 RequiredTypeArguments: application of infix type fails when combined with TemplateHaskell
  • Issue #25121 Unify HsExpr and HsType
  • Commit e61f6e3 Expression/command ambiguity resolution
  • Commit 52fc271 Pattern/expression ambiguity resolution
    • Commit 1959bad Stop misusing EWildPat in pattern match coverage checking
  • Commit 8b2f70a Type syntax in expressions
    • Commit d59faaf docs: Update info on RequiredTypeArguments
  • Commit 990ea99 Fall back to types when looking up data constructors
    • Commit 0bb7883 Suggest similar names when reporting types in terms
  • Commit da2a10c Type operators in promoteOccName
Accepted

Namespace management

to resolve ambiguities

The use of identical names for type-level and term-level entities is called punning. Haskell makes heavy use of punning in its built-in syntax and common types.

However, there are various contexts in which an occurrence of a name may refer either to the type namespace or the data namespace, so disambiguation may be necessary:

  • Import and export lists
  • Fixity declarations
  • WARNING, DEPRECATED, and ANN pragmas
  • Types, when using the DataKinds extension
  • Terms, when using the RequiredTypeArguments extension
  • TemplateHaskell name quotes

The simplest way to avoid namespace ambiguity is to avoid punning entirely. However, given the pervasive use of punning in the Haskell ecosystem, even users who wish to avoid punning will inevitably end up importing modules which make use of it. Thus we need mechanisms to disambiguate the namespace on import or at use sites.

References

  • Proposal #65 Require namespacing fixity declarations for type names and WARNING/DEPRECATED pragmas
  • Issue #14032 Can't splice TH quote with infix declaration for name in two different namespaces
  • Issue #20531 Encourage unticked promoted constructors
  • Issue #24396 Namespacing for WARNING/DEPRECATED pragmas
  • Commit 13d627b Print unticked promoted data constructors
  • Commit 151dda4 Namespacing for WARNING/DEPRECATED pragmas
    • Commit ce90f12 Hide WARNING/DEPRECATED namespacing under -XExplicitNamespaces
  • Commit 77629e7 Namespacing for fixity signatures
    • Commit 778e1db Namespace specifiers for fixity signatures (haddock)

Dependencies

Two unsatisfied prerequisites or remaining subtasks:

  • Pun warnings
  • Namespace-specified imports

Pun warnings

warn on puns and pun bindings

We propose to introduce two new warnings, -Wpuns and -Wpun-bindings, to facilitate writing code as if Haskell had a single namespace.

By making use of those warnings, library authors could ensure their APIs do not require explicit namespace disambiguation to use, whereas users would be able to see where and when implicit namespace disambiguation takes place.

References

  • Proposal PR #270 Support pun-free code
Accepted

Namespace-specified imports

filter imported names

Namespace-specified imports extend ExplicitNamespaces to allow data and type keywords to be used as part of import or export lists, potentially with a .. wildcard:

import qualified Data.Proxy as T (type ..) import qualified Data.Proxy as D (data ..)

The namespace specifier filters imported names, keeping only the ones from the requested namespace.

Current status

The proposal has been accepted and awaits implementation.

References

  • Proposal #581 Namespace-specified imports
  • Issue #23781 Implement namespace-specified imports and fix ExplicitNamespaces
Completed

No list or tuple puns

remove ambiguous built-in syntax

The built-in list syntax [a] could denote either a list of one element or the type of a list. [] could mean either an empty list or the list type constructor. Likewise, (a, b) could be either a tuple type or the tuple itself.

This form of overloading, called punning, is usually resolved based on context, i.e. whether we are in term syntax or type syntax. When we start mixing types and terms (e.g. with DataKinds or RequiredTypeArguments), it becomes a problem.

We proposed and implemented the (No)ListTuplePuns extension. List and tuple types are now available under alternative names List, Unit, Tuple2, Tuple3, and so on.

Constraint tuples and unboxed tuples are also available under alphanumeric names CUnit, CTuple2, CTuple3, Unit#, Tuple2#, Tuple3#, and so on.

Current status

Done, except for the Tuple and Constraints type families that currently cannot be defined due to type inference issues.

References

  • Proposal #475 Non-punning list and tuple syntax
  • Issue #21294 Non-punning list and tuple syntax
  • Issue #22785 'MkSolo sometimes printed incorrectly in diagnostics
  • Issue #22839 badOrigBinding does outdated assumption
  • Issue #23368 base-4.18 haddocks rendering is inconsistent: Eq [a], but Eq1 List
  • Issue #24291 Missing changelog for (at least) tuples
  • Issue #24673 Rename unboxed tuple data constructor from (# #) to MkSolo#
  • Issue #24702 isBuiltInOcc_maybe must not consider Tuple-names as builtin
  • Commit d91d00f Introduce ListTuplePuns extension
    • Commit 94da936 Fix tuple puns renaming
  • Commit 2463df2 Rename Solo[constructor] to MkSolo
    • Commit bf3dcdd Fix pretty-printing of Solo and MkSolo
    • Commit 14b5982 Fix printing of promoted MkSolo datacon
  • Commit 3b51995 Rename Solo# data constructor to MkSolo#
  • Commit 02279a9 Rename [] to List
    • Commit 6b18829 Rename [] to List (haddock)
    • Commit 2648c09 Replace errors from badOrigBinding with new one
  • Commit a13affc Rename () into Unit, (,,...,,) into Tuple<n>
    • Commit 9e0fefd Rename () to Unit, Rename (,,...,,) to Tuple<n> (haddock)
    • Commit 69abc78 Add changelog entry for renaming tuples from (,,...,,) to Tuple<n>
    • Commit 7f13acb List and Tuple<n>: update documentation
  • Commit 457341f Remove fake exports for (~), List, and Tuple<n>
  • Commit 1b27e15 Check for puns (haddock)
Completed

Visible forall

in types of terms

Visible dependent quantification forall a -> t allows defining functions that take type arguments that are syntactically indistinguishable from term arguments:

printf "pkg: %s-%d.%d.%d.%d\n" "typelits-printf" 0 3 0 0

In this example, the formatting string is a required type argument passed and processed at compile time. See section 6.4.18. Required type arguments of the User's Guide for a comprehensive overview of this feature.

The type forall a -> t differs from a Π-type in one important way: the type argument is erased. That is, a required type argument does not exist at runtime and does not support dependent pattern-matching.

By implementing RequiredTypeArguments first, we have been able to tackle many challenges related to parsing and name resolution, so that by the time we get to Π-types, we will not get sidetracked by the minutiae of syntax.

Concrete results include the specification of a resolved syntax tree, the t2t-transformation, and types-in-terms.

Current status

Feature preview is available since GHC 9.10, and the remaining work is tracked by the following tickets:

  • Issue #23704 Visible forall in pattern synonyms
  • Issue #24153 Reject puns in T2T
  • Issue #24231 Error message hints: use the env instead of the namespace
  • Issue #24797 No -Wbadly-staged-types warning for required type argument
  • Issue #25004 Panic with RequiredTypeArguments and EmptyCase
  • Issue #25099 Haddock's support for VDQ looks incomplete
  • Issue #25127 Visible forall in GADTs
  • Issue #25352 Visible forall in class methods
  • Issue #25648 Partial type signature solution too rigid when using required type arguments

References

  • Proposal #281 Visible forall in types of terms, and types in terms
  • Issue #18522 Bugs in debug_ppr_ty and ppr_ty
  • Issue #22326 Visible forall in types of terms, Part 1
  • Issue #23717 Visible forall in types of terms, Part 2
  • Issue #23738 T2T (term-to-type) transformation in expressions
  • Issue #23739 T2T (term-to-type) transformation in patterns
  • Issue #24318 Error message with RequiredTypeArguments
  • Issue #24571 Pattern to type transformation doesn't work with TH splices
  • Commit 33b6850 Visible forall in types of terms: Part 1
    • Commit 9cd9efb Rephrase error message to say visible arguments
  • Commit 0dfb1fa T2T in Expressions
    • Commit 1c9496e docs: update information on RequiredTypeArguments
  • Commit 0f0c53a T2T in Patterns
    • Commit 2c0f8dd Improve pattern to type pattern transformation
    • Commit 6fafc51 Fix TH handling in pat_to_type_pat function
    • Commit 2e59285 Drop outdated comment on TcRnIllformedTypePattern
  • Commit 0ddb438 Fix visible forall in ppr_ty
  • Commit 826d07d Fix debug_ppr_ty ForAllTy

Dependencies

Two loose ends or possible improvements:

  • Syntactic unification
  • Nested quantification in GADTs
Completed

Visibility coercions

in the Core language

In order to implement required type arguments, we needed to settle the question of whether forall a -> t and forall a. t are equal types in Core.

After a long discussion and playing around with ideas like visibility subsumption, we decided on making those types distinct but related by a coercion.

The Core language has been extended with visibility coercions, which unblocked the work on required type arguments.

References

  • Proposal Issue #558 Apartness of visible and invisible forall
  • Issue #18863 Visibility mismatch between data declaration and kind signature, accepted!
  • Issue #22762 eqType, tcEqType, and foralls
  • Commit cf86f3e Equality of forall-types is visibility aware
  • Commit 93647b5 testsuite: Add forall visibility test cases
  • Commit 469ff08 Check visibility of nested foralls in can_eq_nc
Accepted

Nested quantification in GADTs

interleave foralls in constructors

At the moment, type variables in GADTs are subject to two restrictions:

  1. must be bound by a single forall at the front
  2. must be invisible

We propose to lift both restrictions to enable library authors to design better APIs.

Current status

The proposal has been accepted and awaits implementation.

References

  • Proposal #402 Stable GADT constructor syntax
  • Issue #18389 Allow nested foralls and contexts in prefix GADT constructors
  • Issue #25127 Visible forall in GADTs
  • Commit 686e06c Grammar for types and data/newtype constructors
Completed

Embed types

into expressions

To allow resolving namespace-related conflicts, we introduced the type t syntax in patterns and expressions. The new syntax is guarded behind ExplicitNamespaces and allows embedding types as subexpressions:

idv (type a) (x :: a) = x -- `type t` pattern n = idv (type Int) 42 -- `type t` expression

This is only useful to disambiguate namespaces in required type arguments. We recommend omitting type whenever possible.

References

  • Commit 33b6850 Visible forall in types of terms: Part 1
Completed

Term variable capture

mention term variables in types

Our long-term goal is to allow freely mixing terms and types, including the ability to use term-level functions and variables in types:

fn x = ... where g :: x -> x -- `x` used in a type signature g = ...

Term variable capture is going to become especially useful in combination with function promotion and dependent pattern-matching. In the short term, we can use it to bind required type arguments.

Prior to our work on GHC, the x variable bound in the term namespace could never be mentioned in a type signature.

We proposed and implemented new name resolution rules that allow term variable capture, currently guarded behind the RequiredTypeArguments extension.

Current status

Done. Library authors are kindly asked to ensure their code does not trigger the -Wterm-variable-capture warning.

References

  • Issue #23434 -Wterm-variable-capture fires where it should not
  • Issue #23740 Term variable capture and implicit quantification
  • Commit b2857df Added a new warning about compatibility with RequiredTypeArguments
    • Commit b84a290 Fix -Wterm-variable-capture scope
  • Commit d1bf25c Term variable capture
Completed

No star kind syntax

resolve conflict with operators

The * notation for the kind of proper types, i.e. types that classify terms, has traditionally been used in kind signatures such as Int :: * or Maybe :: * -> *.

Unfortunately, as types and kinds have been merged, this notation began to conflict with type operators: a * b can be read as either a (*) b or (*) a b. As a temporary workaround, we introduced the StarIsType extension to control this.

The problem becomes more pressing when we attempt to unify terms and types, as * is commonly used to denote multiplication. We had to decide on a single meaning for the star syntax, and multiplication is a clear winner.

Current status

We are nearing the end of an 8-year-long migration period. Library authors are advised to switch from * to Type.

References

  • Proposal #83 Embrace Type :: Type
  • Proposal #143 Remove the * kind syntax
  • Issue #20627 The Type kind is printed without accounting for scope
  • Issue #22759 Enable -Wstar-is-type by default in 9.6
  • Commit d650729 Embrace -XTypeInType, add -XStarIsType
    • Commit 96ab138 Handle -XStarIsType
    • Commit 07083fc Add -Wstar-is-type to the User's Guide
  • Commit 65c186f Do not imply NoStarIsType by TypeOperators/TypeInType
  • Commit 3354c68 Pretty-printing of the * kind
    • Commit 70dd0e4 Parenthesize the * kind in TH.Ppr
  • Commit 3d7e3d9 Print the Type kind qualified when ambiguous
  • Commit 5b2388b Include -fwarn-star-is-type in -Wcompat
  • Commit e9c0537 Enable -Wstar-is-type by default
  • Commit 9ce9ea5 Deprecate TypeInType extension
Completed

The forall keyword

at the term level

In the past, forall used to be a keyword under two conditions:

  1. the ExplicitForAll extension is enabled
  2. the occurrence is in type syntax

The first condition has been dropped to improve error messages, and the second condition is at odds with unification of type and term syntax. As a result, we ended up making foralla proper unconditional keyword.

To soften the impact of this breaking change, we implemented a transitional warning -Wforall-identifier, and also contacted maintainers of all affected packages.

Thanks to this change, we have been able to extend RequiredTypeArguments with direct support for forall-types in argument positions.

References

  • Proposal #193 Make forall a keyword
  • Proposal #281 Visible forall in types of terms, and types in terms
  • Issue #20609 Implement -Wforall-identifier
  • Issue #23719 Make forall a keyword
  • Proposal Discussion #440 Impact on making forall a keyword
  • Commit d9e4c59 Make forall a keyword
  • Commit 887454d forall always a keyword, plus the dot type operator
  • Commit dfc4093 Implement -Wforall-identifier
  • Commit acf23e6 Do not use forall as an identifier (haddock)
Completed

The tilde operator

for equality constraints

One might be surprised to learn that equality constraints a ~ b used to be implemented as built-in syntax rather than a straightforward application of the type-level operator (~).

In fact, (~) was not a syntactically valid operator at all and was rejected in terms:

(a ~ b) = ... -- syntax error

Building upon our whitespace-sensitive operator parsing framework, we reimplemented equality constraints as infix applications of the tilde operator, exported from Data.Type.Equality.

This makes the syntax of types and terms more uniform and simplifies the language, but it is also a breaking change, as (~) is no longer magically in scope.

We are following the usual procedure for language changes: first a proposal, then transitional warnings -Wtype-equality-out-of-scope and -Wtype-equality-requires-operators, and now we are in the waiting period before we can remove the compatibility fallbacks.

References

  • Proposal #229 Whitespace-sensitive operator parsing
  • Proposal #371 Export (~) from Data.Type.Equality
  • Issue #10056 Inconsistent precedence of ~
  • Issue #12446 Doesn't suggest TypeApplications when ~ used prefix
  • Issue #18252 What fixity does ~ has?
  • Issue #18862 Export (~) from Data.Type.Equality
  • Issue #23748 Binding (~) or (@) is rejected in TH splices
  • Commit ab61830 Export (~) from Data.Type.Equality
  • Commit 3c94c81 Added explicit fixity to (~)
  • Commit b882195 Link to (~) (haddock)
  • Commit e204431 Handle the (~) type operator in tyconsym
  • Commit 46fd8ce Fix (~) and (@) infix operators in TH splices
Completed

The dot type operator

for function composition

Prior to our work, the function composition operator (.) could not be defined at the type level:

type (f . g) x = f (g x) -- syntax error

We extended the syntax of TypeOperators to allow the dot operator in types, thereby bringing the syntax of types and terms closer together.

References

  • Proposal #173 The dot type operator
  • Issue #16339 Cannot put (.) or (!) type operators into an export list
  • Issue #19521 Precedence of record dot
  • Commit 887454d forall always a keyword, plus the dot type operator
  • Commit 20eca48 Refactor: simplify lexing of the dot
  • Commit 92d9842 Fix record dot precedence
  • Commit 2f4af71 Dot/bang operators in export lists
Completed

Whitespace-sensitive operators

prefix vs infix occurrences

To facilitate unification of term- and type-level parsers, we had to find a way to minimize operator-related discrepancies in the syntax. Of particular interest are (~), (!), (@), (-), (.), ($), and ($$), all of which can also act as special syntax depending on enabled extensions.

Our solution is to use surrounding whitespace to classify each operator occurrence into one out of four categories:

a ! bloose infix
a!btight infix
a !bprefix
a! bsuffix

Depending the surrounding whitespace, we can introduce special parsing rules for individual operators. For example, ! could be used either as an ordinary infix operator a ! b or as a bang-pattern f !x.

Within this framework of whitespace-sensitive operator parsing, we have been able to reconcile type applications with as-patterns, laziness annotations with equality constraints, bang-patterns with infix operators, and so on.

Current status

Done, except for one known issue:

  • Issue #19372 -Woperator-whitespace ignores (*), (.), and (-)

References

  • Proposal #229 Whitespace-sensitive operator parsing
  • Proposal #344 Negative Literals Improved
  • Issue #1087 bang patterns with infix ops
  • Issue #12862 Operator (!) causes weird pretty printing and parsing
  • Issue #15457 (~) and (!) are parsed inconsistently in types
  • Issue #16619 Bang pattern hint misdiagnosis with TemplateHaskell
  • Issue #17162 Weird error spans in patterns
  • Issue #18022 NegativeLiterals breaks an otherwise well-typed program
  • Issue #18834 Implement -Woperator-whitespace
  • Issue #19371 Warn on prefix/suffix operators
  • Issue #19838 Can't mix infix operator with prefix - using -XLexicalNegation
  • Issue #22201 Lexer: avoid predicates in varsym rules
  • Commit 3e7569b Whitespace forward compatibility for proposal #229
  • Commit bd78985 Parse the (!) type operator and allow type operators in existential context
    • Commit af300a4 Reject illegal quote mark in data con declarations
  • Commit 8168b42 Whitespace-sensitive bang patterns
    • Commit e2c4a94 Parser regression tests, close #12862 #12446
  • Commit b5b3e34 Implement -Woperator-whitespace
    • Commit 59fe128 Fix -Woperator-whitespace for consym
  • Commit cbb6b62 Implement -XLexicalNegation
    • Commit 3f6208d Handle LexicalNegation's ITprefixminus
    • Commit 3f60a7e Do not reassociate lexical negation
  • Commit aee45d9 Improve NegativeLiterals
  • Commit 02e2897 Remove spaces around @-patterns (haddock)
  • Commit ead3f83 warnSpaceAfterBang only in patterns
  • Commit 7574659 Lexer: define varsym without predicates
    • Commit 7803716 Lexer: pass updated buffer to actions
Completed

Unify type and kind variables

consistent quantification rules

The original implementation of kind polymorphism (PolyKinds) offered no way to explicitly bring a kind variable into scope. Instead, users just mentioned kin an appropriate context and the kind variable came into being.

Because of this legacy, GHC continued to treat kind variables differently than type variables when it came to name resolution. In particular, kind variables were not subject to the forall-or-nothing rule and had unusal interactions with ScopedTypeVariables.

This meant that, for reasons of backwards compatibility, GHC had to maintain a distinction between kind and type variables, even though this distinction was superficial: it had no effect outside implicit quantification.

The discrepancy was eliminated by following the usual procedure: first a proposal to get the changes approved by the committee, then a compatibility warning to help users update their code, and finally a breaking change to simplify the language.

References

  • Proposal #103 Treat kind variables and type variables identically in forall
  • Issue #14548 Lexically scoped kind variables
  • Issue #15264 Warn about implicit kind variables with -Wcompat
  • Issue #16315 Pattern synonym implicit existential quantification
  • Issue #16334 Named wildcards in kinds
  • Commit 8df2447 Warn about implicit kind variables with -Wcompat
  • Commit 5bc195b Treat kind/type variables identically, demolish FKTV
    • Commit 396e01b Add a regression test for #14548
Completed

Unify types and kinds

with the Type :: Type axiom

GHC has been accumulating DT-adjacent features for a long time now. For example, GADTs date back as far as GHC 6.4 (March 2005). However, to keep the scope of this page within reasonable limits, we must choose a more recent cut-off point.

The introduction of the Type :: Type axiom in GHC 8.0 (May 2016) is a rather appropriate milestone for that purpose. This change blurred the line between types and kinds to such an extent that a single forall-quantified variable could be used both as a type variable and a kind variable in one signature.

Aside from various anomalies in the surface language, one could say that the TypeInType extension unified types and kinds in GHC and opened up the next frontier: unifying types and terms.