2.1. Version 9.10.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.

2.1.1. Language

  • The GHC2024 language edition is now supported. It builds on top of GHC2021, adding the following extensions:

    At the moment, GHC2021 remains the default langauge edition that is used when no other language edition is explicitly loaded (e.g. when running ghc directly). Because language editions are not necessarily backwards compatible, and future releases of GHC may change the default, it is highly recommended to specify the language edition explicitly.

  • GHC Proposal #281 “Visible forall in types of terms” has been partially implemented. The following code is now accepted by GHC:

    {-# LANGUAGE RequiredTypeArguments #-}
    
    vshow :: forall a -> Show a => a -> String
    vshow t x = show (x :: t)
    
    s1 = vshow Int    42      -- "42"
    s2 = vshow Double 42      -- "42.0"
    

    The use of forall a -> instead of forall a. indicates a required type argument. A required type argument is visually indistinguishable from a value argument but does not exist at runtime.

    This feature is guarded behind RequiredTypeArguments.

  • The ExplicitNamespaces extension can now be used in conjunction with RequiredTypeArguments to select the type namespace in a required type argument:

    data T = T               -- the name `T` is ambiguous
    f :: forall a -> ...     -- `f` expects a required type argument
    
    x1 = f T         -- refers to the /data/ constructor `T`
    x2 = f (type T)  -- refers to the /type/ constructor `T`
    
  • With LinearTypes, let and where bindings can now be linear. So the following now typechecks:

    f :: A %1 -> B
    g :: B %1 -> C
    
    h :: A %1 -> C
    h x = g y
      where
        y = f x
    
  • Due to an oversight, previous GHC releases (starting from 9.4) allowed the use of promoted data types in kinds, even when DataKinds was not enabled. That is, GHC would erroneously accept the following code:

    {-# LANGUAGE NoDataKinds #-}
    
    import Data.Kind (Type)
    import GHC.TypeNats (Nat)
    
    -- Nat shouldn't be allowed here without DataKinds
    data Vec :: Nat -> Type -> Type
    

    This oversight has now been fixed. If you wrote code that took advantage of this oversight, you may need to enable DataKinds in your code to allow it to compile with GHC 9.10.

    For more information on what types are allowed in kinds, see the Datatype promotion section.

  • Using forall as an identifier is now a parse error, as forewarned by -Wforall-identifier:

    forall :: (Variable a, MonadQSAT s m) => m a
    -- parse error on input ‘forall’
    

    Library authors are advised to use a different name for their functions, such as forAll, for_all, or forall_.

  • GHC Proposal #65 “Require namespacing fixity declarations for type names and WARNING/DEPRECATED pragmas” has been partially implemented. Now, with ExplicitNamespaces enabled, you can specify the namespace of a name in fixity signatures, DEPRECATED and WARNING pragmas:

    type f $ a = f a
    f $ a = f a
    
    infixl 9 type $ -- type-level $ is left-associative with priority 9
    infixr 0 data $ -- term-level $ is right-associative with priority 0
    
    {-# DEPRECATED type D "Use `()` instead" #-} -- this will deprecate type D, but will not touch pattern synonym
    data D = MkD
    
    {-# DEPRECATED data D "Use `MkD` instead" #-} -- this will deprecate pattern synonym only
    pattern D = MkD
    
    pattern Head x <- (head -> x)
    {-# WARNING in "x-partial" data Head [ "This is a partial synonym,"
                                         , "it throws an error on empty lists."] #-}
    
  • GHC Proposal #475 “Non-punning list and tuple syntax” has been partially implemented. When the newly introduced extension ListTuplePuns is disabled, bracket syntax for lists, tuples and sums only denotes their data constructors, while their type constructors have been changed to use regular prefix syntax:

    data List a = [] | a : List a
    data Tuple2 a b = (a, b)
    

    The extension is enabled by default, establishing the usual behavior.

  • In accordance with GHC Proposal #448, the TypeAbstractions extension has been extended to support @-binders in lambdas and function equations:

    id :: forall a. a -> a
    id @t x = x :: t
    -- ^^ @-binder in a function equation
    
    e = higherRank (\ @t -> ... )
    --                ^^ @-binder in a lambda
    

    This feature is an experimental alternative to ScopedTypeVariables, see the Type Abstractions in Functions section.

2.1.2. Compiler

  • GHC Proposal #516 has been implemented. It introduces a warning -Wincomplete-record-selectors which warns about when an invocation of a record selector may fail due to being applied to a constructor for which it is not defined.

    For example

    data T = T1 | T2 { x :: Int }
    f :: T -> Int
    f a = x a + 1 -- emit a warning here, since `f T1` will fail
    

    Unlike -Wpartial-fields this produces a warning about incomplete selectors at use sites instead of definition sites, so it is useful in cases when the library does intend for incomplete record selectors to be used but only in specific circumstances (e.g. when other cases are handled by previous pattern matches).

  • The -finfo-table-map-with-stack and -finfo-table-map-with-fallback flags have been introduced. These flags include STACK info tables and info tables with default source location information in the info table map, respectively. They are implied by the -finfo-table-map flag. The corresponding negative flags (-fno-info-table-map-with-stack, -fno-info-table-map-with-fallback) are useful for omitting these info tables from the info table map and reducing the size of executables containing info table profiling information. In a test on the Agda codebase, the size of the build results was reduced by about 10% when these info tables were omitted.

  • Fixed a bug where compiling with both -ddump-timings and -ddump-to-file did not suppress printing timings to the console. See #20316.

  • Defaulting plugins can now propose solutions to entangled sets of type variables. This allows defaulting of multi-parameter type classes. See #23832.

  • The flag -funbox-small-strict-fields will now properly recognize unboxed tuples containing multiple elements as large. Constructors like Foo (# Int64, Int64# ) will no longer be considered small and therefore not unboxed by default under -O even when used as strict field. #22309.

  • The flag -funbox-small-strict-fields will now always unpack things as if compiling for a 64bit platform. Even when generating code for a 32bit platform. This makes core optimizations more consistent between 32bit and 64bit platforms at the cost of slightly worse 32bit performance in edge cases.

  • Type abstractions in constructor patterns that were previously admitted without enabling the TypeAbstractions extension now trigger a warning, -Wdeprecated-type-abstractions. This new warning is part of the -Wcompat warning group and will become an error in a future GHC release.

  • The -Wforall-identifier flag is now deprecated and removed from -Wdefault, as forall is no longer parsed as an identifier.

  • Late plugins have been added. These are plugins which can access and/or modify the core of a module after optimization and after interface creation. See #24254.

  • If you use -fllvm we now use an assembler from the LLVM toolchain rather than the preconfigured assembler. This is typically clang. The LLVMAS environment variable can be specified at configure time to instruct GHC which clang to use. This means that if you are using -fllvm you now need llc, opt and clang available.

  • The -fprof-late-overloaded flag has been introduced. It causes cost centres to be added to overloaded top level bindings, unlike -fprof-late which adds cost centres to all top level bindings.

  • The -fprof-late-overloaded-calls flag has been introduced. It causes cost centres to be inserted at call sites including instance dictionary arguments. This may be preferred over -fprof-late-overloaded since it may reveal whether imported functions are called overloaded.

2.1.3. JavaScript backend

  • The JavaScript backend now supports linking with C sources. It uses Emscripten to compile them to WebAssembly. The resulting JS file embeds and loads these WebAssembly files. Important note: JavaScript wrappers are required to call into C functions and pragmas have been added to indicate which C functions are exported (see the users guide).

2.1.4. WebAssembly backend

  • The wasm backend now implements JavaScript FFI, allowing JavaScript to be called from Haskell and vice versa when targetting JavaScript environments like browsers and node.js. See JavaScript FFI in the wasm backend for details.

2.1.5. GHCi

  • GHCi now differentiates between adding, unadding, loading, unloading and reloading in its responses to using the respective commands. The output with -fshow-loaded-modules is not changed to keep backwards compatibility for tooling.

2.1.6. Runtime system

  • Internal fragmentation incurred by the non-moving GC’s allocator has been reduced for small objects. In one real-world application, this has reduced resident set size by about 20% and modestly improved run-time. See #23340. --nonmoving-dense-allocator-count=⟨count⟩ has been added to fine-tune this behaviour.
  • Add support for heap profiling with the non-moving GC. See #22221.
  • Add a --no-automatic-time-samples flag which stops time profiling samples being automatically started on startup. Time profiling can be controlled manually using functions in GHC.Profiling.
  • Add a -xr ⟨size⟩ which controls the size of virtual memory address space reserved by the two step allocator on a 64-bit platform. The default size is now 1T on aarch64 as well. See #24498.

2.1.7. base library

  • Updated to Unicode 15.1.0.

  • The functions GHC.Exts.dataToTag# and GHC.Base.getTag have had their types changed to the following:

    dataToTag#, getTag
      :: forall {lev :: Levity} (a :: TYPE (BoxedRep lev))
      .  DataToTag a => a -> Int#
    

    In particular, they are now applicable only at some (not all) lifted types. However, if t is an algebraic data type (i.e. t matches a data or data instance declaration) with all of its constructors in scope and the levity of t is statically known, then the constraint DataToTag t can always be solved.

  • Exceptions can now carry arbitrary user-defined annotations via the new GHC.Exception.Type.ExceptionContext implicit parameter of SomeException. These annotations are intended to be used to carry context describing the provenance of an exception.

  • GHC now collects backtraces for synchronous exceptions. These are carried by the exception via the ExceptionContext mechanism described above. GHC supports several mechanisms by which backtraces can be collected which can be individually enabled and disabled via GHC.Exception.Backtrace.setEnabledBacktraceMechanisms.

2.1.8. ghc-prim library

  • dataToTag# has been moved from GHC.Prim. It remains exported by GHC.Exts, but with a different type, as described in the notes for base above.

  • New primops for unaligned Addr# access. These primops will be emulated on platforms that don’t support unaligned access. These primops take the form

    indexWord8OffAddrAs<ty> :: Addr# -> Int# -> <ty>#
    readWord8OffAddrAs<ty> :: Addr# -> Int# -> State# s -> (# State# s, <ty># #)
    writeWord8OffAddrAs<ty> :: Addr# -> Int# -> <ty># -> State# s -> State# s
    

    where <ty> is one of:

    • Word
    • Word{16,32,64}
    • Int
    • Int{16,32,64,}
    • Char
    • WideChar
    • Addr
    • Float
    • Double
    • StablePtr

2.1.9. ghc library

2.1.10. ghc-heap library

2.1.11. ghc-experimental library

  • ghc-experimental is a new library for functions and data types with weaker stability guarantees. Introduced per the HF Technical Proposal #51.

2.1.12. template-haskell library

  • Extend Pat with TypeP and Exp with TypeE, introduce functions typeP and typeE (Template Haskell support for GHC Proposal #281).

2.1.13. 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.10.0.20240413 The compiler itself
Cabal-syntax 3.12.0.0 Dependency of ghc-pkg utility
Cabal 3.12.0.0 Dependency of ghc-pkg utility
Win32 2.14.0.0 Dependency of ghc library
array 0.5.7.0 Dependency of ghc library
base 4.20.0.0 Core library
binary 0.8.9.2 Dependency of ghc library
bytestring 0.12.1.0 Dependency of ghc library
containers 0.7 Dependency of ghc library
deepseq 1.5.0.0 Dependency of ghc library
directory 1.3.8.3 Dependency of ghc library
exceptions 0.10.7 Dependency of ghc and haskeline library
filepath 1.5.2.0 Dependency of ghc library
ghc-boot-th 9.10.0.20240413 Internal compiler library
ghc-boot 9.10.0.20240413 Internal compiler library
ghc-compact 0.1.0.0 Core library
ghc-heap 9.10.0.20240413 GHC heap-walking library
ghc-prim 0.11.0 Core library
ghci 9.10.0.20240413 The REPL interface
haskeline 0.8.2.1 Dependency of ghci executable
hpc 0.7.0.1 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.19.0 Dependency of ghc library
stm 2.5.3.1 Dependency of haskeline library
template-haskell 2.22.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.1 Dependency of ghc library
unix 2.8.5.1 Dependency of ghc library
xhtml 3000.2.2.1 Dependency of haddock executable