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:
OrPatterns
implements 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
HasField
class, used byOverloadedRecordDot
, now supports representation polymorphism (implementing part of GHC Proposal #583). This means that code usingUnliftedDatatypes
orUnliftedNewtypes
can now useOverloadedRecordDot
.Unboxed
Float#
/Double#
literals now support the HexFloatLiterals extension (#22155).UnliftedFFITypes
: GHC will now accept FFI types like:(# #) -> T
where(# #)
is used as the one and only function argument.The venerable
default
declarations have been generalized. They can now name a class other thanNum
and the class defaults can be exported. The functionality is guarded by the newNamedDefaults
language extension. See the GHC proposal for details.GHC now takes COMPLETE pragmas 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
, andforall
telescopes: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¶
Constructor
PluginProv
of typeUnivCoProvenance
, relevant for typing plugins, gets an extraDCoVarSet
argument. 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-late
will 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
foo
can be allocated at compile time. This reduces code-bloat and reduces overhead for short-running applications.The tradeoff is that calling
whoCreated
on top level value definitions likefoo
will be less informative.A new flag
-fexpose-overloaded-unfoldings
has been added providing a lightweight alternative to-fexpose-all-unfoldings
.-Wderiving-typeable
has 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
stdcall
C 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-asserts
will now also enable theCPP
macro__GLASGOW_HASKELL_ASSERTS_IGNORED__
(#24967). This enables people to write their own custom assertion functions. See Assertions.The flag
-fkeep-auto-rules
that 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.Fixed a bug that caused GHC to panic when using the aarch64 ncg and -fregs-graph on certain programs. (#24941)
A new warning
-Wview-pattern-signatures
is introduced to notify users about future changes in parsing of view patterns in combination with pattern signaturesGHC 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).
2.1.3. GHCi¶
Fix a bug where GHCi would not start alongside a local file called
Prelude.hs
orPrelude.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=yes
but will change to--read-tix-file=no
in 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
,bits256
andbits512
types have been removed, in favour ofvec128
,vec256
andvec512
.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_REGS
andV64_ARG_REGS
(meaning: all scalar registers plus all vector registers up to the given vector width in bytes).
2.1.6. base
library¶
Propagate HasCallStack from errorCallWithCallStackException to exception backtraces, fixing a bug in the implementation of CLC proposal 164 <https://github.com/haskell/core-libraries-committee/issues/164>.
Add exception type metadata to SomeException’s displayException and “Exception:” header to the default handler (i.e.
GHC.Conc.Sync.uncaughtExceptionHandler
):https://github.com/haskell/core-libraries-committee/issues/231 https://github.com/haskell/core-libraries-committee/issues/261
The deprecation process of GHC.Pack <https://gitlab.haskell.org/ghc/ghc/-/issues/21461> has come its term. The module has now been removed from
base
.Annotate re-thrown exceptions with the backtrace as per CLC proposal #202 <https://github.com/haskell/core-libraries-committee/issues/202>
Introduced
catchNoPropagate
,rethrowIO
andtryWithContext
as part of CLC proposal #202 <https://github.com/haskell/core-libraries-committee/issues/202> to facilitate rethrowing exceptions without adding aWhileHandling
context – if rethrowinge
, you don’t want to addWhileHandling e
to the context since it will be redundant. These functions are mostly useful for libraries that define exception-handling combinators likecatch
andonException
, such asbase
, or theexceptions
package.
2.1.7. ghc-prim
library¶
Usage of deprecated primops is now correctly reported (#19629).
New primops isMutableByteArrayWeaklyPinned# and isByteArrayWeaklyPinned# to allow users to avoid copying large arrays safely when dealing with ffi. See the users guide for more details on the different kinds of pinned arrays in 9.12.
This need for this distinction originally surfaced in https://gitlab.haskell.org/ghc/ghc/-/issues/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# and minFloatX4#. 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¶
2.1.10. ghc-experimental
library¶
2.1.11. template-haskell
library¶
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.12.0.20241031 | The compiler itself |
Cabal-syntax |
3.14.0.0 | Dependency of |
Cabal |
3.14.0.0 | Dependency of |
Win32 |
2.14.0.0 | Dependency of |
array |
0.5.8.0 | Dependency of |
base |
4.21.0.0 | Core library |
binary |
0.8.9.2 | Dependency of |
bytestring |
0.12.1.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.7 | Dependency of |
file-io |
0.1.2 | Dependency of |
filepath |
1.5.2.0 | Dependency of |
ghc-boot-th |
9.12.0.20241031 | Internal compiler library |
ghc-boot |
9.12.0.20241031 | Internal compiler library |
ghc-compact |
0.1.0.0 | Core library |
ghc-heap |
9.12.0.20241031 | GHC heap-walking library |
ghc-prim |
0.11.0 | Core library |
ghci |
9.12.0.20241031 | The REPL interface |
haskeline |
0.8.2.1 | Dependency of |
hpc |
0.7.0.1 | Dependency of |
integer-gmp |
1.1 | Core library |
mtl |
2.3.1 | Dependency of |
os-string |
2.0.4 | Dependency of |
parsec |
3.1.17.0 | Dependency of |
pretty |
1.1.3.6 | Dependency of |
process |
1.6.25.0 | Dependency of |
stm |
2.5.3.1 | Dependency of |
template-haskell |
2.22.1.0 | Core library |
terminfo |
0.4.1.6 | Dependency of |
text |
2.1.2 | Dependency of |
time |
1.14 | Dependency of |
transformers |
0.6.1.1 | Dependency of |
unix |
2.8.5.1 | Dependency of |
xhtml |
3000.2.2.1 | Dependency of |
haddock-api |
2.30.0 | Dependency of |
haddock-library |
1.11.0 | Dependency of |