2.1. Version 9.6.1

The significant changes to the various parts of the compiler are listed in the following sections. See the migration guide on the GHC Wiki for specific guidance on migrating programs to this release.

The LLVM backend of this release is to be used with LLVM 10, 11, 12, 13, or 14.

2.1.1. Language

  • Record updates for GADTs and other existential datatypes are now fully supported.

    For example:

    data D b where
      MkD :: { fld1 :: a -> a, fld2 :: a -> (), fld3 :: b } -> D b
    
    foo :: D b -> D b
    foo d = d { fld1 = id, fld2 = const () }
    

    In this example, we have an existential variable a, and we update all fields whose type involves a at once, so the update is valid.

    A side-effect of this change is that GHC now rejects some record updates involving fields whose types contain type families (these record updates were previously erroneously accepted).

    Example:

    type family F a where
      F Int   = Char
      F Float = Char
    
    data T b = MkT { x :: [Int], y :: [F b] }
    
    emptyT :: forall b. T b
    emptyT = MkT [] []
    
    bar :: T Int
    bar = emptyT { x = [3] }
    

    In this example, we can’t infer the type of emptyT in bar: it could be T Int, but it could also be T Float because the type family F is not injective and T Float ~ T Int. Indeed, the following typechecks

    baz :: T Int
    baz = case ( emptyT :: T Float ) of { MkT _ y -> MkT [3] y }
    

    This means that the type of emptyT is ambiguous in the definition of bar above, and thus GHC rejects the record update:

    Couldn't match type `F b0' with `Char'
    Expected: [F Int]
      Actual: [F b0]
    NB: ‘F’ is a non-injective type family
    The type variable ‘b0’ is ambiguous
    

    To fix these issues, add a type signature to the expression that the record update is applied to (emptyT in the example above), or add an injectivity annotation to the type family in the case that the type family is in fact injective.

  • Error messages are now assigned unique error codes, of the form [GHC-12345].

  • GHC Proposal #106 has been implemented, introducing a new language extension TypeData. This extension permits type data declarations as a more fine-grained alternative to DataKinds.

  • GHC now does a better job of solving constraints in the presence of multiple matching quantified constraints. For example, if we want to solve C a b Int and we have matching quantified constraints:

    forall x y z. (Ord x, Enum y, Num z) => C x y z
    forall u v. (Enum v, Eq u) => C u v Int
    

    Then GHC will use the second quantified constraint to solve C a b Int, as it has a strictly weaker precondition.

  • GHC proposal #170 Unrestricted OverloadedLabels has been implemented. This extends the variety syntax for constructing labels under OverloadedLabels. Examples of newly allowed syntax: - Leading capital letters: #Foo equivalant to getLabel @”Foo” - Numeric characters: #1728 equivalent to getLabel @”1728” - Arbitrary strings: #”Hello, World!” equivalent to getLabel @”Hello, World!”

2.1.2. Compiler

  • The WebAssembly backend has been merged. This allows GHC to be built as a cross-compiler that targets wasm32-wasi and compiles Haskell code to self-contained WebAssembly modules that can be executed on a variety of different runtimes. There are a few caveats to be aware of:
    • To use the WebAssembly backend, one would need to follow the instructions on ghc-wasm-meta. The WebAssembly backend is not included in the GHC release bindists for the time being, nor is it supported by ghcup or stack yet.
    • The WebAssembly backend is still under active development. It’s presented in this GHC version as a technology preview, bugs and missing features are expected.
  • The TypeInType is now marked as deprecated. Its meaning has been included in PolyKinds and DataKinds.
  • The -Woperator-whitespace warning no longer ignores constructor symbols (operators starting with :).
  • The -Wstar-is-type warning is now enabled by default, continuing the implementation of GHC proposal #143.

2.1.3. GHCi

  • GHCi will now accept any file-header pragmas it finds, such as {-# OPTIONS_GHC ... #-} and {-# LANGUAGE ... #-} (see Pragmas). For example, instead of using :set to enable -Wmissing-signatures, you could instead write:

    ghci> {-# OPTIONS_GHC -Wmissing-signatures #-}
    

This can be convenient when pasting large multi-line blocks of code into GHCi.

2.1.4. Runtime system

  • The Delimited continuation primops proposal has been implemented, adding native support for first-class, delimited continuations to the RTS. For the reasons given in the proposal, no safe API to access this functionality is provided anywhere in base. Instead, the prompt# and control0# primops are intended to be consumed by library authors directly, who may wrap them a safe API that maintains the necessary invariants. See the documentation in GHC.Prim for more details.
  • The behaviour of the -M flag has been made more strict. It will now trigger a heap overflow if the total amount of memory used by the Haskell heap exceeds the limit. Previously only live blocks were taken into account. This makes it more likely to trigger promptly when the heap is highly fragmented.
  • Fixed a bug that sometimes caused live sparks to be GC’ed too early either during minor GC or major GC with workstealing disabled. See #22528.

2.1.5. base library

2.1.6. ghc-prim library

2.1.7. ghc library

  • Add Foreign.C.Types.ConstPtr was added to encode const-qualified pointer return types in foreign declarations when using CApiFFI extension.

2.1.8. ghc-heap library

2.1.8.1. Included libraries

The package database provided with this distribution also contains a number of packages other than GHC itself. See the changelogs provided with these packages for further change information.

Package Version Reason for inclusion
ghc 9.6.0.20230210 The compiler itself
Cabal-syntax 3.9.0.0 Dependency of ghc-pkg utility
Cabal 3.9.0.0 Dependency of ghc-pkg utility
Win32 2.13.3.0 Dependency of ghc library
array 0.5.4.0 Dependency of ghc library
base 4.18.0.0 Core library
binary 0.8.9.1 Dependency of ghc library
bytestring 0.11.4.0 Dependency of ghc library
containers 0.6.7 Dependency of ghc library
deepseq 1.4.8.0 Dependency of ghc library
directory 1.3.8.0 Dependency of ghc library
exceptions 0.10.7 Dependency of ghc and haskeline library
filepath 1.4.100.0 Dependency of ghc library
ghc-boot-th 9.6.0.20230210 Internal compiler library
ghc-boot 9.6.0.20230210 Internal compiler library
ghc-compact 0.1.0.0 Core library
ghc-heap 9.6.0.20230210 GHC heap-walking library
ghc-prim 0.10.0 Core library
ghci 9.6.0.20230210 The REPL interface
haskeline 0.8.2 Dependency of ghci executable
hpc 0.6.2.0 Dependency of hpc executable
integer-gmp 1.1 Core library
libiserv 9.6.0.20230210 Internal compiler library
mtl 2.3.1 Dependency of Cabal library
parsec 3.1.16.1 Dependency of Cabal library
pretty 1.1.3.6 Dependency of ghc library
process 1.6.16.0 Dependency of ghc library
stm 2.5.1.0 Dependency of haskeline library
template-haskell 2.20.0.0 Core library
terminfo 0.4.1.5 Dependency of haskeline library
text 2.0.1 Dependency of Cabal library
time 1.12.2 Dependency of ghc library
transformers 0.6.1.0 Dependency of ghc library
unix 2.8.0.0 Dependency of ghc library
xhtml 3000.2.2.1 Dependency of haddock executable