summaryrefslogtreecommitdiff
path: root/docs/users_guide/9.2.1-notes.rst
diff options
context:
space:
mode:
Diffstat (limited to 'docs/users_guide/9.2.1-notes.rst')
-rw-r--r--docs/users_guide/9.2.1-notes.rst423
1 files changed, 0 insertions, 423 deletions
diff --git a/docs/users_guide/9.2.1-notes.rst b/docs/users_guide/9.2.1-notes.rst
deleted file mode 100644
index fa9214aa8d..0000000000
--- a/docs/users_guide/9.2.1-notes.rst
+++ /dev/null
@@ -1,423 +0,0 @@
-.. _release-9-2-1:
-
-Version 9.2.1
-==============
-
-Language
-~~~~~~~~
-
-* :extension:`ImpredicativeTypes`: Finally, polymorphic types have become first class!
- GHC 9.2 includes a full implementation of the Quick Look approach to type inference for
- impredicative types, as described in in the paper
- `A quick look at impredicativity
- <https://www.microsoft.com/en-us/research/publication/a-quick-look-at-impredicativity/>`__
- (Serrano et al, ICFP 2020). More information here: :ref:`impredicative-polymorphism`.
- This replaces the old (undefined, flaky) behaviour of the :extension:`ImpredicativeTypes` extension.
-
-* The first stage of the `Pointer Rep Proposal`_ has been implemented. All
- boxed types, both lifted and unlifted, now have representation kinds of
- the shape ``BoxedRep r``. Code that references ``LiftedRep`` and ``UnliftedRep``
- will need to be updated.
-
-.. _Pointer Rep Proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0203-pointer-rep.rst
-
-* :extension:`UnliftedDatatypes`: The `Unlifted Datatypes Proposal`_ has been
- implemented. That means GHC Haskell now offers a way to define algebraic
- data types with strict semantics like in OCaml or Idris! The distinction to
- ordinary lifted data types is made in the kind system: Unlifted data types
- live in kind ``TYPE (BoxedRep Unlifted)``. :extension:`UnliftedDatatypes`
- allows giving data declarations such result kinds, such as in the following
- example with the help of :extension:`StandaloneKindSignatures`: ::
-
- type IntSet :: UnliftedType -- type UnliftedType = TYPE (BoxedRep Unlifted)
- data IntSet = Branch IntSet !Int IntSet | Leaf
-
- See :extension:`UnliftedDatatypes` for what other declarations are
- possible. Slight caveat: Most functions in ``base`` (including ``$``)
- are not levity-polymorphic (yet) and hence won't work with unlifted
- data types.
-
-.. _Unlifted Datatypes Proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0265-unlifted-datatypes.rst
-
-* Kind inference for data/newtype instance declarations is slightly more restrictive than before.
- In particular, GHC now requires that the kind of a data family instance be fully determined
- by the header of the instance, without looking at the definition of the constructor.
-
- This means that data families that dispatched on an invisible parameter might now require this parameter
- to be made explicit, as in the following example: ::
-
- data family DF :: forall (r :: RuntimeRep). TYPE r
- newtype instance DF @IntRep = MkDF2 Int#
- newtype instance DF @FloatRep = MkDF1 Float#
-
- See the user manual :ref:`kind-inference-data-family-instances`.
-
-* GHC is stricter about checking for out-of-scope type variables on the
- right-hand sides of associated type family instances that are not bound on
- the left-hand side. As a result, some programs that were accidentally
- accepted in previous versions of GHC will now be rejected, such as this
- example: ::
-
- class Funct f where
- type Codomain f
- instance Funct ('KProxy :: KProxy o) where
- type Codomain 'KProxy = NatTr (Proxy :: o -> Type)
-
- Where: ::
-
- data Proxy (a :: k) = Proxy
- data KProxy (t :: Type) = KProxy
- data NatTr (c :: o -> Type)
-
- GHC will now reject the ``o`` on the right-hand side of the ``Codomain``
- instance as being out of scope, as it does not meet the requirements for
- being explicitly bound (as it is not mentioned on the left-hand side) nor
- implicitly bound (as it is not mentioned in an *outermost* kind signature,
- as required by :ref:`scoping-class-params`). This program can be repaired in
- a backwards-compatible way by mentioning ``o`` on the left-hand side: ::
-
- instance Funct ('KProxy :: KProxy o) where
- type Codomain ('KProxy @o) = NatTr (Proxy :: o -> Type)
- -- Alternatively,
- -- type Codomain ('KProxy :: KProxy o) = NatTr (Proxy :: o -> Type)
-
-* Previously, ``-XUndecidableInstances`` accidentally implied ``-XFlexibleContexts``.
- This is now fixed, but it means that some programs will newly require
- ``-XFlexibleContexts``.
-
-* The :extension:`GHC2021` language is supported now. It builds on top of
- Haskell2010, adding several stable and conservative extensions, and removing
- deprecated ones. It is now also the “default” language set that is active
- when no other language set, such as :extension:`Haskell98` or
- :extension:`Haskell2010`, is explicitly loaded (e.g via Cabal’s
- ``default-language``).
-
- Because :extension:`GHC2021` includes
- :extension:`GeneralizedNewtypeDeriving`, which is not safe for Safe Haskell,
- users of Safe Haskell are advised to use :extension:`Haskell2010` explicitly.
-
- The default mode of GHC until 9.0 included
- :extension:`NondecreasingIndentation`, but :extension:`GHC2021` does not.
- This may break code implicitly using this extension.
-
-* The `Record Dot Syntax Proposal`_ has been implemented:
-
- - A new extension :extension:`OverloadedRecordDot` provides record ``.`` syntax e.g. ``x.foo``
- - A new extension :extension:`OverloadedRecordUpdate` provides record ``.``
- syntax in record updates e.g. ``x{foo.bar = 1}``. *The design of this
- extension may well change in the future.*
-
-.. _Record Dot Syntax Proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0282-record-dot-syntax.rst
-
-* Various records-related extensions have been improved:
-
- - A new extension :extension:`NoFieldSelectors` hides record field selector
- functions, so it is possible to define top-level bindings with the same names.
-
- - The :extension:`DisambiguateRecordFields` extension now works for updates.
- An update ``expr { field = value }`` will be accepted if there is a single
- field called ``field`` in scope, regardless of whether there are non-fields
- in scope with the same name.
-
- - The :extension:`DuplicateRecordFields` extension now applies to fields in
- record pattern synonyms. In particular, it is possible for a single module
- to define multiple pattern synonyms using the same field names.
-
-* Because of simplifications to the way that GHC typechecks operator sections,
- operators with nested ``forall``\ s or contexts in their type signatures might
- not typecheck when used in a section. For instance, the ``g`` function below,
- which was accepted in previous GHC releases, will no longer typecheck: ::
-
- f :: a -> forall b. b -> a
- f x _ = x
-
- g :: a -> a
- g = (`f` "hello")
-
- ``g`` can be made to typecheck once more by eta expanding it to
- ``\x -> x `f` "hello"``. For more information, see
- :ref:`simple-subsumption`.
-
-* :extension:`LinearTypes` can now infer multiplicity for ``case``
- expressions. Previously, the scrutinee of a ``case`` (the bit between ``case``
- and ``of``) was always assumed to have a multiplicity of ``Many``. Now, GHC
- will allow the scrutinee to have a multiplicity of ``One``, using its best-effort
- inference algorithm.
-
-* Support for matching on GADT constructors in arrow notation has been removed,
- as the current implementation of :extension:`Arrows` doesn't handle GADT
- evidence correctly.
-
- One possible workaround, for the time being, is to perform GADT matches
- inside let bindings: ::
-
- data G a where
- MkG :: Show a => a -> G a
-
- foo :: G a -> String
- foo = proc x -> do
- let res = case x of { MkG a -> show a }
- returnA -< res
-
-Compiler
-~~~~~~~~
-
-- Performance of the compiler in :ghc-flag:`--make` mode with :ghc-flag:`-j[⟨n⟩]`
- is significantly improved by improvements to the parallel
- garbage collector noted below.
-
- Benchmarks show a 20% decrease in wall clock time, and a 40% decrease in cpu
- time, when compiling Cabal with ``-j4`` on linux. Improvements are more dramatic
- with higher parallelism, and we no longer see significant degradation in wall
- clock time as parallelism increases above 4.
-
-- New :ghc-flag:`-Wredundant-bang-patterns` flag that enables checks for "dead" bangs.
- For instance, given this program: ::
-
- f :: Bool -> Bool
- f True = False
- f !x = x
-
- GHC would report that the bang on ``x`` is redundant and can be removed
- since the argument was already forced in the first equation. For more
- details see :ghc-flag:`-Wredundant-bang-patterns`.
-
-- New :ghc-flag:`-Wimplicit-lift` flag which warns when a Template Haskell quote
- implicitly uses ``lift``.
-
-- New :ghc-flag:`-finline-generics` and
- :ghc-flag:`-finline-generics-aggressively` flags for improving performance of
- generics-based algorithms.
-
- For more details see :ghc-flag:`-finline-generics` and
- :ghc-flag:`-finline-generics-aggressively`.
-
-- GHC now supports a flag, :ghc-flag:`-fprof-callers=⟨name⟩`, for requesting
- that the compiler automatically insert cost-centres on all call-sites of
- the named function.
-
-- The heap profiler can now be controlled from within a Haskell program using
- functions in ``GHC.Profiling``. Profiling can be started and stopped or a heap
- census requested at a specific point in the program.
- There is a new RTS flag :rts-flag:`--no-automatic-heap-samples` which can be
- used to stop heap profiling starting when a program starts.
-
-- A new debugging facility, :ghc-flag:`-finfo-table-map`, which embeds a mapping
- from the address of an info table to information about that info table, including
- an approximate source position. :ghc-flag:`-fdistinct-constructor-tables` is
- also useful with this flag to give each usage of a data constructor its own
- unique info table so they can be distinguished in gdb and heap profiles.
-
-GHCi
-~~~~
-
-- GHCi's ``:kind!`` command now expands through type synonyms in addition to
- type families. See :ghci-cmd:`:kind`.
-
-- GHCi's :ghci-cmd:`:edit` command now looks for an editor in
- the :envvar:`VISUAL` environment variable before
- :envvar:`EDITOR`, following UNIX convention.
- (:ghc-ticket:`19030`)
-
-- GHC now follows by default the XDG Base Directory Specification. If
- ``$HOME/.ghc`` is found it will fallback to the old paths to give you
- time to migrate. This fallback will be removed in three releases.
-
-- New debugger command :ghci-cmd:`:ignore` to set an ``ignore count`` for a
- specified breakpoint. The next ``ignore count`` times the program hits this
- breakpoint, the breakpoint is ignored, and the program doesn't stop.
-
-- New optional parameter added to the command :ghci-cmd:`:continue` to set the
- ``ignore count`` for the current breakpoint.
-
-Runtime system
-~~~~~~~~~~~~~~
-
-- The parallel garbage collector is now significantly more performant. Heavily
- contended spinlocks have been replaced with mutexes and condition variables.
- For most programs compiled with the threaded runtime, and run with more than
- four capabilities, we expect minor GC pauses and GC cpu time both to be reduced.
-
- For very short running programs (in the order of 10s of milliseconds), we have seen
- some performance regressions. We recommend programs affected by this to either
- compile with the single threaded runtime, or otherwise to disable the parallel
- garbage collector with :rts-flag:`-qg ⟨gen⟩`.
-
- We don't expect any other performance regressions, however only limited
- benchmarking has been done. We have only benchmarked GHC and nofib and only on
- linux.
-
- Users are advised to reconsider the rts flags that programs are run with. If
- you have been mitigating poor parallel GC performance by: using large
- nurseries (:rts-flag:`-A <-A ⟨size⟩>`), disabling load balancing (:rts-flag:`-qb ⟨gen⟩`), or
- limiting parallel GC to older generations (:rts-flag:`-qg ⟨gen⟩`); then you may
- find these mitigations are no longer necessary.
-
-- The heap profiler now has proper treatment of pinned ``ByteArray#``\ s. Such
- heap objects will now be correctly attributed to their appropriate cost
- centre instead of merely being lumped into the ``PINNED`` category.
- Moreover, we now correctly account for the size of the array, meaning that
- space lost to fragmentation is no longer counted as live data.
-
-- The ``-xt`` RTS flag has been removed. Now STACK and TSO closures are always
- included in heap profiles. Tooling can choose to filter out these closure types
- if necessary.
-
-- A new heap profiling mode, :rts-flag:`-hi`, profile by info table allows for
- fine-grain banding by the info table address of a closure. The profiling
- mode is intended to be used with :ghc-flag:`-finfo-table-map` and can best
- be consumed with ``eventlog2html``. This profiling mode does not require a
- profiling build.
-
-- The RTS will now gradually return unused memory back to the OS rather than
- retaining a large amount (up to 4 * live) indefinitely. The rate at which memory
- is returned is controlled by the :rts-flag:`-Fd ⟨factor⟩`. Memory return
- is triggered by consecutive idle collections.
-
-- The default nursery size, :rts-flag:`-A <-A ⟨size⟩>`, has been increased from
- 1mb to 4mb.
-
-Template Haskell
-~~~~~~~~~~~~~~~~
-
-- There are two new functions ``putDoc`` and ``getDoc``, which allow Haddock
- documentation to be attached and read from module headers, declarations,
- function arguments, class instances and family instances.
- These functions are quite low level, so the ``withDecDoc`` function provides
- a more ergonomic interface for this. Similarly ``funD_doc``, ``dataD_doc``
- and friends provide an easy way to document functions and constructors
- alongside their arguments simultaneously. ::
-
- $(withDecsDoc "This does good things" [d| foo x = 42 |])
-
-``ghc-prim`` library
-~~~~~~~~~~~~~~~~~~~~
-
-- ``Void#`` is now a type synonym for the unboxed tuple ``(# #)``.
- Code using ``Void#`` now has to enable :extension:`UnboxedTuples`.
-
-Eventlog
-~~~~~~~~
-
-- Two new events, :event-type:`BLOCKS_SIZE` tells you about the total size of
- all allocated blocks and :event-type:`MEM_RETURN` gives statistics about why
- the OS is returning and retaining megablocks.
-
-``ghc`` library
-~~~~~~~~~~~~~~~
-
-- There is a significant refactoring in the solver; any type-checker plugins
- will have to be updated, as GHC no longer uses flattening skolems or
- flattening metavariables.
-
-- Type checker plugins which work with the natural numbers now
- should use ``naturalTy`` kind instead of ``typeNatKind``, which has been removed.
-
-- The ``con_args`` field of ``ConDeclGADT`` has been renamed to ``con_g_args``.
- This is because the type of ``con_g_args`` is now different from the type of
- the ``con_args`` field in ``ConDeclH98``: ::
-
- data ConDecl pass
- = ConDeclGADT
- { ...
- , con_g_args :: HsConDeclGADTDetails pass -- ^ Arguments; never infix
- , ...
- }
-
- | ConDeclH98
- { ...
- , con_args :: HsConDeclH98Details pass -- ^ Arguments; can be infix
- , ...
- }
-
- Where: ::
-
- -- Introduced in GHC 9.2; was called `HsConDeclDetails` in previous versions of GHC
- type HsConDeclH98Details pass
- = HsConDetails (HsScaled pass (LBangType pass)) (XRec pass [LConDeclField pass])
-
- -- Introduced in GHC 9.2
- data HsConDeclGADTDetails pass
- = PrefixConGADT [HsScaled pass (LBangType pass)]
- | RecConGADT (XRec pass [LConDeclField pass])
-
- Unlike Haskell98-style constructors, GADT constructors cannot be declared
- using infix syntax, which is why ``HsConDeclGADTDetails`` lacks an
- ``InfixConGADT`` constructor.
-
- As a result of all this, the ``con_args`` field is now partial, so using
- ``con_args`` as a top-level field selector is discouraged.
-
-``base`` library
-~~~~~~~~~~~~~~~~
-
-- Character set metadata bumped to Unicode 13.0.0.
-
-- It's possible now to promote the ``Natural`` type: ::
-
- data Coordinate = Mk2D Natural Natural
- type MyCoordinate = Mk2D 1 10
-
- The separate kind ``Nat`` is removed and now it is just a type synonym for
- ``Natural``. As a consequence, one must enable ``TypeSynonymInstances``
- in order to define instances for ``Nat``.
-
- The ``Numeric`` module receives ``showBin`` and ``readBin`` to show and
- read integer numbers in binary.
-
-- ``Char`` gets type-level support by analogy with strings and natural numbers.
- We extend the ``GHC.TypeLits`` module with these built-in type-families: ::
-
- type family CmpChar (a :: Char) (b :: Char) :: Ordering
- type family ConsSymbol (a :: Char) (b :: Symbol) :: Symbol
- type family UnconsSymbol (a :: Symbol) :: Maybe (Char, Symbol)
- type family CharToNat (c :: Char) :: Natural
- type family NatToChar (n :: Natural) :: Char
-
- and with the type class ``KnownChar`` (and such additional functions as ``charVal`` and ``charVal'``): ::
-
- class KnownChar (n :: Char)
-
- charVal :: forall n proxy. KnownChar n => proxy n -> Char
- charVal' :: forall n. KnownChar n => Proxy# n -> Char
-
-- A new kind-polymorphic ``Compare`` type family was added in ``Data.Type.Ord``
- and has type instances for ``Nat``, ``Symbol``, and ``Char``. Furthermore,
- the ``(<=?)`` type (and ``(<=)``) from ``GHC.TypeNats`` is now governed by
- this type family (as well as new comparison type operators that are exported
- by ``Data.Type.Ord``). This has two important repercussions. First, GHC can
- no longer deduce that all natural numbers are greater than or equal to zero.
- For instance, ::
-
- test1 :: Proxy (0 <=? x) -> Proxy True
- test1 = id
-
- which previously type checked will now result in a type error. Second, when
- these comparison type operators are used very generically, a kind may need to
- be provided. For example, ::
-
- test2 :: Proxy (x <=? x) -> Proxy True
- test2 = id
-
- will now generate a type error because GHC does not know the kind of ``x``.
- To fix this, one must provide an explicit kind, perhaps by changing the type
- to: ::
-
- test2 :: forall (x :: Nat). Proxy (x <=? x) -> Proxy True
-
-- On POSIX, ``System.IO.openFile`` can no longer leak a file descriptor if it
- is interrupted by an asynchronous exception (:ghc-ticket:`19114`, :ghc-ticket:`19115`).
-
-- There's a new binding ``GHC.Exts.considerAccessible``. It's equivalent to
- ``True`` and allows the programmer to turn off pattern-match redundancy
- warnings for particular clauses, like the third one here ::
-
- g :: Bool -> Int
- g x = case (x, x) of
- (True, True) -> 1
- (False, False) -> 2
- (True, False) | considerAccessible -> 3 -- No warning!
-
-- A new ``GHC.TypeError`` module is created which exposes functionality related
- to custom type errors. ``TypeError`` is re-exported from ``GHC.TypeLits`` for
- backwards compatibility.