1.. _release-8-10-1:
2
3Release notes for version 8.10.1
4================================
5
6The significant changes to the various parts of the compiler are listed in the
7following sections.
8
9
10Highlights
11----------
12
13- The :extension:`UnliftedNewtypes` extension, allowing ``newtype``\s to be
14  wrap types of kind other than ``Type``.
15
16- The :extension:`StandaloneKindSignatures` extension, allowing explicit
17  signatures on type constructors.
18
19- A new, :rts-flag:`low-latency garbage collector <-xn>` for the oldest generation.
20
21Full details
22------------
23
24Language
25~~~~~~~~
26
27- Kind variables are no longer implicitly quantified when an explicit ``forall`` is used, see
28  `GHC proposal #24
29  <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0024-no-kind-vars.rst>`__.
30  :ghc-flag:`-Wimplicit-kind-vars` is now obsolete.
31
32- Kind variables are no longer implicitly quantified in constructor declarations: ::
33
34    data T a        = T1 (S (a :: k)) | forall (b::k). T2 (S b)  -- no longer accepted
35    data T (a :: k) = T1 (S (a :: k)) | forall (b::k). T2 (S b)  -- still accepted
36
37- Implicitly quantified kind variables are no longer put in front of other variables: ::
38
39    f :: Proxy (a :: k) -> Proxy (b :: j)
40
41    ghci> :t +v f   -- old order:
42    f :: forall k j (a :: k) (b :: j). Proxy a -> Proxy b
43
44    ghci> :t +v f   -- new order:
45    f :: forall k (a :: k) j (b :: j). Proxy a -> Proxy b
46
47  This is a breaking change for users of :extension:`TypeApplications`.
48
49- In type synonyms and type family equations, free variables on the RHS are no longer
50  implicitly quantified unless used in an outermost kind annotation: ::
51
52    type T = Just (Nothing :: Maybe a)         -- no longer accepted
53    type T = Just Nothing :: Maybe (Maybe a)   -- still accepted
54
55- A new extension :extension:`StandaloneKindSignatures` allows one to explicitly
56  specify the kind of a type constructor, as proposed in `GHC proposal #54
57  <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0054-kind-signatures.rst>`__: ::
58
59    type TypeRep :: forall k. k -> Type
60    data TypeRep a where
61      TyInt   :: TypeRep Int
62      TyMaybe :: TypeRep Maybe
63      TyApp   :: TypeRep a -> TypeRep b -> TypeRep (a b)
64
65  Analogous to function type signatures, a :ref:`standalone kind signature
66  <standalone-kind-signatures>` enables polymorphic recursion. This feature is
67  a replacement for :extension:`CUSKs`.
68
69  **Note:** The finer points around this feature are subject to change. In particular,
70  it is likely that the treatment around :ref:`specified and inferred <inferred-vs-specified>`
71  variables may change, to become more like the way term-level type signatures are
72  handled.
73
74- GHC now parses visible, dependent quantifiers (as proposed in
75  `GHC proposal 35
76  <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0081-forall-arrow.rst>`__),
77  such as the following: ::
78
79    data Proxy :: forall k -> k -> Type
80
81  See the :ref:`section on explicit kind quantification
82  <explicit-kind-quantification>` for more details.
83
84- Type variables in associated type family default declarations can now be
85  explicitly bound with a ``forall`` when :extension:`ExplicitForAll` is
86  enabled, as in the following example: ::
87
88    class C a where
89      type T a b
90      type forall a b. T a b = Either a b
91
92  This has a couple of knock-on consequences:
93
94  - Wildcard patterns are now permitted on the left-hand sides of default
95    declarations, whereas they were rejected by previous versions of GHC.
96
97  - It used to be the case that default declarations supported occurrences of
98    left-hand side arguments with higher-rank kinds, such as in the following
99    example: ::
100
101      class C a where
102        type T a (f :: forall k. k -> Type)
103        type T a (f :: forall k. k -> Type) = f Int
104
105    This will no longer work unless ``f`` is explicitly quantified with a
106    ``forall``, like so: ::
107
108      class C a where
109        type T a (f :: forall k. k -> Type)
110        type forall a (f :: forall k. k -> Type).
111             T a f = f Int
112
113- A new extension :extension:`UnliftedNewtypes` that relaxes restrictions
114  around what kinds of types can appear inside of the data constructor
115  for a ``newtype``. This was proposed in
116  `GHC proposal #13 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0013-unlifted-newtypes.rst>`__.
117
118- A new extension :extension:`ImportQualifiedPost` allows the syntax
119  ``import M qualified``, that is, to annotate a module as qualified by
120  writing ``qualified`` after the module name.
121  This was proposed in `GHC proposal #49 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0049-module-qualified-syntax.rst>`__.
122
123- New flag :ghc-flag:`-Wderiving-defaults` that controls a warning
124  message when both :extension:`DeriveAnyClass` and
125  :extension:`GeneralizedNewtypeDeriving` are enabled and no explicit
126  deriving strategy is in use. The warning is enabled by default and
127  has been present in earlier GHC versions but without the option of
128  disabling it.  For example, this code would trigger the warning: ::
129
130    class C a
131    newtype T a = MkT a deriving C
132
133- GHC now performs more validity checks on inferred type signatures. One
134  consequence of this change is that some programs that used to be accepted
135  will no longer compile without enabling the required language extensions.
136  For example, in these two modules: ::
137
138    {-# LANGUAGE RankNTypes #-}
139    module A where
140
141      foo :: (forall a. a -> a) -> b -> b
142      foo f x = f x
143
144    module B where
145
146      import A
147
148      bar = foo
149
150  Notice that ``A`` enables :ghc-flag:`-XRankNTypes`, but ``B`` does not.
151  Previous versions of GHC would allow ``bar`` to typecheck, even though its
152  inferred type is higher-rank. GHC 8.10 will now reject this, as one must now
153  enable :ghc-flag:`-XRankNTypes` in ``B`` to accept the inferred type signature.
154
155- Type family dependencies (also known as injective type families)
156  sometimes now need :ghc-flag:`-XUndecidableInstances` in order to be
157  accepted. Here is an example::
158
159    type family F1 a = r | r -> a
160    type family F2 a = r | r -> a
161    type instance F2 [a] = Maybe (F1 a)
162
163  Because GHC needs to look under a type family to see that ``a`` is determined
164  by the right-hand side of ``F2``\'s equation, this now needs :ghc-flag:`-XUndecidableInstances`.
165  The problem is very much akin to its need to detect some functional dependencies.
166
167- The pattern-match coverage checker received a number of improvements wrt.
168  correctness and performance.
169
170  Checking against user-defined COMPLETE pragmas
171  "just works" now, so that we could move away from the
172  `complicated procedure for disambiguation <https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html#disambiguating-between-multiple-complete-pragmas>`__
173  we had in place before.
174
175  Previously, the checker performed really badly on some inputs and had no
176  good story for graceful degradation in these situations. These situations
177  should occur much less frequently now and degradation happens much more
178  smoothly, while still producing useful, sound results (see
179  :ghc-flag:`-fmax-pmcheck-models=⟨n⟩`).
180
181Compiler
182~~~~~~~~
183
184- The :ghc-flag:`LLVM backend <-fllvm>` of this release is to be used with LLVM 9.
185
186- (x86) Native code generator support for legacy x87 floating point coprocessor
187  has been removed. From this point forth GHC will only support floating point
188  via SSE2.
189
190- New :ghc-flag:`-Wunused-packages` warning reports unused packages.
191
192- Add new flags :ghc-flag:`-Wunused-record-wildcards` and
193  :ghc-flag:`-Wredundant-record-wildcards`  which warn users when they have
194  redundant or unused uses of a record wildcard match.
195
196- Calls to ``memset`` and ``memcpy`` are now unrolled more aggressively
197  and the produced code is more efficient on x86-64 with added
198  support for 64-bit ``MOV``\s. In particular, ``setByteArray#`` and
199  ``copyByteArray#`` calls that were not optimized before, now will
200  be. See :ghc-ticket:`16052`.
201
202- When loading modules that use :extension:`UnboxedTuples` or
203  :extension:`UnboxedSums` into GHCi, it will now automatically enable
204  :ghc-flag:`-fobject-code` for these modules and all modules they depend on.
205  Before this change, attempting to load these modules into the interpreter
206  would just fail, and the only convenient workaround was to enable
207  :ghc-flag:`-fobject-code` for all modules. See the
208  :ref:`GHCi FAQ <ghci-faq>` for further details.
209
210- The eventlog now contains events for biographical and retainer profiling.
211  The biographical profiling events all appear at the end of the eventlog but
212  the sample start event contains a timestamp of when the census occurred.
213  The retainer profiling events are emitted using the standard events.
214
215- The eventlog now records the cost centre stack on each profiler sample. This
216  enables the ``.prof`` file to be partially reconstructed from the eventlog.
217
218- Add new flag :ghc-flag:`-fkeep-going` which makes the compiler
219  continue as far as it can despite errors.
220
221- Deprecated flag ``-fwarn-hi-shadowing`` because it was not
222  implemented correctly, and appears to be largely unused. This flag
223  will be removed in a later version of GHC.
224
225- Windows bindist has been updated to GCC 9.2 and binutils 2.32.  These binaries have
226  been patched to no longer have have the ``MAX_PATH`` limit.  Windows users
227  should no longer have any issues with long path names.
228
229- Introduce ``DynFlags`` plugins, that allow users to modidy the ``DynFlags``
230  that GHC is going to use when processing a set of files, from plugins.
231  They can be used for applying tiny configuration changes, registering hooks
232  and much more. See the :ref:`user guide <dynflags_plugins>` for
233  more details as well as an example.
234
235- Deprecated flag ``-fmax-pmcheck-iterations`` in favor of
236  :ghc-flag:`-fmax-pmcheck-models=⟨n⟩`, which uses a completely different mechanism.
237
238- GHC now writes ``.o`` files atomically, resulting in reduced chances
239  of truncated files when a build is cancelled or the computer crashes.
240
241  This fixes numerous bug reports in Stack and Cabal where GHC was not
242  able to recover from such situations by itself and users reported having
243  to clean the build directory.
244
245  Other file types are not yet written atomically.
246  Users that observe related problems should report them on
247  `GHC issue #14533 <https://gitlab.haskell.org/ghc/ghc/issues/14533>`__.
248  This fix is part of the
249  `Stack initiative to get rid of persistent build errors due to non-atomic
250  file writes across the Haskell tooling ecosystem
251  <https://github.com/commercialhaskell/stack/issues/4559>`__.
252
253GHC API
254~~~~~~~
255
256- GHC's runtime linker no longer uses global state. This allows programs
257  that use the GHC API to safely use multiple GHC sessions in a single
258  process, as long as there are no native dependencies that rely on
259  global state.
260
261- In the process of making GHC's codebase more modular, many modules have been
262  renamed to better reflect the different phases of the compiler. See
263  :ghc-ticket:`13009`. Programs that rely on the previous GHC API may use the
264  `ghc-api-compat <https://hackage.haskell.org/package/ghc-api-compat>`_ package
265  to make the transition to the new interface easier. The renaming process is
266  still going on so you must expect other similar changes in the next major
267  release.
268
269GHCi
270~~~~
271
272- Added a command :ghci-cmd:`:instances` to show the class instances available for a type.
273
274- Added new debugger commands :ghci-cmd:`:disable` and :ghci-cmd:`:enable` to
275  disable and re-enable breakpoints.
276
277- Improved command name resolution with option ``!``. For example, ``:k!``
278  resolves to ``:kind!``.
279
280Runtime system
281~~~~~~~~~~~~~~
282
283- The runtime system linker now marks loaded code as non-writable (see
284  :ghc-ticket:`14069`) on all tier-1 platforms. This is necessary for
285  out-of-the-box compatibility with OpenBSD and macOS Catalina (see
286  :ghc-ticket:`17353`)
287
288- The RTS API now exposes :ref:`an interface <event_log_output_api>` to
289  configure ``EventLogWriters``, allowing eventlog data to be fed to sinks
290  other than ``.eventlog`` files.
291
292- A new ``+RTS`` flag ``--disable-delayed-os-memory-return`` was added to make
293  for accurate resident memory usage of the program as shown in memory
294  usage reporting tools (e.g. the ``RSS`` column in ``top`` and ``htop``).
295
296  This makes it easier to check the real memory usage of Haskell programs.
297
298  Using this new flag is expected to make the program slightly slower.
299
300  Without this flag, the (Linux) RTS returns unused memory "lazily" to the OS.
301  This makes the memory available to other processes while also allowing the
302  RTS to re-use the memory very efficiently (without zeroing pages) in case it
303  needs it again, but common tools will incorrectly show such memory as
304  occupied by the RTS (because they do not process the ``LazyFree`` field in
305  ``/proc/PID/smaps``).
306
307Template Haskell
308~~~~~~~~~~~~~~~~
309
310- The ``Lift`` typeclass is now levity-polymorphic and has a ``liftTyped``
311  method. Previously disallowed instances for unboxed tuples, unboxed sums, and
312  primitive unboxed types have also been added. Finally, the code generated by
313  :extension:`DeriveLift` has been simplified to take advantage of expression
314  quotations.
315
316- Using ``TupleT 1``, ``TupE [exp]``, or ``TupP [pat]`` will now produce unary
317  tuples (i.e., involving the ``Unit`` type from ``GHC.Tuple``) instead of
318  silently dropping the parentheses. This brings Template Haskell's treatment
319  of boxed tuples in line with that of unboxed tuples, as ``UnboxedTupleT``,
320  ``UnboxedTupE``, and ``UnboxedTupP`` also produce unary unboxed tuples
321  (i.e., ``Unit#``) when applied to only one argument.
322
323- GHC's constraint solver now solves constraints in each top-level group
324  sooner. This has practical consequences for Template Haskell, as TH splices
325  necessarily separate top-level groups. For example, the following program
326  would compile in previous versions of GHC, but not in GHC 8.10: ::
327
328    data T = MkT
329
330    tStr :: String
331    tStr = show MkT
332
333    $(return [])
334
335    instance Show T where
336      show MkT = "MkT"
337
338  This is because each top-level group's constraints are solved before moving
339  on to the next, and since the top-level group for ``tStr`` appears before the
340  top-level group that defines a ``Show T`` instance, GHC 8.10 will throw an
341  error about a missing ``Show T`` instance in the expression ``show MkT``. The
342  issue can be fixed by rearranging the order of declarations. For instance,
343  the following will compile: ::
344
345    data T = MkT
346
347    instance Show T where
348      show MkT = "MkT"
349
350    $(return [])
351
352    tStr :: String
353    tStr = show MkT
354
355- TH splices by default don't generate warnings anymore. For example,
356  ``$([d| f :: Int -> void; f x = case x of {} |])`` used to generate a
357  pattern-match exhaustivity warning, which now it doesn't. The user can
358  activate warnings for TH splices with :ghc-flag:`-fenable-th-splice-warnings`.
359  The reason for opt-in is that the offending code might not have been generated
360  by code the user has control over, for example the ``singletons`` or ``lens``
361  library.
362
363``ghc-prim`` library
364~~~~~~~~~~~~~~~~~~~~
365
366- Add new ``bitReverse#`` primops that, for a ``Word`` of 8, 16, 32 or 64 bits,
367  reverse the order of its bits e.g. ``0b110001`` becomes ``0b100011``.
368  These primitives use optimized machine instructions when available.
369
370``ghc`` library
371~~~~~~~~~~~~~~~
372
373``base`` library
374~~~~~~~~~~~~~~~~
375
376Build system
377~~~~~~~~~~~~
378
379- Countless bug fixes in the new Hadrian build system
380
381- Hadrian now supports a simple key-value configuration language, eliminating
382  the need for users to use Haskell to define build configuration. This should
383  simplify life for packagers and users alike. See :ghc-ticket:`16769` and the
384  documentation in ``hadrian/doc/user-settings.md``.
385
386Included libraries
387------------------
388
389The package database provided with this distribution also contains a number of
390packages other than GHC itself. See the changelogs provided with these packages
391for further change information.
392
393.. ghc-package-list::
394
395    libraries/array/array.cabal:             Dependency of ``ghc`` library
396    libraries/base/base.cabal:               Core library
397    libraries/binary/binary.cabal:           Dependency of ``ghc`` library
398    libraries/bytestring/bytestring.cabal:   Dependency of ``ghc`` library
399    libraries/Cabal/Cabal/Cabal.cabal:       Dependency of ``ghc-pkg`` utility
400    libraries/containers/containers/containers.cabal:   Dependency of ``ghc`` library
401    libraries/deepseq/deepseq.cabal:         Dependency of ``ghc`` library
402    libraries/directory/directory.cabal:     Dependency of ``ghc`` library
403    libraries/exceptions/exceptions.cabal:   Dependency of ``haskeline`` library
404    libraries/filepath/filepath.cabal:       Dependency of ``ghc`` library
405    compiler/ghc.cabal:                      The compiler itself
406    libraries/ghci/ghci.cabal:               The REPL interface
407    libraries/ghc-boot/ghc-boot.cabal:       Internal compiler library
408    libraries/ghc-boot-th/ghc-boot-th.cabal: Internal compiler library
409    libraries/ghc-compact/ghc-compact.cabal: Core library
410    libraries/ghc-heap/ghc-heap.cabal:       GHC heap-walking library
411    libraries/ghc-prim/ghc-prim.cabal:       Core library
412    libraries/haskeline/haskeline.cabal:     Dependency of ``ghci`` executable
413    libraries/hpc/hpc.cabal:                 Dependency of ``hpc`` executable
414    libraries/integer-gmp/integer-gmp.cabal: Core library
415    libraries/libiserv/libiserv.cabal:       Internal compiler library
416    libraries/mtl/mtl.cabal:                 Dependency of ``Cabal`` library
417    libraries/parsec/parsec.cabal:           Dependency of ``Cabal`` library
418    libraries/pretty/pretty.cabal:           Dependency of ``ghc`` library
419    libraries/process/process.cabal:         Dependency of ``ghc`` library
420    libraries/stm/stm.cabal:                 Dependency of ``haskeline`` library
421    libraries/template-haskell/template-haskell.cabal:     Core library
422    libraries/terminfo/terminfo.cabal:       Dependency of ``haskeline`` library
423    libraries/text/text.cabal:               Dependency of ``Cabal`` library
424    libraries/time/time.cabal:               Dependency of ``ghc`` library
425    libraries/transformers/transformers.cabal: Dependency of ``ghc`` library
426    libraries/unix/unix.cabal:               Dependency of ``ghc`` library
427    libraries/Win32/Win32.cabal:             Dependency of ``ghc`` library
428    libraries/xhtml/xhtml.cabal:             Dependency of ``haddock`` executable
429