2.1. Version 9.2.1

The significant changes to the various parts of the compiler are listed in the following sections.

The LLVM backend of this release is to be used with LLVM 10 or 11.

2.1.1. Language

  • ImpredicativeTypes: Finally, polymorphic types have become first class! GHC 9.2 includes a full implementation of the Quick Look approach to type inference for impredicative types, as described in in the paper A quick look at impredicativity (Serrano et al, ICFP 2020). More information here: Impredicative polymorphism. This replaces the old (undefined, flaky) behaviour of the ImpredicativeTypes extension.
  • The first stage of the Pointer Rep Proposal has been implemented. All boxed types, both lifted and unlifted, now have representation kinds of the shape BoxedRep r. Code that references LiftedRep and UnliftedRep will need to be updated.
  • UnliftedDatatypes: The Unlifted Datatypes Proposal has been implemented. That means GHC Haskell now offers a way to define algebraic data types with strict semantics like in OCaml or Idris! The distinction to ordinary lifted data types is made in the kind system: Unlifted data types live in kind TYPE (BoxedRep Unlifted). UnliftedDatatypes allows giving data declarations such result kinds, such as in the following example with the help of StandaloneKindSignatures:

    type IntSet :: UnliftedType -- type UnliftedType = TYPE (BoxedRep Unlifted)
    data IntSet = Branch IntSet !Int IntSet | Leaf
    

    See UnliftedDatatypes for what other declarations are possible. Slight caveat: Most functions in base (including $) are not levity-polymorphic (yet) and hence won’t work with unlifted data types.

  • Kind inference for data/newtype instance declarations is slightly more restrictive than before. In particular, GHC now requires that the kind of a data family instance be fully determined by the header of the instance, without looking at the definition of the constructor.

    This means that data families that dispatched on an invisible parameter might now require this parameter to be made explicit, as in the following example:

    data family DF :: forall (r :: RuntimeRep). TYPE r
    newtype instance DF @IntRep   = MkDF2 Int#
    newtype instance DF @FloatRep = MkDF1 Float#
    

    See the user manual Kind inference for data/newtype instance declarations.

  • GHC is stricter about checking for out-of-scope type variables on the right-hand sides of associated type family instances that are not bound on the left-hand side. As a result, some programs that were accidentally accepted in previous versions of GHC will now be rejected, such as this example:

    class Funct f where
      type Codomain f
    instance Funct ('KProxy :: KProxy o) where
      type Codomain 'KProxy = NatTr (Proxy :: o -> Type)
    

    Where:

    data Proxy (a :: k) = Proxy
    data KProxy (t :: Type) = KProxy
    data NatTr (c :: o -> Type)
    

    GHC will now reject the o on the right-hand side of the Codomain instance as being out of scope, as it does not meet the requirements for being explicitly bound (as it is not mentioned on the left-hand side) nor implicitly bound (as it is not mentioned in an outermost kind signature, as required by Scoping of class parameters). This program can be repaired in a backwards-compatible way by mentioning o on the left-hand side:

    instance Funct ('KProxy :: KProxy o) where
      type Codomain ('KProxy @o) = NatTr (Proxy :: o -> Type)
      -- Alternatively,
      -- type Codomain ('KProxy :: KProxy o) = NatTr (Proxy :: o -> Type)
    
  • Previously, -XUndecidableInstances accidentally implied -XFlexibleContexts. This is now fixed, but it means that some programs will newly require -XFlexibleContexts.

  • The GHC2021 language is supported now. It builds on top of Haskell2010, adding several stable and conservative extensions, and removing deprecated ones. It is now also the “default” language set that is active when no other language set, such as Haskell98 or Haskell2010, is explicitly loaded (e.g via Cabal’s default-language).

    Because GHC2021 includes GeneralizedNewtypeDeriving, which is not safe for Safe Haskell, users of Safe Haskell are advised to use Haskell2010 explicitly.

    The default mode of GHC until 9.0 included NondecreasingIndentation, but GHC2021 does not. This may break code implicitly using this extension.

  • The Record Dot Syntax Proposal has been implemented:

    • A new extension OverloadedRecordDot provides record . syntax e.g. x.foo
    • A new extension OverloadedRecordUpdate provides record . syntax in record updates e.g. x{foo.bar = 1}. The design of this extension may well change in the future.
  • Various records-related extensions have been improved:

    • A new extension NoFieldSelectors hides record field selector functions, so it is possible to define top-level bindings with the same names.
    • The DisambiguateRecordFields extension now works for updates. An update expr { field = value } will be accepted if there is a single field called field in scope, regardless of whether there are non-fields in scope with the same name.
    • The DuplicateRecordFields extension now applies to fields in record pattern synonyms. In particular, it is possible for a single module to define multiple pattern synonyms using the same field names.
  • Because of simplifications to the way that GHC typechecks operator sections, operators with nested foralls or contexts in their type signatures might not typecheck when used in a section. For instance, the g function below, which was accepted in previous GHC releases, will no longer typecheck:

    f :: a -> forall b. b -> a
    f x _ = x
    
    g :: a -> a
    g = (`f` "hello")
    

    g can be made to typecheck once more by eta expanding it to \x -> x `f` "hello". For more information, see simple-subsumption.

  • LinearTypes can now infer multiplicity for case expressions. Previously, the scrutinee of a case (the bit between case and of) was always assumed to have a multiplicity of Many. Now, GHC will allow the scrutinee to have a multiplicity of One, using its best-effort inference algorithm.

  • Support for matching on GADT constructors in arrow notation has been removed, as the current implementation of Arrows doesn’t handle GADT evidence correctly.

    One possible workaround, for the time being, is to perform GADT matches inside let bindings:

    data G a where
      MkG :: Show a => a -> G a
    
    foo :: G a -> String
    foo = proc x -> do
      let res = case x of { MkG a -> show a }
      returnA -< res
    

2.1.2. Compiler

  • GHC now has an ARMv8 native code generator, significantly improving compilation performance for ARM targets and eliminating a dependency on LLVM.

  • Performance of the compiler in --make mode with -j[⟨n⟩] is significantly improved by improvements to the parallel garbage collector noted below.

    Benchmarks show a 20% decrease in wall clock time, and a 40% decrease in cpu time, when compiling Cabal with -j4 on linux. Improvements are more dramatic with higher parallelism, and we no longer see significant degradation in wall clock time as parallelism increases above 4.

  • New -Wredundant-bang-patterns flag that enables checks for “dead” bangs. For instance, given this program:

    f :: Bool -> Bool
    f True = False
    f !x   = x
    

    GHC would report that the bang on x is redundant and can be removed since the argument was already forced in the first equation. For more details see -Wredundant-bang-patterns.

  • New -Wimplicit-lift flag which warns when a Template Haskell quote implicitly uses lift.

  • New -finline-generics and -finline-generics-aggressively flags for improving performance of generics-based algorithms.

    For more details see -finline-generics and -finline-generics-aggressively.

  • GHC now supports a flag, -fprof-callers=⟨name⟩, for requesting that the compiler automatically insert cost-centres on all call-sites of the named function.

  • The heap profiler can now be controlled from within a Haskell program using functions in GHC.Profiling. Profiling can be started and stopped or a heap census requested at a specific point in the program. There is a new RTS flag --no-automatic-heap-samples which can be used to stop heap profiling starting when a program starts.

  • A new debugging facility, -finfo-table-map, which embeds a mapping from the address of an info table to information about that info table, including an approximate source position. -fdistinct-constructor-tables is also useful with this flag to give each usage of a data constructor its own unique info table so they can be distinguished in gdb and heap profiles.

2.1.3. GHCi

  • GHCi’s :kind! command now expands through type synonyms in addition to type families. See :kind.
  • GHCi’s :edit command now looks for an editor in the VISUAL environment variable before EDITOR, following UNIX convention. (#19030)
  • GHC now follows by default the XDG Base Directory Specification. If $HOME/.ghc is found it will fallback to the old paths to give you time to migrate. This fallback will be removed in three releases.
  • New debugger command :ignore to set an ignore count for a specified breakpoint. The next ignore count times the program hits this breakpoint, the breakpoint is ignored, and the program doesn’t stop.
  • New optional parameter added to the command :continue to set the ignore count for the current breakpoint.

2.1.4. Runtime system

  • The parallel garbage collector is now significantly more performant. Heavily contended spinlocks have been replaced with mutexes and condition variables. For most programs compiled with the threaded runtime, and run with more than four capabilities, we expect minor GC pauses and GC cpu time both to be reduced.

    For very short running programs (in the order of 10s of milliseconds), we have seen some performance regressions. We recommend programs affected by this to either compile with the single threaded runtime, or otherwise to disable the parallel garbage collector with -qg ⟨gen⟩.

    We don’t expect any other performance regressions, however only limited benchmarking has been done. We have only benchmarked GHC and nofib and only on linux.

    Users are advised to reconsider the rts flags that programs are run with. If you have been mitigating poor parallel GC performance by: using large nurseries (-A), disabling load balancing (-qb ⟨gen⟩), or limiting parallel GC to older generations (-qg ⟨gen⟩); then you may find these mitigations are no longer necessary.

  • The heap profiler now has proper treatment of pinned ByteArray#s. Such heap objects will now be correctly attributed to their appropriate cost centre instead of merely being lumped into the PINNED category. Moreover, we now correctly account for the size of the array, meaning that space lost to fragmentation is no longer counted as live data.

  • The -xt RTS flag has been removed. Now STACK and TSO closures are always included in heap profiles. Tooling can choose to filter out these closure types if necessary.

  • A new heap profiling mode, -hi, profile by info table allows for fine-grain banding by the info table address of a closure. The profiling mode is intended to be used with -finfo-table-map and can best be consumed with eventlog2html. This profiling mode does not require a profiling build.

  • The RTS will now gradually return unused memory back to the OS rather than retaining a large amount (up to 4 * live) indefinitely. The rate at which memory is returned is controlled by the -Fd ⟨factor⟩. Memory return is triggered by consecutive idle collections.

  • The default nursery size, -A, has been increased from 1mb to 4mb.

2.1.5. Template Haskell

  • There are two new functions putDoc and getDoc, which allow Haddock documentation to be attached and read from module headers, declarations, function arguments, class instances and family instances. These functions are quite low level, so the withDecDoc function provides a more ergonomic interface for this. Similarly funD_doc, dataD_doc and friends provide an easy way to document functions and constructors alongside their arguments simultaneously.

    $(withDecsDoc "This does good things" [d| foo x = 42 |])
    

2.1.6. ghc-prim library

  • Void# is now a type synonym for the unboxed tuple (# #). Code using Void# now has to enable UnboxedTuples.

2.1.7. Eventlog

  • Two new events, BLOCKS_SIZE tells you about the total size of all allocated blocks and MEM_RETURN gives statistics about why the OS is returning and retaining megablocks.

2.1.8. ghc library

  • There is a significant refactoring in the solver; any type-checker plugins will have to be updated, as GHC no longer uses flattening skolems or flattening metavariables.

  • Type checker plugins which work with the natural numbers now should use naturalTy kind instead of typeNatKind, which has been removed.

  • The con_args field of ConDeclGADT has been renamed to con_g_args. This is because the type of con_g_args is now different from the type of the con_args field in ConDeclH98:

    data ConDecl pass
      = ConDeclGADT
          { ...
          , con_g_args :: HsConDeclGADTDetails pass -- ^ Arguments; never infix
          , ...
          }
    
      | ConDeclH98
          { ...
          , con_args :: HsConDeclH98Details pass -- ^ Arguments; can be infix
          , ...
          }
    

    Where:

    -- Introduced in GHC 9.2; was called `HsConDeclDetails` in previous versions of GHC
    type HsConDeclH98Details pass
       = HsConDetails (HsScaled pass (LBangType pass)) (XRec pass [LConDeclField pass])
    
    -- Introduced in GHC 9.2
    data HsConDeclGADTDetails pass
       = PrefixConGADT [HsScaled pass (LBangType pass)]
       | RecConGADT (XRec pass [LConDeclField pass])
    

    Unlike Haskell98-style constructors, GADT constructors cannot be declared using infix syntax, which is why HsConDeclGADTDetails lacks an InfixConGADT constructor.

    As a result of all this, the con_args field is now partial, so using con_args as a top-level field selector is discouraged.

2.1.9. base library

  • The lifted fixed-width integer and word types (e.g. Data.Int.Int8, Data.Word.Word32) are now represented by their associated fixed-width unlifted types. For instance, while in previous GHC versions Int8 was defined as:

    data Int8 = I8# Int#
    

    As of GHC 9.2 it is rather defined as,

    data Int8 = I8# Int8#
    
  • Character set metadata bumped to Unicode 13.0.0.

  • It’s possible now to promote the Natural type:

    data Coordinate = Mk2D Natural Natural
    type MyCoordinate = Mk2D 1 10
    

    The separate kind Nat is removed and now it is just a type synonym for Natural. As a consequence, one must enable TypeSynonymInstances in order to define instances for Nat.

    The Numeric module receives showBin and readBin to show and read integer numbers in binary.

  • Char gets type-level support by analogy with strings and natural numbers. We extend the GHC.TypeLits module with these built-in type-families:

    type family CmpChar (a :: Char) (b :: Char) :: Ordering
    type family ConsSymbol (a :: Char) (b :: Symbol) :: Symbol
    type family UnconsSymbol (a :: Symbol) :: Maybe (Char, Symbol)
    type family CharToNat (c :: Char) :: Natural
    type family NatToChar (n :: Natural) :: Char
    

    and with the type class KnownChar (and such additional functions as charVal and charVal'):

    class KnownChar (n :: Char)
    
    charVal :: forall n proxy. KnownChar n => proxy n -> Char
    charVal' :: forall n. KnownChar n => Proxy# n -> Char
    
  • A new kind-polymorphic Compare type family was added in Data.Type.Ord and has type instances for Nat, Symbol, and Char. Furthermore, the (<=?) type (and (<=)) from GHC.TypeNats is now governed by this type family (as well as new comparison type operators that are exported by Data.Type.Ord). This has two important repercussions. First, GHC can no longer deduce that all natural numbers are greater than or equal to zero. For instance,

    test1 :: Proxy (0 <=? x) -> Proxy True
    test1 = id
    

    which previously type checked will now result in a type error. Second, when these comparison type operators are used very generically, a kind may need to be provided. For example,

    test2 :: Proxy (x <=? x) -> Proxy True
    test2 = id
    

    will now generate a type error because GHC does not know the kind of x. To fix this, one must provide an explicit kind, perhaps by changing the type to:

    test2 :: forall (x :: Nat). Proxy (x <=? x) -> Proxy True
    
  • On POSIX, System.IO.openFile can no longer leak a file descriptor if it is interrupted by an asynchronous exception (#19114, #19115).

  • There’s a new binding GHC.Exts.considerAccessible. It’s equivalent to True and allows the programmer to turn off pattern-match redundancy warnings for particular clauses, like the third one here

    g :: Bool -> Int
    g x = case (x, x) of
      (True,  True)  -> 1
      (False, False) -> 2
      (True,  False) | considerAccessible -> 3 -- No warning!
    

2.1.9.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.2.5 The compiler itself
Cabal 3.6.3.0 Dependency of ghc-pkg utility
Win32 2.12.0.1 Dependency of ghc library
array 0.5.4.0 Dependency of ghc library
base 4.16.4.0 Core library
binary 0.8.9.0 Dependency of ghc library
bytestring 0.11.3.1 Dependency of ghc library
containers 0.6.5.1 Dependency of ghc library
deepseq 1.4.6.1 Dependency of ghc library
directory 1.3.6.2 Dependency of ghc library
exceptions 0.10.4 Dependency of ghc and haskeline library
filepath 1.4.2.2 Dependency of ghc library
ghc-boot-th 9.2.5 Internal compiler library
ghc-boot 9.2.5 Internal compiler library
ghc-compact 0.1.0.0 Core library
ghc-heap 9.2.5 GHC heap-walking library
ghc-prim 0.8.0 Core library
ghci 9.2.5 The REPL interface
haskeline 0.8.2 Dependency of ghci executable
hpc 0.6.1.0 Dependency of hpc executable
integer-gmp 1.1 Core library
libiserv 9.2.5 Internal compiler library
mtl 2.2.2 Dependency of Cabal library
parsec 3.1.15.0 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.0.2 Dependency of haskeline library
template-haskell 2.18.0.0 Core library
terminfo 0.4.1.5 Dependency of haskeline library
text 1.2.5.0 Dependency of Cabal library
time 1.11.1.1 Dependency of ghc library
transformers 0.5.6.2 Dependency of ghc library
unix 2.7.2.2 Dependency of ghc library
xhtml 3000.2.2.1 Dependency of haddock executable