2.1. Version 9.12.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¶
New language extension:
OrPatternsimplements GHC proposal #522.GHC proposal #569 “Multiline string literals” has been implemented. The following code is now accepted by GHC:
{-# LANGUAGE MultilineStrings #-} x :: String x = """ This is a multiline string literal """
This feature is guarded behind
MultilineStrings.The ordering of variables used for visible type application has been changed in two cases. It is supposed to be left-to-right, but due to an oversight, it was wrong:
in an infix application
f :: a `op` b, it is nowforall a op b.rather thanforall op a b.in a linear type
f :: a %m -> b, it is nowforall a m b.rather thanforall a b m..
This change is backwards-incompatible, although in practice we don’t expect it to cause significant disruption.
The built-in
HasFieldclass, used byOverloadedRecordDot, now supports representation polymorphism (implementing part of GHC proposal #583). This means that code usingUnliftedDatatypesorUnliftedNewtypescan now useOverloadedRecordDot.Unboxed
Float#/Double#literals now support theHexFloatLiteralsextension (#22155).UnliftedFFITypes: GHC will now accept FFI types like:(# #) -> Twhere(# #)is used as the one and only function argument.The venerable
defaultdeclarations have been generalized. They can now name a class other thanNumand the class defaults can be exported. The functionality is guarded by the newNamedDefaultslanguage extension. See GHC proposal #409 for details.GHC now takes
COMPLETEpragmas into consideration when deciding whether pattern matches in do notation are fallible.As part of GHC proposal #281 GHC now accepts type syntax in expressions, namely function type arrow
a -> b, constraint arrowa => b, andforalltelescopes:g = f (forall a. Show a => a -> String) where f :: forall a -> ...
In accordance with GHC proposal #425, GHC now permits wildcard binders in type declarations:
type Const a b = a -- before: the `b` had to be named even if unused on the RHS type Const a _ = a -- now: the compiler accepts a wildcard binder `_`
2.1.2. Compiler¶
GHC now has experimental support for native RISC-V code generation (#16783).
Constructor
PluginProvof typeUnivCoProvenance, relevant for typing plugins, gets an extraDCoVarSetargument. The argument is intended to contain the in-scope coercion variables that the the proof represented by the coercion makes use of. SeeNote [The importance of tracking UnivCo dependencies]inGHC.Core.TyCo.Rep, Constraint solving with plugins and the migration guide.The flag
-fprof-latewill no longer prevent top level constructors from being statically allocated.It used to be the case that we would add a cost centre for bindings like
foo = Just bar. This turned the binding into a CAF that would allocate the constructor on first evaluation.However without the cost centre
foocan be allocated at compile time. This reduces code-bloat and reduces overhead for short-running applications.The tradeoff is that calling
whoCreatedon top level value definitions likefoowill be less informative.A new flag
-fexpose-overloaded-unfoldingshas been added providing a lightweight alternative to-fexpose-all-unfoldings.-Wderiving-typeablehas been added to-Wall.SIMD support has been added to the X86 native code generator. For the time being, only 128 bit wide vectors are supported, with most floating-point operations implemented, together with a few integer vector operations. Other operations still require the LLVM backend. Contributors welcome!
i386 Windows support is now completely removed amid massive cleanup of legacy code to pave way for ARM64 Windows support (#24883). Rest assured, this does not impact existing support for x86_64 Windows or i386 Linux. For end users, the
stdcallC calling convention is now fully deprecated and GHC will unconditionally produce a warning and treat it asccall. All C import/export declarations on Windows should now useccall.32-bit macOS/iOS support has also been completely removed (#24921). This does not affect existing support of Apple systems on x86_64/aarch64.
The flag
-fignore-assertswill now also enable theCPPmacro__GLASGOW_HASKELL_ASSERTS_IGNORED__(#24967). This enables people to write their own custom assertion functions. See Assertions.The flag
-fkeep-auto-rulesthat forces GHC to keep auto generated specialization rules was added. It was actually added ghc-9.10.1 already but mistakenly not mentioned in the 9.10.1 changelog.A new flag
-fmax-forced-spec-args=⟨n⟩has been added. When a function with a SPEC argument is specialized GHC now checks the number of arguments the resulting function takes. If the specialized version takes less than max-forced-spec-args arguments it is specialized. Otherwise GHC will not specialize the function and emit a warning.This avoids edge cases where a SPEC keyword could result in functions being specialized to large static data resulting in functions with thousands of arguments.
Fixed a bug that caused GHC to panic when using the aarch64 NCG and
-fregs-graphon certain programs (#22255).A new warning
-Wview-pattern-signaturesis introduced to notify users about future changes in parsing of view patterns in combination with pattern signatures.GHC now includes a new experimental flag,
-fobject-determinism, which enables deterministic object code generation, with a minor trade-off in compilation speed (typically a 1-2% regression). Note, however, that this flag doesn’t yet ensure determinism across all compilation configurations; we anticipate these cases will be addressed in future updates (#12935).GHC now includes a new flag,
-fwrite-if-compression=⟨n⟩, which controls the level of compression used when writing interface files to disk. While we think the majority of users will be well served by the default setting, the flag allows users to pick their own tradeoff between memory footprint and compilation time when needed.
2.1.3. GHCi¶
Fix a bug where GHCi would not start alongside a local file called
Prelude.hsorPrelude.lhs(#10920).
2.1.4. Runtime system¶
Reduce fragmentation incurred by the nonmoving GC’s segment allocator. In one application this reduced resident set size by 26%. See #24150.
Memory return logic now uses live bytes rather than live blocks to measure the size of the heap. This primarily affects the non-moving GC, which should now be more willing to return memory to the OS. Users who have fine-tuned the
-F ⟨factor⟩,-Fd ⟨factor⟩, or-O ⟨size⟩flags, and use the non-moving GC, should see if adjustments are needed in light of this change.The new runtime flag
--read-tix-file=<yes|no>allows to modify whether a preexisting .tix file is read in at the beginning of a program run. The default is currently--read-tix-file=yesbut will change to--read-tix-file=noin a future version of GHC. For this reason, a warning is emitted if a .tix file is read in implicitly. You can silence this warning by explicitly passing--read-tix-file=yes. Details can be found in GHC proposal #612.
2.1.5. Cmm¶
The
bits128,bits256andbits512types have been removed, in favour ofvec128,vec256andvec512.The
[*]jump annotation (“all registers live”) has been removed, in favour of more specific annotationsGP_ARG_REGS(all general-purpose registers live),SCALAR_ARG_REGS(all scalar registers live), andV16_ARG_REGS,V32_ARG_REGSandV64_ARG_REGS(meaning: all scalar registers plus all vector registers up to the given vector width in bytes).
2.1.6. base library¶
Improve display of exception stack traces and display more metadata about exceptions in the default top-level uncaught exception handler (
GHC.Conc.Sync.uncaughtExceptionHandler). See CLC proposals #231, #261 and #285.Propagate HasCallStack from
errorCallWithCallStackExceptionto exception backtraces, fixing a bug in the implementation of CLC proposal #164.Annotate re-thrown exceptions with backtraces as per CLC proposal #202.
Introduced
catchNoPropagate,rethrowIOandtryWithContextas part of CLC proposal #202 to facilitate rethrowing exceptions without adding aWhileHandlingcontext – if rethrowinge, you don’t want to addWhileHandling eto the context since it will be redundant. These functions are mostly useful for libraries that define exception-handling combinators likecatchandonException, such asbase, or theexceptionspackage.The deprecation process of GHC.Pack has come its term. The module has now been removed from
base.GHC.Desugarhas been deprecated and should be removed in GHC 9.14. (CLC proposal #216)Add a
readTixFilefield to theHpcFlagsrecord inGHC.RTS.Flags(CLC proposal #276)Add
compareLengthtoData.ListandData.List.NonEmpty(CLC proposal #257)Add
INLINE[1]tocompareInt/compareWord(CLC proposal #179)Refactor
GHC.RTS.Flagsin preparation for new I/O managers: introducedata IoManagerFlagand use it inMiscFlags, removegetIoManagerFlag, deprecate re-export ofIoSubSystem(CLC proposal #263)Add the
MonadFixinstance for(,) a, similar to the one forWriter a(CLC proposal #238)Improve
toInteger :: Word32 -> Integeron 64-bit platforms (CLC proposal #259)Make
fliprepresentation polymorphic (CLC proposal #245)The
HasFieldclass now supports representation polymorphism (CLC proposal #194)Make
readaccept binary integer notation (CLC proposal #177)Improve the performance of
Data.List.sortusing an improved merging strategy. Instead ofcompare,sortnow uses(>)which may brea-malform-Ordinstances (CLC proposal #236)Add
inits1andtails1toData.List, factored from the corresponding functions inData.List.NonEmpty(CLC proposal #252)Add
firstAandsecondAtoData.Bitraversable. (CLC proposal #172)Deprecate
GHC.TypeNats.Internal,GHC.TypeLits.Internal,GHC.ExecutionStack.Internal(CLC proposal #217)System.IO.Error.ioErrorandControl.Exception.ioErrornow both carryHasCallStackconstraints (CLC proposal #275)Define
Eq1,Ord1,Show1andRead1instances for basicGenericrepresentation types. (CLC proposal #273)setNonBlockingModewill no longer throw an exception when called on a FD associated with a unknown device type. (CLC proposal #282)
2.1.7. ghc-prim library¶
Usage of deprecated primops is now correctly reported (#19629).
New primops
isMutableByteArrayWeaklyPinned#andisByteArrayWeaklyPinned#to allow users to avoid copying large arrays when dealing with FFI. See Pinned Byte Arrays for more details on the different kinds of pinned arrays in 9.12.This need for this distinction originally surfaced in #22255.
New fused multiply-add instructions for vectors of floating-point values, such as
fmaddFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# -> FloatX4#andfnmsubDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# -> DoubleX2#. These follow the same semantics asfmadd/fmsub/fnmadd/fnmsub, operating in parallel on vectors of floating-point values.New vector shuffle instructions, such as
shuffleFloatX4# :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4#. These instructions take two input vectors and a collection of indices (which must be compile-time literal integers), and constructs a result vector by extracting out the values at those indices. For instance,shuffleFloatX4#on input vectors with components(# 0.1#, 11.1#, 22.1#, 33.1# #)and(# 44.1#, 55.1#, 66.1#, 77.1# #), and indices(# 4#, 3#, 6#, 1# #), will return a vector with components(# 44.1#, 33.1#, 66.1#, 11.1# #).New instructions for minimum/maximum, such as
minDouble#andminFloatX4#. These instructions compute the minimum/maximum of their inputs, working component-wise for SIMD vectors. Supported argument types are vector integer values (e.g.Word16X8#,Int32X4#etc) and both scalar and vector floating point values (e.g.Float#,DoubleX2#,FloatX8#etc).
2.1.8. ghc library¶
2.1.9. ghc-heap library¶
ghc-experimental library
j~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2.1.10. template-haskell library¶
Extend
ExpwithForallE,ForallVisE,ConstraintedE, introduce functionsforallE,forallVisE,constraintedEGHC proposal #281.template-haskellis no longer wired-in. All wired-in identifiers have been moved toghc-internal.Liftinstances were added for thetemplate-haskellAST.
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.12.1.20250219 | The compiler itself |
Cabal-syntax |
3.14.1.0 | Dependency of |
Cabal |
3.14.1.0 | Dependency of |
Win32 |
2.14.1.0 | Dependency of |
array |
0.5.8.0 | Dependency of |
base |
4.21.0.0 | Core library |
binary |
0.8.9.3 | Dependency of |
bytestring |
0.12.2.0 | Dependency of |
containers |
0.7 | Dependency of |
deepseq |
1.5.1.0 | Dependency of |
directory |
1.3.9.0 | Dependency of |
exceptions |
0.10.9 | Dependency of |
file-io |
0.1.5 | Dependency of |
filepath |
1.5.4.0 | Dependency of |
ghc-boot-th |
9.12.1.20250219 | Internal compiler library |
ghc-boot |
9.12.1.20250219 | Internal compiler library |
ghc-compact |
0.1.0.0 | Core library |
ghc-experimental |
9.1201.0 | Core library |
ghc-heap |
9.12.1.20250219 | GHC heap-walking library |
ghc-internal |
9.1201.0 | Core library |
ghc-platform |
0.1.0.0 | Internal library |
ghc-prim |
0.13.0 | Core library |
ghci |
9.12.1.20250219 | The REPL interface |
haskeline |
0.8.2.1 | 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.25.0 | Dependency of |
semaphore-compat |
1.0.0 | Dependency of |
stm |
2.5.3.1 | Dependency of |
template-haskell |
2.23.0.0 | Core library |
terminfo |
0.4.1.7 | Dependency of |
text |
2.1.2 | Dependency of |
time |
1.14 | Dependency of |
transformers |
0.6.1.2 | Dependency of |
unix |
2.8.6.0 | Dependency of |
xhtml |
3000.2.2.1 | Dependency of |
haddock-api |
2.30.0 | Dependency of |
haddock-library |
1.11.0 | Dependency of |