2.1. Version 9.8.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 11, 12, 13, 14 or 15.

2.1.1. Breaking changes

  • In accordance with GHC proposal #425 GHC no longer implicitly quantifies over type variables that appear only in the RHS of type and data family instances. This code will no longer work:

    type family F1 a :: k
    type instance F1 Int = Any :: j -> j
    

    Instead you should write:

    type instance F1 @(j -> j) Int = Any :: j -> j
    

    Or:

    type instance forall j . F1 Int = Any :: j -> j
    
  • GHC proposal #475 has been partially implemented. Namely, tuple data types, which were previously represented using a brackets-with-commas syntax form ((), (,), (,,), and so on) have been renamed to common names of the form Unit, Tuple2, Tuple3, and so on, where the number after Tuple indicates its arity:

    data Unit = ()
    
    data Tuple2 a b = (a,b)
    data Tuple3 a b c = (a, b, c)
    -- and so on, up to Tuple64
    

    For consistency, we also introduce type aliases:

    type Tuple0 = Unit
    type Tuple1 = Solo
    

    The renamed tuple data types and the new type aliases can be found in the GHC.Tuple module. This renaming does not break existing code that directly uses tuple data types, but it does affect tools and libraries that have access to the data type names, such as Generic and Template Haskell.

  • Data types with deriving clauses now reject inferred instance contexts that mention TypeError constraints (see Custom compile-time errors), such as this one:

    newtype Foo = Foo Int
    
    class Bar a where
      bar :: a
    
    instance (TypeError (Text "Boo")) => Bar Foo where
      bar = undefined
    
    newtype Baz = Baz Foo
      deriving Bar
    

    Here, the derived Bar instance for Baz would look like this:

    instance TypeError (Text "Boo") => Bar Baz
    

    While GHC would accept this before, GHC 9.8 now rejects it, emitting “Boo” in the resulting error message. If you really want to derive this instance and defer the error to sites where the instance is used, you must do so manually with StandaloneDeriving, e.g.

    deriving instance TypeError (Text "Boo") => Bar Baz
    

2.1.2. Language

  • There is a new extension ExtendedLiterals, which enables sized primitive numeric literals, e.g. 123#Int8 is a literal of type Int8#. See the GHC proposal #451. Derived Show instances for datatypes containing sized literals (Int8#, Word8#, Int16# etc.) now use the extended literal syntax, per GHC proposal #596. Furthermore, it is now possible to derive Show for datatypes containing fields of types Int64# and Word64#.

  • GHC Proposal #425 has been partially implemented. Namely, the @k-binders in type declarations are now permitted:

    type T :: forall k. k -> forall j. j -> Type
    data T @k (a :: k) @(j :: Type) (b :: j)
    

    This feature is guarded behind TypeAbstractions.

2.1.3. Compiler

  • Added a new warning -Wterm-variable-capture that helps to make code compatible with the future extension RequiredTypeArguments.

  • Rewrite rules now support a limited form of higher order matching when a pattern variable is applied to distinct locally bound variables, as proposed in GHC Proposal #555. For example:

    forall f. foo (\x -> f x)
    

    Now matches:

    foo (\x -> x*2 + x)
    
  • GHC Proposal #496 has been implemented, allowing {..} syntax for constructors without fields, for consistency. This is convenient for TH code generation, as you can now uniformly use record wildcards regardless of number of fields.

  • Specialisation of incoherent instance applications can now be disabled with -fno-specialise-incoherents. This is necessary as the current specialisation implementation can result in in nondeterministic instance resolution in certain cases, breaking the specification described in the documentation of the INCOHERENT pragma. See #22448 for further details.

  • Fix a bug in TemplateHaskell evaluation causing excessive calls to setNumCapabilities when -j[⟨n⟩] is greater than -N. See #23049.

  • The -Wno-⟨wflag⟩, -Werror=⟨wflag⟩ and -Wwarn=⟨wflag⟩ options are now defined systematically for all warning groups (for example, -Wno-default, -Werror=unused-binds and -Wwarn=all are now accepted). See Warnings and sanity-checking.

  • WARNING pragmas may now be annotated with a category, following GHC proposal #541, in which case they are controlled with new -Wx-⟨category⟩ flags rather than -Wdeprecations. A new warning group -Wextended-warnings includes all such warnings regardless of category. See WARNING and DEPRECATED pragmas.

  • GHC is now better at disambiguating record updates in the presence of duplicate record fields. The following program is now accepted

    {-# LANGUAGE DuplicateRecordFields #-}
    
    data R = MkR1 { foo :: Int }
           | MkR2 { bar :: Int }
    
    data S = MkS { foo :: Int, bar :: Int }
    
    blah x = x { foo = 5, bar = 6 }
    

    The point is that only the type S has a constructor with both fields foo and bar, so this record update is unambiguous.

  • GHC Proposal #540 has been implemented. This adds the -jsem flag, which instructs GHC to act as a jobserver client. This enables multiple GHC processes running at once to share system resources with each other, communicating via the system semaphore specified by the flag argument.

    Complementary support for this feature in cabal-install will come soon.

  • GHC Proposal #433 has been implemented. This adds the class Unsatisfiable :: ErrorMessage -> Constraint to the GHC.TypeError module. Constraints of the form Unsatisfiable msg provide a mechanism for custom type errors that reports the errors in a more predictable behaviour than TypeError, as these constraints are handled purely during constraint solving.

    For example:

    instance Unsatisfiable (Text "There is no Eq instance for functions") => Eq (a -> b) where
      (==) = unsatisfiable
    

    This allows errors to be reported when users use the instance, even when type errors are being deferred.

  • GHC now deals with “insoluble Givens” in a consistent way. For example:

    k :: (Int ~ Bool) => Int -> Bool
    k x = x
    

    GHC used to accept the contradictory Int~Bool in the type signature, but reject the Int~Bool constraint that arises from typechecking the definition itself. Now it accepts both. More details in #23413, which gives examples of the previous inconsistency. GHC now implements the “PermissivePlan” described in that ticket.

  • The -ddump-spec flag has been split into -ddump-spec and -ddump-spec-constr, allowing only output from the typeclass specialiser or data-constructor specialiser to be dumped if desired.

  • The compiler may now be configured to compress the debugging information included in -finfo-table-map enabled binaries. To do so, one must build GHC from source (see here for directions) and supply the --enable-ipe-data-compression flag to the configure script. Note: This feature requires that the machine building GHC has libzstd version 1.4.0 or greater installed. The compression library libzstd may optionally be statically linked in the resulting compiler (on non-darwin machines) using the --enable-static-libzstd configure flag.

    In a test compiling GHC itself, the size of the -finfo-table-map enabled build results was reduced by over 20% when compression was enabled.

  • GHC Proposal #134 has been implemented. This makes it possible to deprecate certain names exported from a module, without deprecating the name itself. You can check the full specification of the feature at WARNING and DEPRECATED pragmas.

    For example

    module X
        ( {-# DEPRECATE D(D1) "D1 will not be exposed in a version 0.2 and later" #-}
          D(D1, D2)
        ) where
    data D = D1 | D2
    

    This allows for changing the structure of a library without immediately breaking user code, but instead being able to warn the user that a change in the library interface will occur in the future.

  • Guard polymorphic specialisation behind the flag -fpolymorphic-specialisation. This optimisation has led to a number of incorrect runtime result bugs, so we are disabling it by default for now whilst we consider more carefully an appropiate fix. (See #23469, #23109, #21229, #23445)

  • The warning about incompatible command line flags can now be controlled with the -Winconsistent-flags. In particular this allows you to silence a warning when using optimisation flags with --interactive mode.

2.1.4. GHCi

  • The deprecated :ctags and :etags GHCi commands have been removed. See this wiki page if you want to add a macro to recover similar functionality.

2.1.5. Runtime system

  • On POSIX systems that support timerfd, RTS shutdown no longer has to wait for the next RTS ‘tick’ to occur before continuing the shutdown process. See #22692.

2.1.6. base library

Note that this is not an exhaustive list of changes in base. See the base changelog for full details.

  • Added {-# WARNING in "x-partial" #-} to Data.List.{head,tail}.
  • Data.Tuple now exports getSolo :: Solo a -> a.
  • Updated to Unicode 15.1.0.
  • Fixed exponent overflow/underflow bugs in the Read instances for Float and Double (CLC proposal #192)

2.1.7. ghc-prim library

  • Primitive pointer comparison functions are now levity-polymorphic, e.g.

    sameArray# :: forall {l} (a :: TYPE (BoxedRep l)). Array# a -> Array# a -> Int#
    

    This change affects the following functions:

    • sameArray#, sameMutableArray#,
    • sameSmallArray#, sameSmallMutableArray#,
    • sameMutVar#, sameTVar#, sameMVar#
    • sameIOPort#, eqStableName#.
  • New primops for fused multiply-add operations. These primops combine a multiplication and an addition, compiling to a single instruction when the -mfma flag is enabled and the architecture supports it.

    The new primops are fmaddFloat#, fmsubFloat#, fnmaddFloat#, fnmsubFloat# :: Float# -> Float# -> Float# -> Float# and fmaddDouble#, fmsubDouble#, fnmaddDouble#, fnmsubDouble# :: Double# -> Double# -> Double# -> Double#.

    These implement the following operations, while performing one single rounding at the end, leading to a more accurate result:

    • fmaddFloat# x y z, fmaddDouble# x y z compute x * y + z.
    • fmsubFloat# x y z, fmsubDouble# x y z compute x * y - z.
    • fnmaddFloat# x y z, fnmaddDouble# x y z compute - x * y + z.
    • fnmsubFloat# x y z, fnmsubDouble# x y z compute - x * y - z.

    Warning: on unsupported architectures, the software emulation provided by the fallback to the C standard library is not guaranteed to be IEEE-compliant.

2.1.8. ghc library

  • The RecordUpd constructor of HsExpr now takes an HsRecUpdFields instead of Either [LHsRecUpdField p] [LHsRecUpdProj p]. Instead of Left .., use the constructor RegularRecUpdFields, and instead of Right .., use the constructor OverloadedRecUpdFields.
  • The loadWithCache function now takes an extra argument which allows API users to embed GHC diagnostics in their own diagnostic type before they are printed. This allows how messages are rendered and explained to users to be modified. We use this functionality in GHCi to modify how some messages are displayed.
  • The extensions fields of constructors of IE now take Maybe (WarningTxt p) in GhcPs and GhcRn variants of the Syntax Tree. This represents the warning assigned to a certain export item, which is used for deprecated exports.

2.1.9. template-haskell library

  • Record fields now belong to separate NameSpaces, keyed by the parent of the record field. This is the name of the first constructor of the parent type, even if this constructor does not have the field in question. This change enables TemplateHaskell support for DuplicateRecordFields.

2.1.10. text library

The version of the text library included changes Data.Text.Array.Array to be a type synonym of Data.Array.Byte.ByteArray. While its former data constructor, ByteArray, has been replaced with a pattern synonym, it cannot be imported as bundled with the type constructor.

Consequently, imports like:

import Data.Text.Array (Array(..))

will need to avoid using a bundled import (e.g. by qualification):

import Data.Text.Array as A

2.1.11. 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.8.2 The compiler itself
Cabal-syntax 3.10.2.0 Dependency of ghc-pkg utility
Cabal 3.10.2.0 Dependency of ghc-pkg utility
Win32 2.13.4.0 Dependency of ghc library
array 0.5.6.0 Dependency of ghc library
base 4.19.1.0 Core library
binary 0.8.9.1 Dependency of ghc library
bytestring 0.12.1.0 Dependency of ghc library
containers 0.6.8 Dependency of ghc library
deepseq 1.5.0.0 Dependency of ghc library
directory 1.3.8.1 Dependency of ghc library
exceptions 0.10.7 Dependency of ghc and haskeline library
filepath 1.4.200.1 Dependency of ghc library
ghc-boot-th 9.8.2 Internal compiler library
ghc-boot 9.8.2 Internal compiler library
ghc-compact 0.1.0.0 Core library
ghc-heap 9.8.2 GHC heap-walking library
ghc-prim 0.11.0 Core library
ghci 9.8.2 The REPL interface
haskeline 0.8.2.1 Dependency of ghci executable
hpc 0.7.0.0 Dependency of hpc executable
integer-gmp 1.1 Core library
mtl 2.3.1 Dependency of Cabal library
parsec 3.1.17.0 Dependency of Cabal library
pretty 1.1.3.6 Dependency of ghc library
process 1.6.18.0 Dependency of ghc library
semaphore-compat 1.0.0 Dependency of ghc library
stm 2.5.2.1 Dependency of haskeline library
template-haskell 2.21.0.0 Core library
terminfo 0.4.1.6 Dependency of haskeline library
text 2.1.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.4.0 Dependency of ghc library
xhtml 3000.2.2.1 Dependency of haddock executable