[Git][ghc/ghc][wip/ghc-9.10] 5 commits: docs: Drop old release notes

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Thu Mar 21 15:49:37 UTC 2024



Ben Gamari pushed to branch wip/ghc-9.10 at Glasgow Haskell Compiler / GHC


Commits:
47272633 by Ben Gamari at 2024-03-13T18:21:37-04:00
docs: Drop old release notes

- - - - -
db8a17a0 by Ben Gamari at 2024-03-13T18:33:12-04:00
gitlab/rel_eng: More upload.sh tweaks

- - - - -
b55e0ef9 by Ben Gamari at 2024-03-13T18:33:17-04:00
rel_eng: Drop dead prepare_docs codepath

- - - - -
548da279 by Ben Gamari at 2024-03-14T09:13:15-04:00
rel_env/recompress_all: Decompress xz before recompressing

Previously we would rather compress the xz *again*, before in addition
compressing it with the desired scheme.

Fixes #24545.

- - - - -
cf814fe9 by Teo Camarasu at 2024-03-21T11:44:15-04:00
Add preamble to 9.10 release notes

Resolves #24567

- - - - -


5 changed files:

- .gitlab/rel_eng/recompress-all
- .gitlab/rel_eng/upload.sh
- docs/users_guide/9.10.1-notes.rst
- − docs/users_guide/9.6.1-notes.rst
- − docs/users_guide/9.8.1-notes.rst


Changes:

=====================================
.gitlab/rel_eng/recompress-all
=====================================
@@ -9,21 +9,22 @@ usage :
 
 %.gz : %.xz
 	echo "[xz->gz] $< to $@..."
-	xz -c $< | gzip -c > $@
+	xz -cd $< | gzip -c > $@
 
 %.bz2 : %.xz
 	echo "[xz->bz2] $< to $@..."
-	xz -c $< | bzip2 -c > $@
+	xz -cd $< | bzip2 -c > $@
 
 %.lz : %.xz
 	echo "[xz->lz] $< to $@..."
-	xz -c $< | lzip -c > $@
+	xz -cd $< | lzip -c > $@
 
 %.zip : %.tar.xz
 	echo "[tarxz->zip] $< to $@..."
-	tmp="$(mktemp tmp.XXX)" && \
+	tmp="$$(mktemp tmp.XXX)" && \
 		tar -C "$$tmp" -xf $< && \
 		cd "$$tmp" && \
 		zip -9 -r $@ * && \
+		cd .. && \
 		rm -R "$$tmp"
 


=====================================
.gitlab/rel_eng/upload.sh
=====================================
@@ -145,7 +145,7 @@ function purge_all() {
     curl -X PURGE http://downloads.haskell.org/~ghc/$dir
     curl -X PURGE http://downloads.haskell.org/~ghc/$dir/
     for i in *; do
-        purge_file $i
+        purge_file "$i"
     done
 }
 
@@ -158,43 +158,14 @@ function purge_file() {
     )
 
     for dir in ${dirs[@]}; do
-        curl -X PURGE http://downloads.haskell.org/$dir/$i
-        curl -X PURGE http://downloads.haskell.org/$dir/$i/
-        curl -X PURGE http://downloads.haskell.org/$dir/$i/docs/
+        curl -X PURGE http://downloads.haskell.org/$dir/$1
+        curl -X PURGE http://downloads.haskell.org/$dir/$1/
+        curl -X PURGE http://downloads.haskell.org/$dir/$1/docs/
     done
 }
 
 function prepare_docs() {
     echo "THIS COMMAND IS DEPRECATED, THE DOCS FOLDER SHOULD BE PREPARED BY THE FETCH SCRIPT"
-    local tmp
-    rm -Rf docs
-    if [ -z "$GHC_TREE" ]; then
-        tmp="$(mktemp -d)"
-        tar -xf "ghc-$ver-src.tar.xz" -C "$tmp"
-        GHC_TREE="$tmp/ghc-$ver"
-    fi
-    mkdocs="$GHC_TREE/distrib/mkDocs/mkDocs"
-    if [ ! -e "$mkdocs" ]; then
-        echo "Couldn't find GHC mkDocs at $mkdocs."
-        echo "Perhaps you need to override GHC_TREE?"
-        rm -Rf "$tmp"
-        exit 1
-    fi
-    windows_bindist="$(ls ghc-$ver-x86_64-unknown-mingw32.tar.xz | head -n1)"
-    linux_bindist="$(ls ghc-$ver-x86_64-deb9-linux.tar.xz | head -n1)"
-    echo "Windows bindist: $windows_bindist"
-    echo "Linux bindist: $linux_bindist"
-    $ENTER_FHS_ENV $mkdocs $linux_bindist $windows_bindist
-    if [ -d "$tmp" ]; then rm -Rf "$tmp"; fi
-
-    mkdir -p docs/html
-    tar -Jxf "$linux_bindist"
-    cp -R "ghc-$ver/docs/users_guide/build-html/users_guide docs/html/users_guide"
-    #cp -R ghc-$ver/utils/haddock/doc/haddock docs/html/haddock
-    rm -R "ghc-$ver"
-
-    tar -Jxf docs/libraries.html.tar.xz -C docs/html
-    mv docs/index.html docs/html
 }
 
 function recompress() {
@@ -213,7 +184,7 @@ function recompress() {
         needed+=( "$(basename $i .tar.xz).zip" )
     done
 
-    recompress-all -l ${needed[@]}
+    recompress-all -j10 ${needed[@]}
 }
 
 function upload_docs() {


=====================================
docs/users_guide/9.10.1-notes.rst
=====================================
@@ -2,6 +2,10 @@
 
 Version 9.10.1
 ==============
+The significant changes to the various parts of the compiler are listed in the
+following sections. See the `migration guide
+<https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.10>`_ on the GHC Wiki
+for specific guidance on migrating programs to this release.
 
 Language
 ~~~~~~~~


=====================================
docs/users_guide/9.6.1-notes.rst deleted
=====================================
@@ -1,267 +0,0 @@
-.. _release-9-6-1:
-
-Version 9.6.1
-==============
-
-Language
-~~~~~~~~
-
-- GHC is now more conservative when solving constraints that arise from
-  superclass expansion in terms of other constraints that also arise from
-  superclass expansion.
-
-  For example: ::
-
-    class C a
-    class C a => D a b
-    instance D a a => D a b
-
-  When typechecking the instance, we need to also solve the constraints arising
-  from the superclasses of ``D``; in this case, we need ``C a``. We could obtain
-  evidence for this constraint by expanding the superclasses of the context,
-  as ``D a a`` also has a superclass context of ``C a``.
-  However, is it unsound to do so in general, as we might be assuming precisely
-  the predicate we want to prove! This can lead to programs that loop at runtime.
-
-  When such potentially-loopy situations arise, GHC now emits a warning.
-  In future releases, this behaviour will no longer be supported, and the
-  typechecker will outright refuse to solve these constraints, emitting a
-  ``Could not deduce`` error.
-
-  In practice, you should be able to fix these issues by adding the necessary
-  constraint to the context, e.g. for the above example: ::
-
-    instance (C a, D a a) => D a b
-
-- Record updates for GADTs and other existential datatypes are now
-  fully supported.
-
-  For example: ::
-
-    data D b where
-      MkD :: { fld1 :: a -> a, fld2 :: a -> (), fld3 :: b } -> D b
-
-    foo :: D b -> D b
-    foo d = d { fld1 = id, fld2 = const () }
-
-  In this example, we have an existential variable ``a``, and we update
-  all fields whose type involves ``a`` at once, so the update is valid.
-
-  A side-effect of this change is that GHC now rejects some record updates
-  involving fields whose types contain type families (these record updates
-  were previously erroneously accepted).
-
-  Example: ::
-
-    type family F a where
-      F Int   = Char
-      F Float = Char
-
-    data T b = MkT { x :: [Int], y :: [F b] }
-
-    emptyT :: forall b. T b
-    emptyT = MkT [] []
-
-    bar :: T Int
-    bar = emptyT { x = [3] }
-
-  In this example, we can't infer the type of ``emptyT`` in ``bar``: it could be
-  ``T Int``, but it could also be ``T Float`` because the type family ``F``
-  is not injective and ``T Float ~ T Int``. Indeed, the following typechecks ::
-
-    baz :: T Int
-    baz = case ( emptyT :: T Float ) of { MkT _ y -> MkT [3] y }
-
-  This means that the type of ``emptyT`` is ambiguous in the definition
-  of ``bar`` above, and thus GHC rejects the record update: ::
-
-    Couldn't match type `F b0' with `Char'
-    Expected: [F Int]
-      Actual: [F b0]
-    NB: ‘F’ is a non-injective type family
-    The type variable ‘b0’ is ambiguous
-
-  To fix these issues, add a type signature to the expression that the
-  record update is applied to (``emptyT`` in the example above), or
-  add an injectivity annotation to the type family in the case that
-  the type family is in fact injective.
-
-- Error messages are now assigned unique error codes, of the form ``[GHC-12345]``.
-
-- GHC Proposal `#106
-  <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0106-type-data.rst>`_
-  has been implemented, introducing a new language extension
-  :extension:`TypeData`. This extension permits ``type data`` declarations
-  as a more fine-grained alternative to :extension:`DataKinds`.
-
-- GHC now does a better job of solving constraints in the presence of multiple
-  matching quantified constraints. For example, if we want to solve
-  ``C a b Int`` and we have matching quantified constraints: ::
-
-    forall x y z. (Ord x, Enum y, Num z) => C x y z
-    forall u v. (Enum v, Eq u) => C u v Int
-
-  Then GHC will use the second quantified constraint to solve ``C a b Int``,
-  as it has a strictly weaker precondition.
-
-- GHC proposal `#170 Unrestricted OverloadedLabels
-  <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0170-unrestricted-overloadedlabels.rst>`_
-  has been implemented.
-  This extends the variety syntax for constructing labels under :extension:`OverloadedLabels`.
-  Examples of newly allowed syntax:
-  - Leading capital letters: `#Foo` equivalant to `getLabel @"Foo"`
-  - Numeric characters: `#1728` equivalent to `getLabel @"1728"`
-  - Arbitrary strings: `#"Hello, World!"` equivalent to `getLabel @"Hello, World!"`
-
-Compiler
-~~~~~~~~
-
-- The `WebAssembly backend
-  <https://www.tweag.io/blog/2022-11-22-wasm-backend-merged-in-ghc>`_
-  has been merged. This allows GHC to be built as a cross-compiler
-  that targets ``wasm32-wasi`` and compiles Haskell code to
-  self-contained WebAssembly modules that can be executed on a variety
-  of different runtimes. There are a few caveats to be aware of:
-
-  - To use the WebAssembly backend, one would need to follow the
-    instructions on `ghc-wasm-meta
-    <https://gitlab.haskell.org/ghc/ghc-wasm-meta>`_. The WebAssembly
-    backend is not included in the GHC release bindists for the time
-    being, nor is it supported by ``ghcup`` or ``stack`` yet.
-  - The WebAssembly backend is still under active development. It's
-    presented in this GHC version as a technology preview, bugs and
-    missing features are expected.
-
-- The JavaScript backend has been merged. GHC is now able to be built as a
-  cross-compiler targeting the JavaScript platform. The backend should be
-  considered a technology preview. As such it is not ready for use in
-  production, is not distributed in the GHC release bindists and requires the
-  user to manually build GHC as a cross-compiler. See the JavaScript backend
-  `wiki <https://gitlab.haskell.org/ghc/ghc/-/wikis/javascript-backend>`_ page
-  on the GHC wiki for the current status, project roadmap, build instructions
-  and demos.
-
-- The :extension:`TypeInType` is now marked as deprecated. Its meaning has been included
-  in :extension:`PolyKinds` and :extension:`DataKinds`.
-
-- The :ghc-flag:`-Woperator-whitespace` warning no longer ignores constructor symbols
-  (operators starting with ``:``).
-
-- The :ghc-flag:`-Wstar-is-type` warning is now enabled by default.
-
-- The 32bit x86 NCG backend will now generate inline assembly for most common 64bit
-  operations. This improves Int64/Word64 performance substantially on this platform.
-
-GHCi
-~~~~
-
-- GHCi will now accept any file-header pragmas it finds, such as
-  ``{-# OPTIONS_GHC ... #-}`` and ``{-# LANGUAGE ... #-}`` (see :ref:`pragmas`).  For example,
-  instead of using :ghci-cmd:`:set` to enable :ghc-flag:`-Wmissing-signatures`,
-  you could instead write:
-
-  .. code-block:: none
-
-      ghci> {-# OPTIONS_GHC -Wmissing-signatures #-}
-
-This can be convenient when pasting large multi-line blocks of code into GHCi.
-
-Runtime system
-~~~~~~~~~~~~~~
-
-- The `Delimited continuation primops <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0313-delimited-continuation-primops.rst>`_
-  proposal has been implemented, adding native support for first-class,
-  delimited continuations to the RTS. For the reasons given in the proposal,
-  no safe API to access this functionality is provided anywhere in ``base``.
-  Instead, the ``prompt#`` and ``control0#`` primops are intended to be consumed
-  by library authors directly, who may wrap them a safe API that maintains the
-  necessary invariants. See the documentation in ``GHC.Prim`` for more details.
-
-- The behaviour of the ``-M`` flag has been made more strict. It will now trigger
-  a heap overflow if the total amount of memory used by the Haskell heap exceeds the limit.
-  Previously only live blocks were taken into account.
-  This makes it more likely to trigger promptly when the heap is highly fragmented.
-
-- Fixed a bug that sometimes caused live sparks to be GC'ed too early either during
-  minor GC or major GC with workstealing disabled. See #22528.
-
-
-``base`` library
-~~~~~~~~~~~~~~~~
-
-- Exceptions thrown by weak pointer finalizers can now be reported by setting
-  a global exception handler, using ``GHC.Weak.Finalize.setFinalizerExceptionHandler``.
-  The default behaviour is unchanged (exceptions are ignored and not reported).
-
-- GHC now provides a set of operations for introspecting on the threads of a
-  program, ``GHC.Conc.listThreads``, as well as operations for querying a thread's
-  label (:base-ref:`GHC.Conc.Sync.threadLabel`) and status
-  (:base-ref:`GHC.Conc.threadStatus`).
-
-- Change default ``Ord`` implementation of ``(>=)``, ``(>)``, and ``(<)`` to use
-  ``(<=)`` instead of ``compare`` per CLC proposal:
-  https://github.com/haskell/core-libraries-committee/issues/24
-
-- Updated to `Unicode 15.0.0 <https://www.unicode.org/versions/Unicode15.0.0/>`_.
-
-- Add standard Unicode case predicates :base-ref:`Data.Char.isUpperCase` and
-  :base-ref:`Data.Char.isLowerCase`. These predicates use the standard Unicode
-  case properties and are more intuitive than :base-ref:`Data.Char.isUpper` and
-  :base-ref:`Data.Char.isLower`.
-
-``ghc-prim`` library
-~~~~~~~~~~~~~~~~~~~~
-
-``ghc`` library
-~~~~~~~~~~~~~~~
-
-- Add `Foreign.C.Types.ConstPtr` was added to encode ``const``-qualified pointer return
-  types in foreign declarations when using ``CApiFFI`` extension.
-
-``ghc-heap`` library
-~~~~~~~~~~~~~~~~~~~~
-
-
-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.
-
-.. ghc-package-list::
-
-    libraries/array/array.cabal:             Dependency of ``ghc`` library
-    libraries/base/base.cabal:               Core library
-    libraries/binary/binary.cabal:           Dependency of ``ghc`` library
-    libraries/bytestring/bytestring.cabal:   Dependency of ``ghc`` library
-    libraries/Cabal/Cabal/Cabal.cabal:       Dependency of ``ghc-pkg`` utility
-    libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal:  Dependency of ``ghc-pkg`` utility
-    libraries/containers/containers/containers.cabal: Dependency of ``ghc`` library
-    libraries/deepseq/deepseq.cabal:         Dependency of ``ghc`` library
-    libraries/directory/directory.cabal:     Dependency of ``ghc`` library
-    libraries/exceptions/exceptions.cabal:   Dependency of ``ghc`` and ``haskeline`` library
-    libraries/filepath/filepath.cabal:       Dependency of ``ghc`` library
-    compiler/ghc.cabal:                      The compiler itself
-    libraries/ghci/ghci.cabal:               The REPL interface
-    libraries/ghc-boot/ghc-boot.cabal:       Internal compiler library
-    libraries/ghc-boot-th/ghc-boot-th.cabal: Internal compiler library
-    libraries/ghc-compact/ghc-compact.cabal: Core library
-    libraries/ghc-heap/ghc-heap.cabal:       GHC heap-walking library
-    libraries/ghc-prim/ghc-prim.cabal:       Core library
-    libraries/haskeline/haskeline.cabal:     Dependency of ``ghci`` executable
-    libraries/hpc/hpc.cabal:                 Dependency of ``hpc`` executable
-    libraries/integer-gmp/integer-gmp.cabal: Core library
-    libraries/mtl/mtl.cabal:                 Dependency of ``Cabal`` library
-    libraries/parsec/parsec.cabal:           Dependency of ``Cabal`` library
-    libraries/pretty/pretty.cabal:           Dependency of ``ghc`` library
-    libraries/process/process.cabal:         Dependency of ``ghc`` library
-    libraries/stm/stm.cabal:                 Dependency of ``haskeline`` library
-    libraries/template-haskell/template-haskell.cabal: Core library
-    libraries/terminfo/terminfo.cabal:       Dependency of ``haskeline`` library
-    libraries/text/text.cabal:               Dependency of ``Cabal`` library
-    libraries/time/time.cabal:               Dependency of ``ghc`` library
-    libraries/transformers/transformers.cabal: Dependency of ``ghc`` library
-    libraries/unix/unix.cabal:               Dependency of ``ghc`` library
-    libraries/Win32/Win32.cabal:             Dependency of ``ghc`` library
-    libraries/xhtml/xhtml.cabal:             Dependency of ``haddock`` executable


=====================================
docs/users_guide/9.8.1-notes.rst deleted
=====================================
@@ -1,334 +0,0 @@
-.. _release-9-8-1:
-
-Version 9.8.1
-=============
-
-Language
-~~~~~~~~
-
-- There is a new extension :extension:`ExtendedLiterals`, which enables
-  sized primitive literals, e.g. ``123#Int8`` is a literal of type ``Int8#``.
-  See the GHC proposal `#451 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0451-sized-literals.rst>`_.
-  Derived ``Show`` instances for datatypes containing sized literals (``Int8#``, ``Word8#``, ``Int16#`` etc.)
-  now use the extended literal syntax, per GHC proposal `#596 <https://github.com/ghc-proposals/ghc-proposals/pull/596>`_.
-  Furthermore, it is now possible to derive ``Show`` for datatypes containing
-  fields of types ``Int64#`` and ``Word64#``.
-
-- GHC Proposal `#425
-  <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0425-decl-invis-binders.rst>`_
-  has been partially implemented. Namely, the ``@k``-binders in type declarations are now permitted::
-
-    type T :: forall k. k -> forall j. j -> Type
-    data T @k (a :: k) @(j :: Type) (b :: j)
-
-  This feature is guarded behind :extension:`TypeAbstractions`.
-
-- In accordance with GHC proposal `#425
-  <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0425-decl-invis-binders.rst>`_
-  GHC no longer implicitly quantifies over type variables that appear only in the RHS of type and
-  data family instances. This code will no longer work: ::
-
-    type family F1 a :: k
-    type instance F1 Int = Any :: j -> j
-
-  Instead you should write::
-
-    type instance F1 @(j -> j) Int = Any :: j -> j
-
-  Or::
-
-    type instance forall j . F1 Int = Any :: j -> j
-
-- GHC proposal `#475 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0475-tuple-syntax.rst>`_
-  has been partially implemented. Namely, tuple data types, which were previously represented using a brackets-with-commas
-  syntax form ((), (,), (,,), and so on) have been renamed to common names of the form ``Unit``, ``Tuple2``, ``Tuple3``,
-  and so on, where the number after ``Tuple`` indicates its arity: ::
-
-    data Unit = ()
-
-    data Tuple2 a b = (a,b)
-    data Tuple3 a b c = (a, b, c)
-    -- and so on, up to Tuple64
-
-  For consistency, we also introduce type aliases: ::
-
-    type Tuple0 = Unit
-    type Tuple1 = Solo
-
-  The renamed tuple data types and the new type aliases can be found in the ``GHC.Tuple`` module. This renaming
-  does not break existing code that directly uses tuple data types, but it does affect tools and libraries
-  that have access to the data type names, such as ``Generic`` and Template Haskell.
-
-Compiler
-~~~~~~~~
-
-- Added a new warning :ghc-flag:`-Wterm-variable-capture` that helps to make code compatible with
-  the future extension ``RequiredTypeArguments``.
-
-- Rewrite rules now support a limited form of higher order matching when a
-  pattern variable is applied to distinct locally bound variables. For example: ::
-
-      forall f. foo (\x -> f x)
-
-  Now matches: ::
-
-      foo (\x -> x*2 + x)
-
-- GHC Proposal `#496
-  <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0496-empty-record-wildcards.rst>`_
-  has been implemented, allowing ``{..}`` syntax for constructors without fields, for consistency.
-  This is convenient for TH code generation, as you can now uniformly use record wildcards
-  regardless of number of fields.
-
-- Incoherent instance applications are no longer specialised. The previous implementation of
-  specialisation resulted in nondeterministic instance resolution in certain cases, breaking
-  the specification described in the documentation of the `INCOHERENT` pragma. See :ghc-ticket:`22448` for further details.
-
-- Fix a bug in TH causing excessive calls to ``setNumCapabilities`` when ``-j`` is greater than ``-N``.
-  See :ghc-ticket:`23049`.
-
-- The ``-Wno-⟨wflag⟩``, ``-Werror=⟨wflag⟩`` and ``-Wwarn=⟨wflag⟩`` options are
-  now defined systematically for all warning groups (for example,
-  ``-Wno-default``, ``-Werror=unused-binds`` and ``-Wwarn=all`` are now
-  accepted). See :ref:`options-sanity`.
-
-- ``WARNING`` pragmas may now be annotated with a category, following
-  `GHC proposal #541 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0541-warning-pragmas-with-categories.rst>`_, in which case they are controlled with new
-  ``-Wx-⟨category⟩`` flags rather than :ghc-flag:`-Wdeprecations`.
-  A new warning group :ghc-flag:`-Wextended-warnings` includes all such warnings
-  regardless of category.  See :ref:`warning-deprecated-pragma`.
-
-- GHC is now better at disambiguating record updates in the presence of duplicate
-  record fields. The following program is now accepted ::
-
-     {-# LANGUAGE DuplicateRecordFields #-}
-
-     data R = MkR1 { foo :: Int }
-            | MkR2 { bar :: Int }
-
-     data S = MkS { foo :: Int, bar :: Int }
-
-     blah x = x { foo = 5, bar = 6 }
-
-  The point is that only the type S has a constructor with both fields "foo"
-  and "bar", so this record update is unambiguous.
-
-- Data types with ``deriving`` clauses now reject inferred instance contexts
-  that mention ``TypeError`` constraints (see :ref:`custom-errors`), such as
-  this one: ::
-
-      newtype Foo = Foo Int
-
-      class Bar a where
-        bar :: a
-
-      instance (TypeError (Text "Boo")) => Bar Foo where
-        bar = undefined
-
-      newtype Baz = Baz Foo
-        deriving Bar
-
-  Here, the derived ``Bar`` instance for ``Baz`` would look like this: ::
-
-      instance TypeError (Text "Boo") => Bar Baz
-
-  While GHC would accept this before, GHC 9.8 now rejects it, emitting "``Boo``"
-  in the resulting error message. If you really want to derive this instance and
-  defer the error to sites where the instance is used, you must do so manually
-  with :extension:`StandaloneDeriving`, e.g. ::
-
-      deriving instance TypeError (Text "Boo") => Bar Baz
-
-- GHC Proposal `#540 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0540-jsem.rst>`_ has been implemented.
-  This adds the `-jsem`:ghc-flag: flag, which instructs GHC to act as a jobserver client.
-  This enables multiple GHC processes running at once to share system resources
-  with each other, communicating via the system semaphore specified by
-  the flag argument.
-
-- GHC Proposal `#433
-  <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0433-unsatisfiable.rst>`_
-  has been implemented. This adds the class ``Unsatisfiable :: ErrorMessage -> Constraint``
-  to the ``GHC.TypeError`` module. Constraints of the form ``Unsatisfiable msg``
-  provide a mechanism for custom type errors that reports the errors in a more
-  predictable behaviour than ``TypeError``, as these constraints are
-  handled purely during constraint solving.
-
-  For example: ::
-
-      instance Unsatisfiable (Text "There is no Eq instance for functions") => Eq (a -> b) where
-        (==) = unsatisfiable
-
-  This allows errors to be reported when users use the instance, even when
-  type errors are being deferred.
-
-- GHC is now deals "insoluble Givens" in a consistent way. For example: ::
-
-        k :: (Int ~ Bool) => Int -> Bool
-        k x = x
-
-  GHC used to accept the contradictory ``Int~Bool`` in the type signature, but reject the ``Int~Bool`` constraint that arises from typechecking the definition itself.  Now it accepts both.  More details in `GHC ticket #23413 <https://gitlab.haskell.org/ghc/ghc/-/issues/23413>`_, which gives examples of the previous inconsistency.  GHC now implements the "PermissivePlan" described in that ticket.
-
-- The `-ddump-spec` flag has been split into `-ddump-spec` and
-  `-ddump-spec-constr`, allowing only output from the typeclass specialiser or
-  `SpecConstr` to be seen if desired.
-
-- The compiler may now be configured to compress the debugging information
-  included in :ghc-flag:`-finfo-table-map` enabled binaries. To do so, one must
-  build GHC from source (see
-  `here<https://gitlab.haskell.org/ghc/ghc/-/wikis/building>` for directions)
-  and supply the ``--enable-ipe-data-compression`` flag to the ``configure``
-  script. **Note**: This feature requires that the machine building GHC has
-  `libzstd <https://github.com/facebook/zstd/>`_ version 1.4.0 or greater
-  installed. The compression library `libzstd` may optionally be statically
-  linked in the resulting compiler (on non-darwin machines) using the
-  ``--enable-static-libzstd`` configure flag.
-
-  In a test compiling GHC itself, the size of the :ghc-flag:`-finfo-table-map`
-  enabled build results was reduced by over 20% when compression was enabled.
-
-- GHC Proposal `#134
-  <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0134-deprecating-exports-proposal.rst>`_
-  has been implemented. This makes it possible to deprecate certain names exported from a module, without deprecating
-  the name itself. You can check the full specification of the feature at :ref:`warning-deprecated-pragma`.
-
-  For example ::
-
-      module X (
-          {-# WARNING "do not use that constructor" D(D1),
-          D(D2)
-        )
-        data D = D1 | D2
-
-  This allows for changing the structure of a library without immediately breaking user code,
-  but instead being able to warn the user that a change in the library interface
-  will occur in the future.
-
-- Guard polymorphic specialisation behind the flag :ghc-flag:`-fpolymorphic-specialisation`.
-  This optimisation has led to a number of incorrect runtime result bugs, so we are disabling it
-  by default for now whilst we consider more carefully an appropriate fix.
-  (See :ghc-ticket:`23469`, :ghc-ticket:`23109`, :ghc-ticket:`21229`, :ghc-ticket:`23445`)
-
-- The warning about incompatible command line flags can now be controlled with the
-  :ghc-flag:`-Winconsistent-flags`. In particular this allows you to silence a warning
-  when using optimisation flags with :ghc-flag:`--interactive` mode.
-
-GHCi
-~~~~
-
-- The deprecated `:ctags` and `:etags` GHCi commands have been removed. See this `wiki page <https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/GHCi/Tags>`_ if you want to add a macro to recover similar functionality.
-
-Runtime system
-~~~~~~~~~~~~~~
-
-- On POSIX systems that support timerfd, RTS shutdown no longer has to wait for
-  the next RTS 'tick' to occur before continuing the shutdown process. See :ghc-ticket:`22692`.
-
-``base`` library
-~~~~~~~~~~~~~~~~
-
-- ``Data.Tuple`` now exports ``getSolo :: Solo a -> a``.
-
-``ghc-prim`` library
-~~~~~~~~~~~~~~~~~~~~
-
-- Primitive pointer comparison functions are now levity-polymorphic, e.g. ::
-
-      sameArray# :: forall {l} (a :: TYPE (BoxedRep l)). Array# a -> Array# a -> Int#
-
-  This change affects the following functions:
-
-    - ``sameArray#``, ``sameMutableArray#``,
-    - ``sameSmallArray#``, ``sameSmallMutableArray#``,
-    - ``sameMutVar#``, ``sameTVar#``, ``sameMVar#``
-    - ``sameIOPort#``, ``eqStableName#``.
-
-- New primops for fused multiply-add operations. These primops combine a
-  multiplication and an addition, compiling to a single instruction when
-  the ``-mfma`` flag is enabled and the architecture supports it.
-
-  The new primops are ``fmaddFloat#, fmsubFloat#, fnmaddFloat#, fnmsubFloat# :: Float# -> Float# -> Float# -> Float#``
-  and ``fmaddDouble#, fmsubDouble#, fnmaddDouble#, fnmsubDouble# :: Double# -> Double# -> Double# -> Double#``.
-
-  These implement the following operations, while performing one single
-  rounding at the end, leading to a more accurate result:
-
-    - ``fmaddFloat# x y z``, ``fmaddDouble# x y z`` compute ``x * y + z``.
-    - ``fmsubFloat# x y z``, ``fmsubDouble# x y z`` compute ``x * y - z``.
-    - ``fnmaddFloat# x y z``, ``fnmaddDouble# x y z`` compute ``- x * y + z``.
-    - ``fnmsubFloat# x y z``, ``fnmsubDouble# x y z`` compute ``- x * y - z``.
-
-  Warning: on unsupported architectures, the software emulation provided by
-  the fallback to the C standard library is not guaranteed to be IEEE-compliant.
-
-``ghc`` library
-~~~~~~~~~~~~~~~
-
-- The ``RecordUpd`` constructor of ``HsExpr`` now takes an ``HsRecUpdFields``
-  instead of ``Either [LHsRecUpdField p] [LHsRecUpdProj p]``.
-  Instead of ``Left ..``, use the constructor ``RegularRecUpdFields``, and instead
-  of ``Right ..``, use the constructor ``OverloadedRecUpdFields``.
-
-- The ``loadWithCache`` function now takes an extra argument which allows API users
-  to embed GHC diagnostics in their own diagnostic type before they are printed.
-  This allows how messages are rendered and explained to users to be modified.
-  We use this functionality in GHCi to modify how some messages are displayed.
-
-- The extensions fields of constructors of ``IE`` now take ``Maybe (WarningTxt p)``
-  in ``GhcPs`` and ``GhcRn`` variants of the Syntax Tree.
-  This represents the warning assigned to a certain export item,
-  which is used for deprecated exports (see :ref:`warning-deprecated-pragma`).
-
-``ghc-heap`` library
-~~~~~~~~~~~~~~~~~~~~
-
-``template-haskell`` library
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-
-- Record fields now belong to separate ``NameSpace``s, keyed by the parent of
-  the record field. This is the name of the first constructor of the parent type,
-  even if this constructor does not have the field in question.
-  This change enables TemplateHaskell support for ``DuplicateRecordFields``.
-
-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.
-
-.. ghc-package-list::
-
-    libraries/array/array.cabal:             Dependency of ``ghc`` library
-    libraries/base/base.cabal:               Core library
-    libraries/binary/binary.cabal:           Dependency of ``ghc`` library
-    libraries/bytestring/bytestring.cabal:   Dependency of ``ghc`` library
-    libraries/Cabal/Cabal/Cabal.cabal:       Dependency of ``ghc-pkg`` utility
-    libraries/Cabal/Cabal-syntax/Cabal-syntax.cabal:  Dependency of ``ghc-pkg`` utility
-    libraries/containers/containers/containers.cabal: Dependency of ``ghc`` library
-    libraries/deepseq/deepseq.cabal:         Dependency of ``ghc`` library
-    libraries/directory/directory.cabal:     Dependency of ``ghc`` library
-    libraries/exceptions/exceptions.cabal:   Dependency of ``ghc`` and ``haskeline`` library
-    libraries/filepath/filepath.cabal:       Dependency of ``ghc`` library
-    compiler/ghc.cabal:                      The compiler itself
-    libraries/ghci/ghci.cabal:               The REPL interface
-    libraries/ghc-boot/ghc-boot.cabal:       Internal compiler library
-    libraries/ghc-boot-th/ghc-boot-th.cabal: Internal compiler library
-    libraries/ghc-compact/ghc-compact.cabal: Core library
-    libraries/ghc-heap/ghc-heap.cabal:       GHC heap-walking library
-    libraries/ghc-prim/ghc-prim.cabal:       Core library
-    libraries/haskeline/haskeline.cabal:     Dependency of ``ghci`` executable
-    libraries/hpc/hpc.cabal:                 Dependency of ``hpc`` executable
-    libraries/integer-gmp/integer-gmp.cabal: Core library
-    libraries/mtl/mtl.cabal:                 Dependency of ``Cabal`` library
-    libraries/parsec/parsec.cabal:           Dependency of ``Cabal`` library
-    libraries/pretty/pretty.cabal:           Dependency of ``ghc`` library
-    libraries/process/process.cabal:         Dependency of ``ghc`` library
-    libraries/stm/stm.cabal:                 Dependency of ``haskeline`` library
-    libraries/template-haskell/template-haskell.cabal: Core library
-    libraries/terminfo/terminfo.cabal:       Dependency of ``haskeline`` library
-    libraries/text/text.cabal:               Dependency of ``Cabal`` library
-    libraries/time/time.cabal:               Dependency of ``ghc`` library
-    libraries/transformers/transformers.cabal: Dependency of ``ghc`` library
-    libraries/unix/unix.cabal:               Dependency of ``ghc`` library
-    libraries/Win32/Win32.cabal:             Dependency of ``ghc`` library
-    libraries/xhtml/xhtml.cabal:             Dependency of ``haddock`` executable



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9f85900d1d851adaa91215b21d362eed95387b5d...cf814fe982f42483c672802ce905350d99a85a35

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9f85900d1d851adaa91215b21d362eed95387b5d...cf814fe982f42483c672802ce905350d99a85a35
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240321/9d84f1ff/attachment-0001.html>


More information about the ghc-commits mailing list