2.1. Version 9.14.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¶
GHC proposal 493: allow expressions in SPECIALISE pragmas has been implemented. SPECIALISE pragmas now allow arbitrary expressions such as:
{-# SPECIALISE f @Int False :: Int -> Char #-}The ability to specify multiple specialisations in a single SPECIALISE pragma, with syntax of the form (note the comma between the type signatures):
{-# SPECIALISE g : Int -> Int, Float -> Float #-}has been deprecated, and is scheduled to be removed in GHC 9.18. This deprecation is controlled by the newly introduced
-Wdeprecated-pragmasflag in-Wdefault.Visible
GADTsyntax can now be used in GADT data constructors (#25127)data KindVal a where K :: forall k. forall (a::k) -> -- now allowed! k -> KindVal a
-Wincomplete-record-selectorsis now part of -Wall, as specified by GHC Proposal 516: add warning for incomplete record selectors. Hence, if a library is compiled with-Werror, compilation may now fail. Solution: fix the library. Workaround: add-Werror=no-incomplete-record-selectors.Note that this warning is at least as serious as a warning about missing patterns from a function definition, perhaps even more so, since it is invisible in the source program.
The combination of
ScopedTypeVariablesandTypeApplicationsno longer enables type applications in patterns, which now always requiresTypeAbstractions. The warning flag``deprecated-type-abstractions`` has also been removed from the compiler.OverloadedRecordUpdatenow passes the arguments to asetFieldfunction in the flipped order, as specified by GHC Proposal 583: HasField redesign.Previously GHC expected
setFieldto have this type:setField :: forall (fld :: Symbol) a r. r -> a -> r
And that’s what GHC expects now:
setField :: forall (fld :: Symbol) a r. a -> r -> r
That will break the combination of
OverloadedRecordUpdatewithRebindableSyntax.Multiline strings are now accepted in
foreign imports. (#25157)GHC now does a better job at inferring types in calls to
coerce: instead of complaining about ambiguous type variables, GHC will consider that such type variables are determined by theCoercibleconstraints they appear in.With
LinearTypesrecord fields can now be non-linear. This means that the following record declaration is now valid:data Record = Rec { x %'Many :: Int, y :: Char }
This causes the constructor to have type
Rec :: Int %'Many -> Char %1 -> Record.The
ExplicitNamespacesextension now allows thedatanamespace specifier in import and export lists.The
-Wdata-kinds-tcwarning has been deprecated, and the use of promoted data types in kinds is now an error (rather than a warning) unless theDataKindsextension is enabled. For example, the following code will be rejected unlessDataKindsis on:import Data.Kind (Type) import GHC.TypeNats (Nat) -- Nat shouldn't be allowed here without DataKinds data Vec :: Nat -> Type -> Type
(The
-Wdata-kinds-tcwarning was introduced in GHC 9.10 as part of a fix for an accidental oversight in which programs like the one above were mistakenly accepted without the use ofDataKinds.)The
MonadComprehensionsextension now impliesParallelListCompas was originally intended (see Monad Comprehensions).In accordance with GHC Proposal #281, section 4.7 “Data constructors”, the
RequiredTypeArgumentsextension now allows visible forall in types of data constructors (#25127). The following declaration is now accepted by GHC:data T a where Typed :: forall a -> a -> T a
See Visible forall in GADTs for details.
Explicit level import support, allowing
importdeclarations to explicitly state which compilation stages they are are visible to.
2.1.2. Compiler¶
An improved error message is introduced to refer users to the heap-controlling flags of the RTS when there is a heap overflow during compilation. (#25198)
The kind checker now does a better job of finding type family instances for use in the kinds of other declarations in the same module. This fixes a number of tickets: #12088, #12239, #14668, #15561, #16410, #16448, #16693, #19611, #20875, #21172, #22257, #25238, #25834.
The compiler no longer accepts invalid
typenamespace specifiers in subordinate import lists (#22581).A new flag,
-Wuseless-specialisations, controls warnings emitted when GHC determines that aSPECIALISEpragma would have no effect.A new flag,
-Wrule-lhs-equalities, controls warnings emitted forRULESwhose left-hand side attempts to quantify over equality constraints that previous GHC versions accepted quantifying over. GHC will now drop such RULES, emitting a warning message controlled by this flag.This warning is intended to give visibility to the fact that the
RULESthat previous GHC versions generated in such circumstances could never fire.A new flag,
-Wunusable-unpack-pragmas, controls warnings emitted when GHC is unable to unpack a data constructor field annotated by the{-# UNPACK #-}pragma.Previous GHC versions issued this warning unconditionally. Now it is possible to disable it with
-Wno-unusable-unpack-pragmasor turn it into an error with-Werror=unusable-unpack-pragmas.Introduce a new warning
-Wpattern-namespace-specifierto detect uses of the now deprecatedpatternnamespace specifier in import/export lists. See GHC Proposal #581, section 2.3.Code coverage (
-fhpc) now treats uses of record fields viaRecordWildCardsorNamedFieldPunsas if the fields were accessed using the generated record selector functions, marking the fields as covered in coverage reports (#17834).SIMD support in the x86 native code generator has been extended with 128-bit integer operations. Also,
shuffleFloatX4#andshuffleDoubleX2#no longer require-mavx.Initial native code generator support for the LoongArch CPU architecture.
2.1.3. GHCi¶
Support for multiple home units in GHCi (#20889)
:infonow outputs type declarations with@-binders that are considered semantically significant. See the documentation for:infoitself for a more detailed explanation.GHCi errors and warnings now have their own numeric error codes that are displayed alongside the error.
Many performance and correctness improvements in the bytecode interpreter.
Numerous improvements in the GHCi debugger including:
Significantly improved performance of the
:steplocalcommand (#25779)Every
dostatement is now a breakpoint, resulting in more predictable and intuitive:breakbehaviorA
:stepoutcommand is now available, allowing stepping out from functions and bindings when stopped at a breakpoint. Note that this feature is made available as a technology preview and we expect further refinement in future releases.Improvements in the GHCi debugger API, setting the groundwork for integration with Debug Adapter Protocol (DAP) and other interactive debugging clients
Internal refactorings towards making the debugger multi-thread aware (#26064)
2.1.4. WebAssembly backend¶
The WebAssembly backend now supports evaluation via the interpreter, allowing
both interactive usage via GHCi and TemplateHaskell evaluation. This includes
usage of foreign import javascript, allowing interactive
usage within the browser including interaction with the DOM (modulo various
constraints imposed by WebAsm implementations).
See the blog post on Tweag’s blog for more information.
2.1.5. Runtime system¶
Add new runtime flag
--optimistic-linkingwhich instructs the runtime linker to continue in the presence of unknown symbols. By default this flag is not passed, preserving previous behavior.
2.1.6. base library¶
Updated to Unicode 17.0.0.
2.1.7. ghc-prim library¶
ghc-prim is now a legacy interface providing access to primitive operations
and types which are now also exposed via the ghc-experimental package.
2.1.8. ghc library¶
The
UnknownDiagnosticconstructor now takes an additional type argument for the type of hints corresponding to the diagnostic, and an additional value-level argument used for existential wrapping of the hints of the inner diagnostic.Changes to the HPT and HUG interface:
addToHptandaddListToHPTwere moved fromGHC.Unit.Home.ModInfotoGHC.Unit.Home.PackageTableand deprecated in favour ofaddHomeModInfoToHptandaddHomeModInfosToHpt.UnitEnvGraphand operationsunitEnv_lookup_maybe,unitEnv_foldWithKey, ``unitEnv_singleton,unitEnv_adjust,unitEnv_insert,unitEnv_newwere moved fromGHC.Unit.EnvtoGHC.Unit.Home.Graph.The HomePackageTable (HPT) is now exported from
GHC.Unit.Home.PackageTable, and is now backed by an IORef to avoid by construction very bad memory leaks. This means the API to the HPT now is for the most part in IO. For instance,emptyHomePackageTableandaddHomeModInfoToHptare now in IO.mkHomeUnitEnvwas moved toGHC.Unit.Home.PackageTable, and now takes two extra explicit arguments. To restore previous behaviour, passemptyUnitStateandNothingas the first two arguments additionally.hugEltswas removed. Users should preferallUnitsto get the keys of the HUG (the typical use case), ortraverseorunitEnv_foldWithKeyin other cases.
Changes to
Language.Haskell.Syntax.ExprThe
ParStmtBlocklist argument of theParStmtconstructor ofStmtLRis nowNonEmpty.
As part of the implementation of
GHC proposal 493 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0493-specialise-expressions.rst>``_, the ``SpecSigconstructor ofSighas been deprecated. It is replaced by the constructorSpecSigEwhich supports expressions at the head, rather than a lone variable.
2.1.9. ghc-heap library¶
The functions
getClosureInfoTbl_maybe,getClosureInfoTbl,getClosurePtrArgsandgetClosurePtrArgs_maybehave been added to allow reading of the relevant Closure attributes without reliance on incomplete selectors.
2.1.10. ghc-experimental library¶
ghc-experimentalnow exposesGHC.RTS.FlagsandGHC.StatsasGHC.RTS.Flags.ExperimentalandGHC.Stats.Experimental. These are also exposed inbase, however thebaseversions will be deprecated as part of the split base project. See CLC proposal 289. Downstream consumers of these flags are encouraged to migrate to theghc-experimentalversions.
2.1.11. template-haskell library¶
As part of the implementation of GHC proposal 493, the
SpecialisePconstructor of the Template HaskellPragmatype, as well as the helperspragSpecDandpragSpecInlD, have been deprecated.They are replaced, respectively, by
SpecialiseEP,pragSpecEDandpragSpecInlED.
2.1.12. 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.14.0.20251028 | The compiler itself |
Cabal-syntax |
3.16.0.0 | Dependency of |
Cabal |
3.16.0.0 | Dependency of |
Win32 |
2.14.2.1 | Dependency of |
array |
0.5.8.0 | Dependency of |
base |
4.22.0.0 | Core library |
binary |
0.8.9.3 | Dependency of |
bytestring |
0.12.2.0 | Dependency of |
containers |
0.8 | Dependency of |
deepseq |
1.5.1.0 | Dependency of |
directory |
1.3.10.0 | Dependency of |
exceptions |
0.10.9 | Dependency of |
file-io |
0.1.5 | Dependency of |
filepath |
1.5.4.0 | Dependency of |
ghc-bignum |
1.4 | Core library. |
ghc-boot-th |
9.14.0.20251028 | Internal compiler library |
ghc-boot |
9.14.0.20251028 | Internal compiler library |
ghc-compact |
0.1.0.0 | Core library |
ghc-experimental |
9.1400.0 | Core library. |
ghc-heap |
9.14.0.20251028 | Core library. |
ghc-internal |
9.1400.0 | Internal implementation. |
ghc-platform |
0.1.0.0 | Internal compiler library. |
ghc-prim |
0.13.1 | Core library |
ghci |
9.14.0.20251028 | The REPL interface |
haskeline |
0.8.3.0 | Dependency of |
hpc |
0.7.0.2 | Dependency of |
integer-gmp |
1.1 | Core library |
mtl |
2.3.1 | Dependency of |
os-string |
2.0.7 | Dependency of |
parsec |
3.1.18.0 | Dependency of |
pretty |
1.1.3.6 | Dependency of |
process |
1.6.26.1 | Dependency of |
semaphore-compat |
1.0.0 | Dependency of |
stm |
2.5.3.1 | Dependency of |
template-haskell |
2.24.0.0 | Core library |
terminfo |
0.4.1.7 | Dependency of |
text |
2.1.3 | Dependency of |
time |
1.15 | Dependency of |
transformers |
0.6.1.2 | Dependency of |
unix |
2.8.8.0 | Dependency of |
xhtml |
3000.2.2.1 | Dependency of |
ghc-toolchain |
0.1.0.0 | Internal compiler library. |
haddock-api |
2.33.0 | Dependency of |
haddock-library |
1.11.0 | Dependency of |