Florian Ragwitz pushed to branch wip/rafl/cover-data at Glasgow Haskell Compiler / GHC

Commits:

3 changed files:

Changes:

  • docs/users_guide/9.14.1-notes.rst deleted
    1
    -.. _release-9-14-1:
    
    2
    -
    
    3
    -Version 9.14.1
    
    4
    -==============
    
    5
    -
    
    6
    -The significant changes to the various parts of the compiler are listed in the
    
    7
    -following sections. See the `migration guide
    
    8
    -<https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.14>`_ on the GHC Wiki
    
    9
    -for specific guidance on migrating programs to this release.
    
    10
    -
    
    11
    -Language
    
    12
    -~~~~~~~~
    
    13
    -
    
    14
    -* `GHC proposal 493: allow expressions in SPECIALISE pragmas <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0493-specialise-expressions.rst>`_
    
    15
    -  has been implemented. SPECIALISE pragmas now allow arbitrary expressions such as: ::
    
    16
    -
    
    17
    -    {-# SPECIALISE f @Int False :: Int -> Char #-}
    
    18
    -
    
    19
    -  The ability to specify multiple specialisations in a single SPECIALISE pragma,
    
    20
    -  with syntax of the form (note the comma between the type signatures): ::
    
    21
    -
    
    22
    -    {-# SPECIALISE g : Int -> Int, Float -> Float #-}
    
    23
    -
    
    24
    -  has been deprecated, and is scheduled to be removed in GHC 9.18.
    
    25
    -  This deprecation is controlled by the newly introduced ``-Wdeprecated-pragmas``
    
    26
    -  flag in ``-Wdefault``.
    
    27
    -
    
    28
    -* ``-Wincomplete-record-selectors`` is now part of `-Wall`, as specified
    
    29
    -  by `GHC Proposal 516: add warning for incomplete record selectors <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0516-incomplete-record-selectors.rst>`_.
    
    30
    -  Hence, if a library is compiled with ``-Werror``, compilation may now fail. Solution: fix the library.
    
    31
    -  Workaround: add ``-Werror=no-incomplete-record-selectors``.
    
    32
    -
    
    33
    -  Note that this warning is at least
    
    34
    -  as serious as a warning about missing patterns from a function definition, perhaps even
    
    35
    -  more so, since it is invisible in the source program.
    
    36
    -
    
    37
    -* The combination of :extension:`ScopedTypeVariables` and :extension:`TypeApplications`
    
    38
    -  no longer enables type applications in patterns, which now always requires
    
    39
    -  :extension:`TypeAbstractions`. The warning flag``deprecated-type-abstractions``
    
    40
    -  has also been removed from the compiler.
    
    41
    -
    
    42
    -* :extension:`OverloadedRecordUpdate` now passes the arguments to a ``setField`` function
    
    43
    -  in the flipped order, as specified by `GHC Proposal 583: HasField redesign <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0583-hasfield-redesign.rst>`_.
    
    44
    -
    
    45
    -  Previously GHC expected ``setField`` to have this type: ::
    
    46
    -
    
    47
    -    setField :: forall (fld :: Symbol) a r. r -> a -> r
    
    48
    -
    
    49
    -  And that's what GHC expects now: ::
    
    50
    -
    
    51
    -    setField :: forall (fld :: Symbol) a r. a -> r -> r
    
    52
    -
    
    53
    -  That will break the combination of :extension:`OverloadedRecordUpdate` with :extension:`RebindableSyntax`.
    
    54
    -
    
    55
    -* Multiline strings are now accepted in foreign imports. (#25157)
    
    56
    -
    
    57
    -* GHC now does a better job at inferring types in calls to ``coerce``: instead of
    
    58
    -  complaining about ambiguous type variables, GHC will consider that such type
    
    59
    -  variables are determined by the ``Coercible`` constraints they appear in.
    
    60
    -
    
    61
    -* With :extension:`LinearTypes` record fields can now be non-linear. This means that
    
    62
    -  the following record declaration is now valid:
    
    63
    -
    
    64
    -  ::
    
    65
    -
    
    66
    -      data Record = Rec { x %'Many :: Int, y :: Char }
    
    67
    -
    
    68
    -  This causes the constructor to have type ``Rec :: Int %'Many -> Char %1 -> Record``.
    
    69
    -
    
    70
    -* The :extension:`ExplicitNamespaces` extension now allows the ``data``
    
    71
    -  namespace specifier in import and export lists.
    
    72
    -
    
    73
    -* The ``-Wdata-kinds-tc`` warning has been deprecated, and the use of promoted
    
    74
    -  data types in kinds is now an error (rather than a warning) unless the
    
    75
    -  :extension:`DataKinds` extension is enabled. For example, the following code
    
    76
    -  will be rejected unless :extension:`DataKinds` is on:
    
    77
    -
    
    78
    -    import Data.Kind (Type)
    
    79
    -    import GHC.TypeNats (Nat)
    
    80
    -
    
    81
    -    -- Nat shouldn't be allowed here without DataKinds
    
    82
    -    data Vec :: Nat -> Type -> Type
    
    83
    -
    
    84
    -  (The ``-Wdata-kinds-tc`` warning was introduced in GHC 9.10 as part of a fix
    
    85
    -  for an accidental oversight in which programs like the one above were
    
    86
    -  mistakenly accepted without the use of :extension:`DataKinds`.)
    
    87
    -
    
    88
    -* The :extension:`MonadComprehensions` extension now implies :extension:`ParallelListComp` as was originally intended (see `Monad Comprehensions <https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/monad_comprehensions.html>`_).
    
    89
    -
    
    90
    -* In accordance with `GHC Proposal #281 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0281-visible-forall.rst>`_,
    
    91
    -  section 4.7 "Data constructors", the :extension:`RequiredTypeArguments`
    
    92
    -  extension now allows visible forall in types of data constructors
    
    93
    -  (:ghc-ticket:`25127`). The following declaration is now accepted by GHC:
    
    94
    -
    
    95
    -  ::
    
    96
    -
    
    97
    -    data T a where
    
    98
    -      Typed :: forall a -> a -> T a
    
    99
    -
    
    100
    -  See :ref:`visible-forall-in-gadts` for details.
    
    101
    -
    
    102
    -Compiler
    
    103
    -~~~~~~~~
    
    104
    -
    
    105
    -- 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)
    
    106
    -
    
    107
    -- The kind checker now does a better job of finding type family instances for
    
    108
    -  use in the kinds of other declarations in the same module. This fixes a number
    
    109
    -  of tickets:
    
    110
    -  :ghc-ticket:`12088`, :ghc-ticket:`12239`, :ghc-ticket:`14668`, :ghc-ticket:`15561`,
    
    111
    -  :ghc-ticket:`16410`, :ghc-ticket:`16448`, :ghc-ticket:`16693`, :ghc-ticket:`19611`,
    
    112
    -  :ghc-ticket:`20875`, :ghc-ticket:`21172`, :ghc-ticket:`22257`, :ghc-ticket:`25238`,
    
    113
    -  :ghc-ticket:`25834`.
    
    114
    -
    
    115
    -- The compiler no longer accepts invalid ``type`` namespace specifiers in
    
    116
    -  subordinate import lists (:ghc-ticket:`22581`).
    
    117
    -
    
    118
    -- A new flag, :ghc-flag:`-Wuseless-specialisations`, controls warnings emitted when GHC
    
    119
    -  determines that a SPECIALISE pragma would have no effect.
    
    120
    -
    
    121
    -- A new flag, :ghc-flag:`-Wrule-lhs-equalities`, controls warnings emitted for RULES
    
    122
    -  whose left-hand side attempts to quantify over equality constraints that
    
    123
    -  previous GHC versions accepted quantifying over. GHC will now drop such RULES,
    
    124
    -  emitting a warning message controlled by this flag.
    
    125
    -
    
    126
    -  This warning is intended to give visibility to the fact that the RULES that
    
    127
    -  previous GHC versions generated in such circumstances could never fire.
    
    128
    -
    
    129
    -- A new flag, :ghc-flag:`-Wunusable-unpack-pragmas`, controls warnings emitted
    
    130
    -  when GHC is unable to unpack a data constructor field annotated by the
    
    131
    -  ``{-# UNPACK #-}`` pragma.
    
    132
    -
    
    133
    -  Previous GHC versions issued this warning unconditionally. Now it is possible
    
    134
    -  to disable it with ``-Wno-unusable-unpack-pragmas`` or turn it into an error
    
    135
    -  with ``-Werror=unusable-unpack-pragmas``.
    
    136
    -
    
    137
    -- Introduce a new warning :ghc-flag:`-Wpattern-namespace-specifier` to detect
    
    138
    -  uses of the now deprecated ``pattern`` namespace specifier in import/export
    
    139
    -  lists. See `GHC Proposal #581, section 2.3 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0581-namespace-specified-imports.rst#deprecate-use-of-pattern-in-import-export-lists>`_.
    
    140
    -
    
    141
    -- Code coverage (:ghc-flag:`-fhpc`) now treats uses of record fields
    
    142
    -  (including via :extension:`RecordWildCards` or :extension:`NamedFieldPuns`)
    
    143
    -  as if the fields were accessed using the generated record selector functions,
    
    144
    -  marking the fields as covered in coverage reports (:ghc-ticket:`17834`,
    
    145
    -  :ghc-ticket:`26191`). Note that this currently only works when record fields
    
    146
    -  (or values contained within them) are bound to variables, and usage of those
    
    147
    -  variables marks the record selectors as covered. That is, a pattern like
    
    148
    -  ``Foo{bar = Bar{baz = b}}`` will mark ``bar`` and ``baz`` as covered if ``b``
    
    149
    -  is used, but the similar pattern ``Foo{bar = Bar{baz = 42}}`` will mark
    
    150
    -  neither as covered.
    
    151
    -
    
    152
    -- SIMD support in the X86 native code generator has been extended with 128-bit
    
    153
    -  integer operations.  Also, ``shuffleFloatX4#`` and ``shuffleDoubleX2#`` no longer
    
    154
    -  require ``-mavx``.
    
    155
    -
    
    156
    -- JSON diagnostics produced with (:ghc-flag:`-fdiagnostics-as-json`) now
    
    157
    -  include the `rendered` diagnostics message, in the exact same format as what
    
    158
    -  GHC would have produced without -fdiagnostics-as-json (including ANSI escape
    
    159
    -  sequences).
    
    160
    -
    
    161
    -GHCi
    
    162
    -~~~~
    
    163
    -
    
    164
    -- :ghci-cmd:`:info` now outputs type declarations with @-binders that are
    
    165
    -  considered semantically significant. See the documentation for :ghci-cmd:`:info`
    
    166
    -  itself for a more detailed explanation.
    
    167
    -
    
    168
    -- GHCi errors and warnings now have their own numeric error codes that are
    
    169
    -  displayed alongside the error.
    
    170
    -
    
    171
    -Runtime system
    
    172
    -~~~~~~~~~~~~~~
    
    173
    -
    
    174
    -- Add new runtime flag :rts-flag:`--optimistic-linking` which instructs the
    
    175
    -  runtime linker to continue in the presence of unknown symbols. By default this
    
    176
    -  flag is not passed, preserving previous behavior.
    
    177
    -
    
    178
    -Cmm
    
    179
    -~~~
    
    180
    -
    
    181
    -``base`` library
    
    182
    -~~~~~~~~~~~~~~~~
    
    183
    -
    
    184
    -``ghc-prim`` library
    
    185
    -~~~~~~~~~~~~~~~~~~~~
    
    186
    -
    
    187
    -``ghc`` library
    
    188
    -~~~~~~~~~~~~~~~
    
    189
    -
    
    190
    -* The `UnknownDiagnostic` constructor now takes an additional type argument
    
    191
    -  for the type of hints corresponding to the diagnostic, and an additional
    
    192
    -  value-level argument used for existential wrapping of the hints of the inner
    
    193
    -  diagnostic.
    
    194
    -
    
    195
    -* Changes to the HPT and HUG interface:
    
    196
    -
    
    197
    -  - `addToHpt` and `addListToHPT` were moved from `GHC.Unit.Home.ModInfo` to `GHC.Unit.Home.PackageTable` and deprecated in favour of `addHomeModInfoToHpt` and `addHomeModInfosToHpt`.
    
    198
    -  - `UnitEnvGraph` and operations `unitEnv_lookup_maybe`, `unitEnv_foldWithKey, `unitEnv_singleton`, `unitEnv_adjust`, `unitEnv_insert`, `unitEnv_new` were moved from `GHC.Unit.Env` to `GHC.Unit.Home.Graph`.
    
    199
    -  - The HomePackageTable (HPT) is now exported from `GHC.Unit.Home.PackageTable`,
    
    200
    -    and is now backed by an IORef to avoid by construction very bad memory leaks.
    
    201
    -    This means the API to the HPT now is for the most part in IO. For instance,
    
    202
    -    `emptyHomePackageTable` and `addHomeModInfoToHpt` are now in IO.
    
    203
    -  - `mkHomeUnitEnv` was moved to `GHC.Unit.Home.PackageTable`, and now takes two
    
    204
    -    extra explicit arguments. To restore previous behaviour, pass `emptyUnitState`
    
    205
    -    and `Nothing` as the first two arguments additionally.
    
    206
    -  - `hugElts` was removed. Users should prefer `allUnits` to get the keys of the
    
    207
    -    HUG (the typical use case), or `traverse` or `unitEnv_foldWithKey` in other
    
    208
    -    cases.
    
    209
    -
    
    210
    -* Changes to `Language.Haskell.Syntax.Expr`
    
    211
    -
    
    212
    -  - The `ParStmtBlock` list argument of the `ParStmt` constructor of `StmtLR` is now `NonEmpty`.
    
    213
    -
    
    214
    -* As part of the implementation of `GHC proposal 493 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0493-specialise-expressions.rst>`_,
    
    215
    -  the `SpecSig` constructor of `Sig` has been deprecated. It is replaced by
    
    216
    -  the constructor `SpecSigE` which supports expressions at the head, rather than
    
    217
    -  a lone variable.
    
    218
    -
    
    219
    -``ghc-heap`` library
    
    220
    -~~~~~~~~~~~~~~~~~~~~
    
    221
    -
    
    222
    -* The functions `getClosureInfoTbl_maybe`, `getClosureInfoTbl`,
    
    223
    -  `getClosurePtrArgs` and `getClosurePtrArgs_maybe` have been added to allow
    
    224
    -  reading of the relevant Closure attributes without reliance on incomplete
    
    225
    -  selectors.
    
    226
    -
    
    227
    -``ghc-experimental`` library
    
    228
    -~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    229
    -
    
    230
    -- ``ghc-experimental`` now exposes ``GHC.RTS.Flags`` and ``GHC.Stats`` as
    
    231
    -  ``GHC.RTS.Flags.Experimental`` and ``GHC.Stats.Experimental``. These are
    
    232
    -  *also* exposed in ``base``, however the ``base`` versions will be deprecated as
    
    233
    -  part of the split base project. See `CLC proposal 289
    
    234
    -  <https://github.com/haskell/core-libraries-committee/issues/289>`__.
    
    235
    -  Downstream consumers of these flags are encouraged to migrate to the
    
    236
    -  ``ghc-experimental`` versions.
    
    237
    -
    
    238
    -
    
    239
    -
    
    240
    -``template-haskell`` library
    
    241
    -~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    242
    -
    
    243
    -- As part of the implementation of `GHC proposal 493 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0493-specialise-expressions.rst>`_,
    
    244
    -  the ``SpecialiseP`` constructor of the Template Haskell ``Pragma`` type, as
    
    245
    -  well as the helpers ``pragSpecD`` and ``pragSpecInlD``, have been deprecated.
    
    246
    -
    
    247
    -  They are replaced, respectively, by ``SpecialiseEP``, ``pragSpecED`` and
    
    248
    -  ``pragSpecInlED``.
    
    249
    -
    
    250
    -Included libraries
    
    251
    -~~~~~~~~~~~~~~~~~~
    
    252
    -
    
    253
    -The package database provided with this distribution also contains a number of
    
    254
    -packages other than GHC itself. See the changelogs provided with these packages
    
    255
    -for further change information.
    
    256
    -
    
    257
    -.. ghc-package-list::
    
    258
    -
    
    259
    -    libraries/array/array.cabal:                         Dependency of ``ghc`` library
    
    260
    -    libraries/base/base.cabal:                           Core library
    
    261
    -    libraries/binary/binary.cabal:                       Dependency of ``ghc`` library
    
    262
    -    libraries/bytestring/bytestring.cabal:               Dependency of ``ghc`` library
    
    263
    -    libraries/Cabal/Cabal/Cabal.cabal:                   Dependency of ``ghc-pkg`` utility
    
    264
    -    libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal:     Dependency of ``ghc-pkg`` utility
    
    265
    -    libraries/containers/containers/containers.cabal:    Dependency of ``ghc`` library
    
    266
    -    libraries/deepseq/deepseq.cabal:                     Dependency of ``ghc`` library
    
    267
    -    libraries/directory/directory.cabal:                 Dependency of ``ghc`` library
    
    268
    -    libraries/exceptions/exceptions.cabal:               Dependency of ``ghc`` and ``haskeline`` library
    
    269
    -    libraries/filepath/filepath.cabal:                   Dependency of ``ghc`` library
    
    270
    -    compiler/ghc.cabal:                                  The compiler itself
    
    271
    -    libraries/ghci/ghci.cabal:                           The REPL interface
    
    272
    -    libraries/ghc-boot/ghc-boot.cabal:                   Internal compiler library
    
    273
    -    libraries/ghc-boot-th/ghc-boot-th.cabal:             Internal compiler library
    
    274
    -    libraries/ghc-compact/ghc-compact.cabal:             Core library
    
    275
    -    libraries/ghc-heap/ghc-heap.cabal:                   GHC heap-walking library
    
    276
    -    libraries/ghc-prim/ghc-prim.cabal:                   Core library
    
    277
    -    utils/haddock/haddock-api/haddock-api.cabal:         Dependency of ``haddock`` executable
    
    278
    -    utils/haddock/haddock-library/haddock-library.cabal: Dependency of ``haddock`` executable
    
    279
    -    libraries/haskeline/haskeline.cabal:                 Dependency of ``ghci`` executable
    
    280
    -    libraries/hpc/hpc.cabal:                             Dependency of ``hpc`` executable
    
    281
    -    libraries/integer-gmp/integer-gmp.cabal:             Core library
    
    282
    -    libraries/mtl/mtl.cabal:                             Dependency of ``Cabal`` library
    
    283
    -    libraries/parsec/parsec.cabal:                       Dependency of ``Cabal`` library
    
    284
    -    libraries/pretty/pretty.cabal:                       Dependency of ``ghc`` library
    
    285
    -    libraries/process/process.cabal:                     Dependency of ``ghc`` library
    
    286
    -    libraries/stm/stm.cabal:                             Dependency of ``haskeline`` library
    
    287
    -    libraries/template-haskell/template-haskell.cabal:   Core library
    
    288
    -    libraries/terminfo/terminfo.cabal:                   Dependency of ``haskeline`` library
    
    289
    -    libraries/text/text.cabal:                           Dependency of ``Cabal`` library
    
    290
    -    libraries/time/time.cabal:                           Dependency of ``ghc`` library
    
    291
    -    libraries/transformers/transformers.cabal:           Dependency of ``ghc`` library
    
    292
    -    libraries/unix/unix.cabal:                           Dependency of ``ghc`` library
    
    293
    -    libraries/Win32/Win32.cabal:                         Dependency of ``ghc`` library
    
    294
    -    libraries/xhtml/xhtml.cabal:                         Dependency of ``haddock`` executable
    
    295
    -    libraries/os-string/os-string.cabal:                 Dependency of ``filepath`` library
    
    296
    -    libraries/file-io/file-io.cabal:                     Dependency of ``directory`` library

  • docs/users_guide/9.16.1-notes.rst
    1
    +.. _release-9-16-1:
    
    2
    +
    
    3
    +Version 9.16.1
    
    4
    +==============
    
    5
    +
    
    6
    +The significant changes to the various parts of the compiler are listed in the
    
    7
    +following sections. See the `migration guide
    
    8
    +<https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.16>`_ on the GHC Wiki
    
    9
    +for specific guidance on migrating programs to this release.
    
    10
    +
    
    11
    +Language
    
    12
    +~~~~~~~~
    
    13
    +
    
    14
    +Compiler
    
    15
    +~~~~~~~~
    
    16
    +
    
    17
    +- Code coverage's (:ghc-flag:`-fhpc`) treatment of record fields now extends
    
    18
    +  beyond record fields accessed via :extension:`RecordWildCards` and
    
    19
    +  :extension:`NamedFieldPuns`, and also handles access to nested record fields.
    
    20
    +  That is, in a pattern such as ``Foo{bar = Bar{baz = b}}`` both ``bar`` and
    
    21
    +  ``baz`` will now be marked as covered if ``b`` is evaluated. Note that this
    
    22
    +  currently only works when record fields (or values contained within them) are
    
    23
    +  bound to variables. The very similar pattern ``Foo{bar = Bar{baz = 42}}``
    
    24
    +  will will not yet mark ``bar`` or ``baz`` as covered.
    
    25
    +
    
    26
    +GHCi
    
    27
    +~~~~
    
    28
    +
    
    29
    +Runtime system
    
    30
    +~~~~~~~~~~~~~~
    
    31
    +
    
    32
    +Cmm
    
    33
    +~~~
    
    34
    +
    
    35
    +``base`` library
    
    36
    +~~~~~~~~~~~~~~~~
    
    37
    +
    
    38
    +``ghc-prim`` library
    
    39
    +~~~~~~~~~~~~~~~~~~~~
    
    40
    +
    
    41
    +``ghc`` library
    
    42
    +~~~~~~~~~~~~~~~
    
    43
    +
    
    44
    +``ghc-heap`` library
    
    45
    +~~~~~~~~~~~~~~~~~~~~
    
    46
    +
    
    47
    +``ghc-experimental`` library
    
    48
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    49
    +
    
    50
    +``template-haskell`` library
    
    51
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    52
    +
    
    53
    +Included libraries
    
    54
    +~~~~~~~~~~~~~~~~~~
    
    55
    +
    
    56
    +The package database provided with this distribution also contains a number of
    
    57
    +packages other than GHC itself. See the changelogs provided with these packages
    
    58
    +for further change information.
    
    59
    +
    
    60
    +.. ghc-package-list::
    
    61
    +
    
    62
    +    libraries/array/array.cabal:                         Dependency of ``ghc`` library
    
    63
    +    libraries/base/base.cabal:                           Core library
    
    64
    +    libraries/binary/binary.cabal:                       Dependency of ``ghc`` library
    
    65
    +    libraries/bytestring/bytestring.cabal:               Dependency of ``ghc`` library
    
    66
    +    libraries/Cabal/Cabal/Cabal.cabal:                   Dependency of ``ghc-pkg`` utility
    
    67
    +    libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal:     Dependency of ``ghc-pkg`` utility
    
    68
    +    libraries/containers/containers/containers.cabal:    Dependency of ``ghc`` library
    
    69
    +    libraries/deepseq/deepseq.cabal:                     Dependency of ``ghc`` library
    
    70
    +    libraries/directory/directory.cabal:                 Dependency of ``ghc`` library
    
    71
    +    libraries/exceptions/exceptions.cabal:               Dependency of ``ghc`` and ``haskeline`` library
    
    72
    +    libraries/filepath/filepath.cabal:                   Dependency of ``ghc`` library
    
    73
    +    compiler/ghc.cabal:                                  The compiler itself
    
    74
    +    libraries/ghci/ghci.cabal:                           The REPL interface
    
    75
    +    libraries/ghc-boot/ghc-boot.cabal:                   Internal compiler library
    
    76
    +    libraries/ghc-boot-th/ghc-boot-th.cabal:             Internal compiler library
    
    77
    +    libraries/ghc-compact/ghc-compact.cabal:             Core library
    
    78
    +    libraries/ghc-heap/ghc-heap.cabal:                   GHC heap-walking library
    
    79
    +    libraries/ghc-prim/ghc-prim.cabal:                   Core library
    
    80
    +    utils/haddock/haddock-api/haddock-api.cabal:         Dependency of ``haddock`` executable
    
    81
    +    utils/haddock/haddock-library/haddock-library.cabal: Dependency of ``haddock`` executable
    
    82
    +    libraries/haskeline/haskeline.cabal:                 Dependency of ``ghci`` executable
    
    83
    +    libraries/hpc/hpc.cabal:                             Dependency of ``hpc`` executable
    
    84
    +    libraries/integer-gmp/integer-gmp.cabal:             Core library
    
    85
    +    libraries/mtl/mtl.cabal:                             Dependency of ``Cabal`` library
    
    86
    +    libraries/parsec/parsec.cabal:                       Dependency of ``Cabal`` library
    
    87
    +    libraries/pretty/pretty.cabal:                       Dependency of ``ghc`` library
    
    88
    +    libraries/process/process.cabal:                     Dependency of ``ghc`` library
    
    89
    +    libraries/stm/stm.cabal:                             Dependency of ``haskeline`` library
    
    90
    +    libraries/template-haskell/template-haskell.cabal:   Core library
    
    91
    +    libraries/terminfo/terminfo.cabal:                   Dependency of ``haskeline`` library
    
    92
    +    libraries/text/text.cabal:                           Dependency of ``Cabal`` library
    
    93
    +    libraries/time/time.cabal:                           Dependency of ``ghc`` library
    
    94
    +    libraries/transformers/transformers.cabal:           Dependency of ``ghc`` library
    
    95
    +    libraries/unix/unix.cabal:                           Dependency of ``ghc`` library
    
    96
    +    libraries/Win32/Win32.cabal:                         Dependency of ``ghc`` library
    
    97
    +    libraries/xhtml/xhtml.cabal:                         Dependency of ``haddock`` executable
    
    98
    +    libraries/os-string/os-string.cabal:                 Dependency of ``filepath`` library
    
    99
    +    libraries/file-io/file-io.cabal:                     Dependency of ``directory`` library

  • docs/users_guide/release-notes.rst
    ... ... @@ -4,4 +4,4 @@ Release notes
    4 4
     .. toctree::
    
    5 5
        :maxdepth: 1
    
    6 6
     
    
    7
    -   9.14.1-notes
    7
    +   9.16.1-notes