[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: NCG: Fix a bug in jump shortcutting.
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Mon Mar 25 12:46:06 UTC 2024
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
5bd8ed53 by Andreas Klebinger at 2024-03-23T16:18:33-04:00
NCG: Fix a bug in jump shortcutting.
When checking if a jump has more than one destination account for the
possibility of some jumps not being representable by a BlockId.
We do so by having isJumpishInstr return a `Maybe BlockId` where Nothing
represents non-BlockId jump destinations.
Fixes #24507
- - - - -
8d67f247 by Ben Gamari at 2024-03-23T16:19:09-04:00
docs: Drop old release notes, add for 9.12.1
- - - - -
e6c5e010 by Cheng Shao at 2024-03-25T08:45:25-04:00
rts: fix clang compilation on aarch64
This patch fixes function prototypes in ARMOutlineAtomicsSymbols.h
which causes "error: address argument to atomic operation must be a
pointer to _Atomic type" when compiling with clang on aarch64.
- - - - -
70398925 by Sylvain Henry at 2024-03-25T08:45:36-04:00
Lexer: fix imports for Alex 3.5.1 (#24583)
- - - - -
19 changed files:
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/BlockLayout.hs
- compiler/GHC/CmmToAsm/Instr.hs
- compiler/GHC/CmmToAsm/PPC/Instr.hs
- compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
- compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs
- compiler/GHC/CmmToAsm/Reg/Liveness.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/Parser/Lexer.x
- − docs/users_guide/9.10.1-notes.rst
- + docs/users_guide/9.12.1-notes.rst
- − docs/users_guide/9.6.1-notes.rst
- − docs/users_guide/9.8.1-notes.rst
- docs/users_guide/release-notes.rst
- rts/ARMOutlineAtomicsSymbols.h
- + testsuite/tests/codeGen/should_run/T24507.hs
- + testsuite/tests/codeGen/should_run/T24507.stdout
- + testsuite/tests/codeGen/should_run/T24507_cmm.cmm
- testsuite/tests/codeGen/should_run/all.T
Changes:
=====================================
compiler/GHC/CmmToAsm/AArch64/Instr.hs
=====================================
@@ -301,15 +301,20 @@ isJumpishInstr instr = case instr of
-- | Checks whether this instruction is a jump/branch instruction.
-- One that can change the flow of control in a way that the
-- register allocator needs to worry about.
-jumpDestsOfInstr :: Instr -> [BlockId]
+jumpDestsOfInstr :: Instr -> [Maybe BlockId]
jumpDestsOfInstr (ANN _ i) = jumpDestsOfInstr i
-jumpDestsOfInstr (CBZ _ t) = [ id | TBlock id <- [t]]
-jumpDestsOfInstr (CBNZ _ t) = [ id | TBlock id <- [t]]
-jumpDestsOfInstr (J t) = [id | TBlock id <- [t]]
-jumpDestsOfInstr (B t) = [id | TBlock id <- [t]]
-jumpDestsOfInstr (BL t _ _) = [ id | TBlock id <- [t]]
-jumpDestsOfInstr (BCOND _ t) = [ id | TBlock id <- [t]]
-jumpDestsOfInstr _ = []
+jumpDestsOfInstr i = case i of
+ (CBZ _ t) -> [ mkDest t ]
+ (CBNZ _ t) -> [ mkDest t ]
+ (J t) -> [ mkDest t ]
+ (B t) -> [ mkDest t ]
+ (BL t _ _) -> [ mkDest t ]
+ (BCOND _ t) -> [ mkDest t ]
+ _ -> []
+ where
+ mkDest (TBlock id) = Just id
+ mkDest TLabel{} = Nothing
+ mkDest TReg{} = Nothing
-- | Change the destination of this jump instruction.
-- Used in the linear allocator when adding fixup blocks for join
=====================================
compiler/GHC/CmmToAsm/BlockLayout.hs
=====================================
@@ -771,7 +771,7 @@ dropJumps :: forall a i. Instruction i => LabelMap a -> [GenBasicBlock i]
dropJumps _ [] = []
dropJumps info (BasicBlock lbl ins:todo)
| Just ins <- nonEmpty ins --This can happen because of shortcutting
- , [dest] <- jumpDestsOfInstr (NE.last ins)
+ , [Just dest] <- jumpDestsOfInstr (NE.last ins)
, BasicBlock nextLbl _ : _ <- todo
, not (mapMember dest info)
, nextLbl == dest
@@ -870,7 +870,7 @@ mkNode edgeWeights block@(BasicBlock id instrs) =
| length successors > 2 || edgeWeight info <= 0 -> []
| otherwise -> [target]
| Just instr <- lastMaybe instrs
- , [one] <- jumpDestsOfInstr instr
+ , [one] <- jumpBlockDestsOfInstr instr
= [one]
| otherwise = []
=====================================
compiler/GHC/CmmToAsm/Instr.hs
=====================================
@@ -17,6 +17,8 @@ import GHC.Cmm.BlockId
import GHC.CmmToAsm.Config
import GHC.Data.FastString
+import Data.Maybe (catMaybes)
+
-- | Holds a list of source and destination registers used by a
-- particular instruction.
--
@@ -73,9 +75,17 @@ class Instruction instr where
-- | Give the possible destinations of this jump instruction.
-- Must be defined for all jumpish instructions.
+ -- Returns Nothing for non BlockId destinations.
jumpDestsOfInstr
+ :: instr -> [Maybe BlockId]
+
+ -- | Give the possible block destinations of this jump instruction.
+ -- Must be defined for all jumpish instructions.
+ jumpBlockDestsOfInstr
:: instr -> [BlockId]
+ jumpBlockDestsOfInstr = catMaybes . jumpDestsOfInstr
+
-- | Change the destination of this jump instruction.
-- Used in the linear allocator when adding fixup blocks for join
=====================================
compiler/GHC/CmmToAsm/PPC/Instr.hs
=====================================
@@ -513,12 +513,15 @@ isJumpishInstr instr
-- | Checks whether this instruction is a jump/branch instruction.
-- One that can change the flow of control in a way that the
-- register allocator needs to worry about.
-jumpDestsOfInstr :: Instr -> [BlockId]
+jumpDestsOfInstr :: Instr -> [Maybe BlockId]
jumpDestsOfInstr insn
= case insn of
- BCC _ id _ -> [id]
- BCCFAR _ id _ -> [id]
- BCTR targets _ _ -> [id | Just id <- targets]
+ BCC _ id _ -> [Just id]
+ BCCFAR _ id _ -> [Just id]
+ BCTR targets _ _ -> targets
+ BCTRL{} -> [Nothing]
+ BL{} -> [Nothing]
+ JMP{} -> [Nothing]
_ -> []
=====================================
compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs
=====================================
@@ -207,7 +207,7 @@ cleanForward platform blockId assoc acc (li : instrs)
-- Remember the association over a jump.
| LiveInstr instr _ <- li
- , targets <- jumpDestsOfInstr instr
+ , targets <- jumpBlockDestsOfInstr instr
, not $ null targets
= do mapM_ (accJumpValid assoc) targets
cleanForward platform blockId assoc (li : acc) instrs
@@ -386,7 +386,7 @@ cleanBackward' liveSlotsOnEntry reloadedBy noReloads acc (li : instrs)
-- it always does, but if those reloads are cleaned the slot
-- liveness map doesn't get updated.
| LiveInstr instr _ <- li
- , targets <- jumpDestsOfInstr instr
+ , targets <- jumpBlockDestsOfInstr instr
= do
let slotsReloadedByTargets
= IntSet.unions
=====================================
compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs
=====================================
@@ -57,7 +57,7 @@ joinToTargets block_live id instr
= return ([], instr)
| otherwise
- = joinToTargets' block_live [] id instr (jumpDestsOfInstr instr)
+ = joinToTargets' block_live [] id instr (jumpBlockDestsOfInstr instr)
-----
joinToTargets'
=====================================
compiler/GHC/CmmToAsm/Reg/Liveness.hs
=====================================
@@ -468,7 +468,7 @@ slurpReloadCoalesce live
-- if we hit a jump, remember the current slotMap
| LiveInstr (Instr instr) _ <- li
- , targets <- jumpDestsOfInstr instr
+ , targets <- jumpBlockDestsOfInstr instr
, not $ null targets
= do mapM_ (accSlotMap slotMap) targets
return (slotMap, Nothing)
@@ -760,7 +760,7 @@ sccBlocks blocks entries mcfg = map (fmap node_payload) sccs
sccs = stronglyConnCompG g2
getOutEdges :: Instruction instr => [instr] -> [BlockId]
- getOutEdges instrs = concatMap jumpDestsOfInstr instrs
+ getOutEdges instrs = concatMap jumpBlockDestsOfInstr instrs
-- This is truly ugly, but I don't see a good alternative.
-- Digraph just has the wrong API. We want to identify nodes
@@ -837,7 +837,7 @@ checkIsReverseDependent sccs'
slurpJumpDestsOfBlock (BasicBlock _ instrs)
= unionManyUniqSets
- $ map (mkUniqSet . jumpDestsOfInstr)
+ $ map (mkUniqSet . jumpBlockDestsOfInstr)
[ i | LiveInstr i _ <- instrs]
@@ -1047,7 +1047,7 @@ liveness1 platform liveregs blockmap (LiveInstr instr _)
-- union in the live regs from all the jump destinations of this
-- instruction.
- targets = jumpDestsOfInstr instr -- where we go from here
+ targets = jumpBlockDestsOfInstr instr -- where we go from here
not_a_branch = null targets
targetLiveRegs target
=====================================
compiler/GHC/CmmToAsm/X86/Instr.hs
=====================================
@@ -672,13 +672,16 @@ isJumpishInstr instr
jumpDestsOfInstr
:: Instr
- -> [BlockId]
+ -> [Maybe BlockId]
jumpDestsOfInstr insn
= case insn of
- JXX _ id -> [id]
- JMP_TBL _ ids _ _ -> [id | Just (DestBlockId id) <- ids]
+ JXX _ id -> [Just id]
+ JMP_TBL _ ids _ _ -> [(mkDest dest) | Just dest <- ids]
_ -> []
+ where
+ mkDest (DestBlockId id) = Just id
+ mkDest _ = Nothing
patchJumpInstr
=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -2870,7 +2870,7 @@ alexInputPrevChar (AI _ buf) = unsafeChr (fromIntegral (adjustChar pc))
where pc = prevChar buf '\n'
unsafeChr :: Int -> Char
-unsafeChr (I# c) = C# (chr# c)
+unsafeChr (I# c) = GHC.Exts.C# (GHC.Exts.chr# c)
-- backwards compatibility for Alex 2.x
alexGetChar :: AlexInput -> Maybe (Char,AlexInput)
=====================================
docs/users_guide/9.10.1-notes.rst deleted
=====================================
@@ -1,379 +0,0 @@
-.. _release-9-10-1:
-
-Version 9.10.1
-==============
-
-Language
-~~~~~~~~
-
-- The :extension:`GHC2024` language edition is now supported. It builds on top of
- :extension:`GHC2021`, adding the following extensions:
-
- * :extension:`DataKinds`
- * :extension:`DerivingStrategies`
- * :extension:`DisambiguateRecordFields`
- * :extension:`ExplicitNamespaces`
- * :extension:`GADTs`
- * :extension:`MonoLocalBinds`
- * :extension:`LambdaCase`
- * :extension:`RoleAnnotations`
-
- At the moment, :extension:`GHC2021` remains the default langauge edition that
- is used when no other language edition is explicitly loaded (e.g. when running
- ``ghc`` directly). Because language editions are not necessarily backwards
- compatible, and future releases of GHC may change the default, it is highly
- recommended to specify the language edition explicitly.
-
-- GHC Proposal `#281 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0281-visible-forall.rst>`_
- "Visible forall in types of terms" has been partially implemented.
- The following code is now accepted by GHC::
-
- {-# LANGUAGE RequiredTypeArguments #-}
-
- vshow :: forall a -> Show a => a -> String
- vshow t x = show (x :: t)
-
- s1 = vshow Int 42 -- "42"
- s2 = vshow Double 42 -- "42.0"
-
- The use of ``forall a ->`` instead of ``forall a.`` indicates a *required* type
- argument. A required type argument is visually indistinguishable from a value
- argument but does not exist at runtime.
-
- This feature is guarded behind :extension:`RequiredTypeArguments`.
-
-- The :extension:`ExplicitNamespaces` extension can now be used in conjunction
- with :extension:`RequiredTypeArguments` to select the type namespace in a
- required type argument::
-
- data T = T -- the name `T` is ambiguous
- f :: forall a -> ... -- `f` expects a required type argument
-
- x1 = f T -- refers to the /data/ constructor `T`
- x2 = f (type T) -- refers to the /type/ constructor `T`
-
-- With :extension:`LinearTypes`, ``let`` and ``where`` bindings can
- now be linear. So the following now typechecks::
-
- f :: A %1 -> B
- g :: B %1 -> C
-
- h :: A %1 -> C
- h x = g y
- where
- y = f x
-
-- Due to an oversight, previous GHC releases (starting from 9.4) allowed the use
- of promoted data types in kinds, even when :extension:`DataKinds` was not
- enabled. That is, GHC would erroneously accept the following code: ::
-
- {-# LANGUAGE NoDataKinds #-}
-
- import Data.Kind (Type)
- import GHC.TypeNats (Nat)
-
- -- Nat shouldn't be allowed here without DataKinds
- data Vec :: Nat -> Type -> Type
-
- This oversight has now been fixed. If you wrote code that took advantage of
- this oversight, you may need to enable :extension:`DataKinds` in your code to
- allow it to compile with GHC 9.10.
-
- For more information on what types are allowed in kinds, see the
- :ref:`promotion` section.
-
-- Using ``forall`` as an identifier is now a parse error, as forewarned
- by :ghc-flag:`-Wforall-identifier`::
-
- forall :: (Variable a, MonadQSAT s m) => m a
- -- parse error on input ‘forall’
-
- Library authors are advised to use a different name for their functions,
- such as ``forAll``, ``for_all``, or ``forall_``.
-
-- GHC Proposal `#65 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0065-type-infix.rst>`_
- "Require namespacing fixity declarations for type names and WARNING/DEPRECATED pragmas" has been partially implemented.
- Now, with :extension:`ExplicitNamespaces` enabled, you can specify the
- namespace of a name in fixity signatures, ``DEPRECATED`` and ``WARNING`` pragmas: ::
-
- type f $ a = f a
- f $ a = f a
-
- infixl 9 type $ -- type-level $ is left-associative with priority 9
- infixr 0 data $ -- term-level $ is right-associative with priority 0
-
- {-# DEPRECATED type D "Use `()` instead" #-} -- this will deprecate type D, but will not touch pattern synonym
- data D = MkD
-
- {-# DEPRECATED data D "Use `MkD` instead" #-} -- this will deprecate pattern synonym only
- pattern D = MkD
-
- pattern Head x <- (head -> x)
- {-# WARNING in "x-partial" data Head [ "This is a partial synonym,"
- , "it throws an error on empty lists."] #-}
-
-- GHC Proposal `#475 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0475-tuple-syntax.rst>`_
- "Non-punning list and tuple syntax" has been partially implemented.
- When the newly introduced extension :extension:`ListTuplePuns` is disabled,
- bracket syntax for lists, tuples and sums only denotes their data
- constructors, while their type constructors have been changed to use regular
- prefix syntax::
-
- data List a = [] | a : List a
- data Tuple2 a b = (a, b)
-
- The extension is enabled by default, establishing the usual behavior.
-
-- In accordance with GHC Proposal `#448 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0448-type-variable-scoping.rst>`_,
- the :extension:`TypeAbstractions` extension has been extended to support
- ``@``-binders in lambdas and function equations::
-
- id :: forall a. a -> a
- id @t x = x :: t
- -- ^^ @-binder in a function equation
-
- e = higherRank (\ @t -> ... )
- -- ^^ @-binder in a lambda
-
- This feature is an experimental alternative to :extension:`ScopedTypeVariables`,
- see the :ref:`type-abstractions-in-functions` section.
-
-Compiler
-~~~~~~~~
-
-- GHC Proposal `#516
- <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0516-incomplete-record-selectors.rst>`_
- has been implemented. It introduces a warning :ghc-flag:`-Wincomplete-record-selectors` which warns about when
- an invocation of a record selector may fail due to being applied to a constructor for which it is not defined.
-
- For example ::
-
- data T = T1 | T2 { x :: Int }
- f :: T -> Int
- f a = x a + 1 -- emit a warning here, since `f T1` will fail
-
- Unlike :ghc-flag:`-Wpartial-fields` this produces a warning about incomplete selectors at use sites instead of
- definition sites, so it is useful in cases when the library does intend for incomplete record selectors to be
- used but only in specific circumstances (e.g. when other cases are handled by previous pattern matches).
-
-- The :ghc-flag:`-finfo-table-map-with-stack` and
- :ghc-flag:`-finfo-table-map-with-fallback` flags have been introduced. These
- flags include ``STACK`` info tables and info tables with default source
- location information in the info table map, respectively. They are implied by
- the :ghc-flag:`-finfo-table-map` flag. The corresponding negative flags
- (:ghc-flag:`-fno-info-table-map-with-stack`,
- :ghc-flag:`-fno-info-table-map-with-fallback`) are useful for omitting these
- info tables from the info table map and reducing the size of executables
- containing info table profiling information. In a test on the `Agda codebase
- <https://github.com/agda/agda>`_, the size of the build results was reduced by
- about 10% when these info tables were omitted.
-
-- Fixed a bug where compiling with both :ghc-flag:`-ddump-timings` and :ghc-flag:`-ddump-to-file` did not
- suppress printing timings to the console. See :ghc-ticket:`20316`.
-
-- Defaulting plugins can now propose solutions to entangled sets of type variables. This allows defaulting
- of multi-parameter type classes. See :ghc-ticket:`23832`.
-
-- The flag `-funbox-small-strict-fields` will now properly recognize unboxed tuples
- containing multiple elements as large. Constructors like `Foo (# Int64, Int64# )`
- will no longer be considered small and therefore not unboxed by default under `-O`
- even when used as strict field. :ghc-ticket:`22309`.
-
-- The flag `-funbox-small-strict-fields` will now always unpack things as if compiling
- for a 64bit platform. Even when generating code for a 32bit platform.
- This makes core optimizations more consistent between 32bit and 64bit platforms
- at the cost of slightly worse 32bit performance in edge cases.
-
-- Type abstractions in constructor patterns that were previously admitted without enabling the :extension:`TypeAbstractions`
- extension now trigger a warning, :ghc-flag:`-Wdeprecated-type-abstractions`.
- This new warning is part of the :ghc-flag:`-Wcompat` warning group and will become an error in a future GHC release.
-
-- The :ghc-flag:`-Wforall-identifier` flag is now deprecated and removed from :ghc-flag:`-Wdefault`,
- as ``forall`` is no longer parsed as an identifier.
-
-- Late plugins have been added. These are plugins which can access and/or modify
- the core of a module after optimization and after interface creation. See :ghc-ticket:`24254`.
-
-- If you use :ghc-flag:`-fllvm` we now use an assembler from the LLVM toolchain rather than
- the preconfigured assembler. This is typically ``clang``. The ``LLVMAS`` environment
- variable can be specified at configure time to instruct GHC which ``clang`` to use.
- This means that if you are using ``-fllvm`` you now need ``llc``, ``opt`` and ``clang``
- available.
-
-- The :ghc-flag:`-fprof-late-overloaded` flag has been introduced. It causes
- cost centres to be added to *overloaded* top level bindings, unlike
- :ghc-flag:`-fprof-late` which adds cost centres to all top level bindings.
-
-- The :ghc-flag:`-fprof-late-overloaded-calls` flag has been introduced. It
- causes cost centres to be inserted at call sites including instance dictionary
- arguments. This may be preferred over :ghc-flag:`-fprof-late-overloaded` since
- it may reveal whether imported functions are called overloaded.
-
-JavaScript backend
-~~~~~~~~~~~~~~~~~~
-
-- The JavaScript backend now supports linking with C sources. It uses Emscripten
- to compile them to WebAssembly. The resulting JS file embeds and loads these
- WebAssembly files. Important note: JavaScript wrappers are required to call
- into C functions and pragmas have been added to indicate which C functions are
- exported (see the users guide).
-
-WebAssembly backend
-~~~~~~~~~~~~~~~~~~~
-
-- The wasm backend now implements JavaScript FFI, allowing JavaScript
- to be called from Haskell and vice versa when targetting JavaScript
- environments like browsers and node.js. See :ref:`JavaScript FFI in
- the wasm backend <wasm-jsffi>` for details.
-
-GHCi
-~~~~
-
-- GHCi now differentiates between adding, unadding, loading, unloading and reloading
- in its responses to using the respective commands. The output with `-fshow-loaded-modules`
- is not changed to keep backwards compatibility for tooling.
-
-Runtime system
-~~~~~~~~~~~~~~
-
-- Internal fragmentation incurred by the non-moving GC's allocator has been reduced for small objects.
- In one real-world application, this has reduced resident set size by about 20% and modestly improved run-time.
- See :ghc-ticket:`23340`.
- :rts-flag:`--nonmoving-dense-allocator-count=⟨count⟩` has been added to fine-tune this behaviour.
-- Add support for heap profiling with the non-moving GC.
- See :ghc-ticket:`22221`.
-
-- Add a :rts-flag:`--no-automatic-time-samples` flag which stops time profiling samples being automatically started on
- startup. Time profiling can be controlled manually using functions in ``GHC.Profiling``.
-
-- Add a :rts-flag:`-xr ⟨size⟩` which controls the size of virtual
- memory address space reserved by the two step allocator on a 64-bit
- platform. The default size is now 1T on aarch64 as well. See
- :ghc-ticket:`24498`.
-
-``base`` library
-~~~~~~~~~~~~~~~~
-
-- Updated to `Unicode 15.1.0 <https://www.unicode.org/versions/Unicode15.1.0/>`_.
-
-- The functions :base-ref:`GHC.Exts.dataToTag#` and
- :base-ref:`GHC.Base.getTag` have had their types changed to the
- following:
-
- ::
-
- dataToTag#, getTag
- :: forall {lev :: Levity} (a :: TYPE (BoxedRep lev))
- . DataToTag a => a -> Int#
-
- In particular, they are now applicable only at some (not all)
- lifted types. However, if ``t`` is an algebraic data type (i.e. ``t``
- matches a ``data`` or ``data instance`` declaration) with all of its
- constructors in scope and the levity of ``t`` is statically known,
- then the constraint ``DataToTag t`` can always be solved.
-
-- Exceptions can now carry arbitrary user-defined annotations via the new
- :base-ref:`GHC.Exception.Type.ExceptionContext` implicit parameter of
- ``SomeException``. These annotations are intended to be used to carry
- context describing the provenance of an exception.
-
-- GHC now collects backtraces for synchronous exceptions. These are carried by
- the exception via the ``ExceptionContext`` mechanism described above.
- GHC supports several mechanisms by which backtraces can be collected which
- can be individually enabled and disabled via
- :base-ref:`GHC.Exception.Backtrace.setEnabledBacktraceMechanisms`.
-
-
-``ghc-prim`` library
-~~~~~~~~~~~~~~~~~~~~
-
-- ``dataToTag#`` has been moved from ``GHC.Prim``. It remains
- exported by ``GHC.Exts``, but with a different type, as described in
- the notes for ``base`` above.
-
-- New primops for unaligned ``Addr#`` access.
- These primops will be emulated on platforms that don't support unaligned access.
- These primops take the form
-
- .. code-block:: haskell
-
- indexWord8OffAddrAs<ty> :: Addr# -> Int# -> <ty>#
- readWord8OffAddrAs<ty> :: Addr# -> Int# -> State# s -> (# State# s, <ty># #)
- writeWord8OffAddrAs<ty> :: Addr# -> Int# -> <ty># -> State# s -> State# s
-
- where ``<ty>`` is one of:
-
- - ``Word``
- - ``Word{16,32,64}``
- - ``Int``
- - ``Int{16,32,64,}``
- - ``Char``
- - ``WideChar``
- - ``Addr``
- - ``Float``
- - ``Double``
- - ``StablePtr``
-
-``ghc`` library
-~~~~~~~~~~~~~~~
-
-``ghc-heap`` library
-~~~~~~~~~~~~~~~~~~~~
-
-``ghc-experimental`` library
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-
-- ``ghc-experimental`` is a new library for functions and data types with
- weaker stability guarantees. Introduced per the HF Technical Proposal `#51
- <https://github.com/haskellfoundation/tech-proposals/blob/main/proposals/accepted/051-ghc-base-libraries.rst>`_.
-
-``template-haskell`` library
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-
-- Extend ``Pat`` with ``TypeP`` and ``Exp`` with ``TypeE``,
- introduce functions ``typeP`` and ``typeE`` (Template Haskell support for GHC Proposal `#281
- <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0281-visible-forall.rst>`_).
-
-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.12.1-notes.rst
=====================================
@@ -0,0 +1,88 @@
+.. _release-9-11-1:
+
+Version 9.12.1
+==============
+
+The significant changes to the various parts of the compiler are listed in the
+following sections. See the `migration guide
+<https://gitlab.haskell.org/ghc/ghc/-/wikis/migration/9.12>`_ on the GHC Wiki
+for specific guidance on migrating programs to this release.
+
+Language
+~~~~~~~~
+
+
+Compiler
+~~~~~~~~
+
+
+GHCi
+~~~~
+
+
+Runtime system
+~~~~~~~~~~~~~~
+
+``base`` library
+~~~~~~~~~~~~~~~~
+
+
+``ghc-prim`` library
+~~~~~~~~~~~~~~~~~~~~
+
+``ghc`` library
+~~~~~~~~~~~~~~~
+
+``ghc-heap`` library
+~~~~~~~~~~~~~~~~~~~~
+
+``ghc-experimental`` library
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+``template-haskell`` 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
+ libraries/os-string/os-string.cabal: Dependency of ``filepath`` library
=====================================
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
=====================================
docs/users_guide/release-notes.rst
=====================================
@@ -4,4 +4,4 @@ Release notes
.. toctree::
:maxdepth: 1
- 9.10.1-notes
+ 9.12.1-notes
=====================================
rts/ARMOutlineAtomicsSymbols.h
=====================================
@@ -10,583 +10,583 @@
#include <stdint.h>
#include <stdatomic.h>
-uint8_t ghc___aarch64_cas1_relax(uint8_t old, uint8_t new, uint8_t* p);
-uint8_t ghc___aarch64_cas1_relax(uint8_t old, uint8_t new, uint8_t* p) {
+uint8_t ghc___aarch64_cas1_relax(uint8_t old, uint8_t new, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_cas1_relax(uint8_t old, uint8_t new, _Atomic uint8_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_relaxed, memory_order_relaxed); return old;
}
-uint8_t ghc___aarch64_cas1_acq(uint8_t old, uint8_t new, uint8_t* p);
-uint8_t ghc___aarch64_cas1_acq(uint8_t old, uint8_t new, uint8_t* p) {
+uint8_t ghc___aarch64_cas1_acq(uint8_t old, uint8_t new, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_cas1_acq(uint8_t old, uint8_t new, _Atomic uint8_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_acquire, memory_order_acquire); return old;
}
-uint8_t ghc___aarch64_cas1_acq_rel(uint8_t old, uint8_t new, uint8_t* p);
-uint8_t ghc___aarch64_cas1_acq_rel(uint8_t old, uint8_t new, uint8_t* p) {
+uint8_t ghc___aarch64_cas1_acq_rel(uint8_t old, uint8_t new, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_cas1_acq_rel(uint8_t old, uint8_t new, _Atomic uint8_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_acq_rel, memory_order_acquire); return old;
}
-uint8_t ghc___aarch64_cas1_sync(uint8_t old, uint8_t new, uint8_t* p);
-uint8_t ghc___aarch64_cas1_sync(uint8_t old, uint8_t new, uint8_t* p) {
+uint8_t ghc___aarch64_cas1_sync(uint8_t old, uint8_t new, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_cas1_sync(uint8_t old, uint8_t new, _Atomic uint8_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_seq_cst, memory_order_seq_cst); return old;
}
-uint16_t ghc___aarch64_cas2_relax(uint16_t old, uint16_t new, uint16_t* p);
-uint16_t ghc___aarch64_cas2_relax(uint16_t old, uint16_t new, uint16_t* p) {
+uint16_t ghc___aarch64_cas2_relax(uint16_t old, uint16_t new, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_cas2_relax(uint16_t old, uint16_t new, _Atomic uint16_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_relaxed, memory_order_relaxed); return old;
}
-uint16_t ghc___aarch64_cas2_acq(uint16_t old, uint16_t new, uint16_t* p);
-uint16_t ghc___aarch64_cas2_acq(uint16_t old, uint16_t new, uint16_t* p) {
+uint16_t ghc___aarch64_cas2_acq(uint16_t old, uint16_t new, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_cas2_acq(uint16_t old, uint16_t new, _Atomic uint16_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_acquire, memory_order_acquire); return old;
}
-uint16_t ghc___aarch64_cas2_acq_rel(uint16_t old, uint16_t new, uint16_t* p);
-uint16_t ghc___aarch64_cas2_acq_rel(uint16_t old, uint16_t new, uint16_t* p) {
+uint16_t ghc___aarch64_cas2_acq_rel(uint16_t old, uint16_t new, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_cas2_acq_rel(uint16_t old, uint16_t new, _Atomic uint16_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_acq_rel, memory_order_acquire); return old;
}
-uint16_t ghc___aarch64_cas2_sync(uint16_t old, uint16_t new, uint16_t* p);
-uint16_t ghc___aarch64_cas2_sync(uint16_t old, uint16_t new, uint16_t* p) {
+uint16_t ghc___aarch64_cas2_sync(uint16_t old, uint16_t new, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_cas2_sync(uint16_t old, uint16_t new, _Atomic uint16_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_seq_cst, memory_order_seq_cst); return old;
}
-uint32_t ghc___aarch64_cas4_relax(uint32_t old, uint32_t new, uint32_t* p);
-uint32_t ghc___aarch64_cas4_relax(uint32_t old, uint32_t new, uint32_t* p) {
+uint32_t ghc___aarch64_cas4_relax(uint32_t old, uint32_t new, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_cas4_relax(uint32_t old, uint32_t new, _Atomic uint32_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_relaxed, memory_order_relaxed); return old;
}
-uint32_t ghc___aarch64_cas4_acq(uint32_t old, uint32_t new, uint32_t* p);
-uint32_t ghc___aarch64_cas4_acq(uint32_t old, uint32_t new, uint32_t* p) {
+uint32_t ghc___aarch64_cas4_acq(uint32_t old, uint32_t new, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_cas4_acq(uint32_t old, uint32_t new, _Atomic uint32_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_acquire, memory_order_acquire); return old;
}
-uint32_t ghc___aarch64_cas4_acq_rel(uint32_t old, uint32_t new, uint32_t* p);
-uint32_t ghc___aarch64_cas4_acq_rel(uint32_t old, uint32_t new, uint32_t* p) {
+uint32_t ghc___aarch64_cas4_acq_rel(uint32_t old, uint32_t new, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_cas4_acq_rel(uint32_t old, uint32_t new, _Atomic uint32_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_acq_rel, memory_order_acquire); return old;
}
-uint32_t ghc___aarch64_cas4_sync(uint32_t old, uint32_t new, uint32_t* p);
-uint32_t ghc___aarch64_cas4_sync(uint32_t old, uint32_t new, uint32_t* p) {
+uint32_t ghc___aarch64_cas4_sync(uint32_t old, uint32_t new, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_cas4_sync(uint32_t old, uint32_t new, _Atomic uint32_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_seq_cst, memory_order_seq_cst); return old;
}
-uint64_t ghc___aarch64_cas8_relax(uint64_t old, uint64_t new, uint64_t* p);
-uint64_t ghc___aarch64_cas8_relax(uint64_t old, uint64_t new, uint64_t* p) {
+uint64_t ghc___aarch64_cas8_relax(uint64_t old, uint64_t new, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_cas8_relax(uint64_t old, uint64_t new, _Atomic uint64_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_relaxed, memory_order_relaxed); return old;
}
-uint64_t ghc___aarch64_cas8_acq(uint64_t old, uint64_t new, uint64_t* p);
-uint64_t ghc___aarch64_cas8_acq(uint64_t old, uint64_t new, uint64_t* p) {
+uint64_t ghc___aarch64_cas8_acq(uint64_t old, uint64_t new, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_cas8_acq(uint64_t old, uint64_t new, _Atomic uint64_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_acquire, memory_order_acquire); return old;
}
-uint64_t ghc___aarch64_cas8_acq_rel(uint64_t old, uint64_t new, uint64_t* p);
-uint64_t ghc___aarch64_cas8_acq_rel(uint64_t old, uint64_t new, uint64_t* p) {
+uint64_t ghc___aarch64_cas8_acq_rel(uint64_t old, uint64_t new, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_cas8_acq_rel(uint64_t old, uint64_t new, _Atomic uint64_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_acq_rel, memory_order_acquire); return old;
}
-uint64_t ghc___aarch64_cas8_sync(uint64_t old, uint64_t new, uint64_t* p);
-uint64_t ghc___aarch64_cas8_sync(uint64_t old, uint64_t new, uint64_t* p) {
+uint64_t ghc___aarch64_cas8_sync(uint64_t old, uint64_t new, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_cas8_sync(uint64_t old, uint64_t new, _Atomic uint64_t* p) {
atomic_compare_exchange_strong_explicit(p, &old, new, memory_order_seq_cst, memory_order_seq_cst); return old;
}
-uint8_t ghc___aarch64_swp1_relax(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_swp1_relax(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_swp1_relax(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_swp1_relax(uint8_t v, _Atomic uint8_t* p) {
return atomic_exchange_explicit(p, v, memory_order_relaxed);
}
-uint8_t ghc___aarch64_swp1_acq(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_swp1_acq(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_swp1_acq(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_swp1_acq(uint8_t v, _Atomic uint8_t* p) {
return atomic_exchange_explicit(p, v, memory_order_acquire);
}
-uint8_t ghc___aarch64_swp1_rel(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_swp1_rel(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_swp1_rel(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_swp1_rel(uint8_t v, _Atomic uint8_t* p) {
return atomic_exchange_explicit(p, v, memory_order_release);
}
-uint8_t ghc___aarch64_swp1_acq_rel(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_swp1_acq_rel(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_swp1_acq_rel(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_swp1_acq_rel(uint8_t v, _Atomic uint8_t* p) {
return atomic_exchange_explicit(p, v, memory_order_acq_rel);
}
-uint8_t ghc___aarch64_swp1_sync(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_swp1_sync(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_swp1_sync(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_swp1_sync(uint8_t v, _Atomic uint8_t* p) {
return atomic_exchange_explicit(p, v, memory_order_seq_cst);
}
-uint16_t ghc___aarch64_swp2_relax(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_swp2_relax(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_swp2_relax(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_swp2_relax(uint16_t v, _Atomic uint16_t* p) {
return atomic_exchange_explicit(p, v, memory_order_relaxed);
}
-uint16_t ghc___aarch64_swp2_acq(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_swp2_acq(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_swp2_acq(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_swp2_acq(uint16_t v, _Atomic uint16_t* p) {
return atomic_exchange_explicit(p, v, memory_order_acquire);
}
-uint16_t ghc___aarch64_swp2_rel(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_swp2_rel(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_swp2_rel(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_swp2_rel(uint16_t v, _Atomic uint16_t* p) {
return atomic_exchange_explicit(p, v, memory_order_release);
}
-uint16_t ghc___aarch64_swp2_acq_rel(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_swp2_acq_rel(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_swp2_acq_rel(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_swp2_acq_rel(uint16_t v, _Atomic uint16_t* p) {
return atomic_exchange_explicit(p, v, memory_order_acq_rel);
}
-uint16_t ghc___aarch64_swp2_sync(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_swp2_sync(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_swp2_sync(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_swp2_sync(uint16_t v, _Atomic uint16_t* p) {
return atomic_exchange_explicit(p, v, memory_order_seq_cst);
}
-uint32_t ghc___aarch64_swp4_relax(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_swp4_relax(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_swp4_relax(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_swp4_relax(uint32_t v, _Atomic uint32_t* p) {
return atomic_exchange_explicit(p, v, memory_order_relaxed);
}
-uint32_t ghc___aarch64_swp4_acq(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_swp4_acq(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_swp4_acq(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_swp4_acq(uint32_t v, _Atomic uint32_t* p) {
return atomic_exchange_explicit(p, v, memory_order_acquire);
}
-uint32_t ghc___aarch64_swp4_rel(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_swp4_rel(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_swp4_rel(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_swp4_rel(uint32_t v, _Atomic uint32_t* p) {
return atomic_exchange_explicit(p, v, memory_order_release);
}
-uint32_t ghc___aarch64_swp4_acq_rel(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_swp4_acq_rel(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_swp4_acq_rel(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_swp4_acq_rel(uint32_t v, _Atomic uint32_t* p) {
return atomic_exchange_explicit(p, v, memory_order_acq_rel);
}
-uint32_t ghc___aarch64_swp4_sync(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_swp4_sync(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_swp4_sync(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_swp4_sync(uint32_t v, _Atomic uint32_t* p) {
return atomic_exchange_explicit(p, v, memory_order_seq_cst);
}
-uint64_t ghc___aarch64_swp8_relax(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_swp8_relax(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_swp8_relax(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_swp8_relax(uint64_t v, _Atomic uint64_t* p) {
return atomic_exchange_explicit(p, v, memory_order_relaxed);
}
-uint64_t ghc___aarch64_swp8_acq(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_swp8_acq(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_swp8_acq(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_swp8_acq(uint64_t v, _Atomic uint64_t* p) {
return atomic_exchange_explicit(p, v, memory_order_acquire);
}
-uint64_t ghc___aarch64_swp8_rel(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_swp8_rel(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_swp8_rel(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_swp8_rel(uint64_t v, _Atomic uint64_t* p) {
return atomic_exchange_explicit(p, v, memory_order_release);
}
-uint64_t ghc___aarch64_swp8_acq_rel(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_swp8_acq_rel(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_swp8_acq_rel(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_swp8_acq_rel(uint64_t v, _Atomic uint64_t* p) {
return atomic_exchange_explicit(p, v, memory_order_acq_rel);
}
-uint64_t ghc___aarch64_swp8_sync(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_swp8_sync(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_swp8_sync(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_swp8_sync(uint64_t v, _Atomic uint64_t* p) {
return atomic_exchange_explicit(p, v, memory_order_seq_cst);
}
-uint8_t ghc___aarch64_ldadd1_relax(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldadd1_relax(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldadd1_relax(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldadd1_relax(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_relaxed);
}
-uint8_t ghc___aarch64_ldadd1_acq(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldadd1_acq(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldadd1_acq(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldadd1_acq(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_acquire);
}
-uint8_t ghc___aarch64_ldadd1_rel(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldadd1_rel(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldadd1_rel(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldadd1_rel(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_release);
}
-uint8_t ghc___aarch64_ldadd1_acq_rel(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldadd1_acq_rel(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldadd1_acq_rel(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldadd1_acq_rel(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_acq_rel);
}
-uint8_t ghc___aarch64_ldadd1_sync(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldadd1_sync(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldadd1_sync(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldadd1_sync(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_seq_cst);
}
-uint16_t ghc___aarch64_ldadd2_relax(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldadd2_relax(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldadd2_relax(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldadd2_relax(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_relaxed);
}
-uint16_t ghc___aarch64_ldadd2_acq(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldadd2_acq(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldadd2_acq(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldadd2_acq(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_acquire);
}
-uint16_t ghc___aarch64_ldadd2_rel(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldadd2_rel(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldadd2_rel(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldadd2_rel(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_release);
}
-uint16_t ghc___aarch64_ldadd2_acq_rel(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldadd2_acq_rel(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldadd2_acq_rel(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldadd2_acq_rel(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_acq_rel);
}
-uint16_t ghc___aarch64_ldadd2_sync(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldadd2_sync(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldadd2_sync(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldadd2_sync(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_seq_cst);
}
-uint32_t ghc___aarch64_ldadd4_relax(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldadd4_relax(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldadd4_relax(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldadd4_relax(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_relaxed);
}
-uint32_t ghc___aarch64_ldadd4_acq(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldadd4_acq(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldadd4_acq(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldadd4_acq(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_acquire);
}
-uint32_t ghc___aarch64_ldadd4_rel(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldadd4_rel(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldadd4_rel(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldadd4_rel(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_release);
}
-uint32_t ghc___aarch64_ldadd4_acq_rel(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldadd4_acq_rel(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldadd4_acq_rel(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldadd4_acq_rel(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_acq_rel);
}
-uint32_t ghc___aarch64_ldadd4_sync(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldadd4_sync(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldadd4_sync(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldadd4_sync(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_seq_cst);
}
-uint64_t ghc___aarch64_ldadd8_relax(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldadd8_relax(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldadd8_relax(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldadd8_relax(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_relaxed);
}
-uint64_t ghc___aarch64_ldadd8_acq(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldadd8_acq(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldadd8_acq(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldadd8_acq(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_acquire);
}
-uint64_t ghc___aarch64_ldadd8_rel(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldadd8_rel(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldadd8_rel(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldadd8_rel(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_release);
}
-uint64_t ghc___aarch64_ldadd8_acq_rel(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldadd8_acq_rel(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldadd8_acq_rel(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldadd8_acq_rel(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_acq_rel);
}
-uint64_t ghc___aarch64_ldadd8_sync(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldadd8_sync(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldadd8_sync(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldadd8_sync(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_add_explicit(p, v, memory_order_seq_cst);
}
-uint8_t ghc___aarch64_ldclr1_relax(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldclr1_relax(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldclr1_relax(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldclr1_relax(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_relaxed);
}
-uint8_t ghc___aarch64_ldclr1_acq(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldclr1_acq(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldclr1_acq(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldclr1_acq(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_acquire);
}
-uint8_t ghc___aarch64_ldclr1_rel(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldclr1_rel(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldclr1_rel(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldclr1_rel(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_release);
}
-uint8_t ghc___aarch64_ldclr1_acq_rel(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldclr1_acq_rel(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldclr1_acq_rel(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldclr1_acq_rel(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_acq_rel);
}
-uint8_t ghc___aarch64_ldclr1_sync(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldclr1_sync(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldclr1_sync(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldclr1_sync(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_seq_cst);
}
-uint16_t ghc___aarch64_ldclr2_relax(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldclr2_relax(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldclr2_relax(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldclr2_relax(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_relaxed);
}
-uint16_t ghc___aarch64_ldclr2_acq(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldclr2_acq(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldclr2_acq(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldclr2_acq(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_acquire);
}
-uint16_t ghc___aarch64_ldclr2_rel(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldclr2_rel(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldclr2_rel(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldclr2_rel(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_release);
}
-uint16_t ghc___aarch64_ldclr2_acq_rel(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldclr2_acq_rel(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldclr2_acq_rel(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldclr2_acq_rel(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_acq_rel);
}
-uint16_t ghc___aarch64_ldclr2_sync(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldclr2_sync(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldclr2_sync(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldclr2_sync(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_seq_cst);
}
-uint32_t ghc___aarch64_ldclr4_relax(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldclr4_relax(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldclr4_relax(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldclr4_relax(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_relaxed);
}
-uint32_t ghc___aarch64_ldclr4_acq(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldclr4_acq(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldclr4_acq(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldclr4_acq(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_acquire);
}
-uint32_t ghc___aarch64_ldclr4_rel(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldclr4_rel(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldclr4_rel(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldclr4_rel(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_release);
}
-uint32_t ghc___aarch64_ldclr4_acq_rel(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldclr4_acq_rel(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldclr4_acq_rel(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldclr4_acq_rel(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_acq_rel);
}
-uint32_t ghc___aarch64_ldclr4_sync(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldclr4_sync(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldclr4_sync(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldclr4_sync(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_seq_cst);
}
-uint64_t ghc___aarch64_ldclr8_relax(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldclr8_relax(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldclr8_relax(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldclr8_relax(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_relaxed);
}
-uint64_t ghc___aarch64_ldclr8_acq(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldclr8_acq(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldclr8_acq(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldclr8_acq(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_acquire);
}
-uint64_t ghc___aarch64_ldclr8_rel(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldclr8_rel(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldclr8_rel(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldclr8_rel(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_release);
}
-uint64_t ghc___aarch64_ldclr8_acq_rel(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldclr8_acq_rel(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldclr8_acq_rel(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldclr8_acq_rel(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_acq_rel);
}
-uint64_t ghc___aarch64_ldclr8_sync(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldclr8_sync(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldclr8_sync(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldclr8_sync(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_and_explicit(p, v, memory_order_seq_cst);
}
-uint8_t ghc___aarch64_ldeor1_relax(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldeor1_relax(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldeor1_relax(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldeor1_relax(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_relaxed);
}
-uint8_t ghc___aarch64_ldeor1_acq(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldeor1_acq(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldeor1_acq(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldeor1_acq(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_acquire);
}
-uint8_t ghc___aarch64_ldeor1_rel(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldeor1_rel(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldeor1_rel(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldeor1_rel(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_release);
}
-uint8_t ghc___aarch64_ldeor1_acq_rel(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldeor1_acq_rel(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldeor1_acq_rel(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldeor1_acq_rel(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_acq_rel);
}
-uint8_t ghc___aarch64_ldeor1_sync(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldeor1_sync(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldeor1_sync(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldeor1_sync(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_seq_cst);
}
-uint16_t ghc___aarch64_ldeor2_relax(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldeor2_relax(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldeor2_relax(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldeor2_relax(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_relaxed);
}
-uint16_t ghc___aarch64_ldeor2_acq(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldeor2_acq(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldeor2_acq(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldeor2_acq(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_acquire);
}
-uint16_t ghc___aarch64_ldeor2_rel(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldeor2_rel(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldeor2_rel(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldeor2_rel(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_release);
}
-uint16_t ghc___aarch64_ldeor2_acq_rel(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldeor2_acq_rel(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldeor2_acq_rel(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldeor2_acq_rel(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_acq_rel);
}
-uint16_t ghc___aarch64_ldeor2_sync(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldeor2_sync(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldeor2_sync(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldeor2_sync(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_seq_cst);
}
-uint32_t ghc___aarch64_ldeor4_relax(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldeor4_relax(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldeor4_relax(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldeor4_relax(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_relaxed);
}
-uint32_t ghc___aarch64_ldeor4_acq(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldeor4_acq(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldeor4_acq(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldeor4_acq(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_acquire);
}
-uint32_t ghc___aarch64_ldeor4_rel(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldeor4_rel(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldeor4_rel(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldeor4_rel(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_release);
}
-uint32_t ghc___aarch64_ldeor4_acq_rel(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldeor4_acq_rel(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldeor4_acq_rel(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldeor4_acq_rel(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_acq_rel);
}
-uint32_t ghc___aarch64_ldeor4_sync(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldeor4_sync(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldeor4_sync(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldeor4_sync(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_seq_cst);
}
-uint64_t ghc___aarch64_ldeor8_relax(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldeor8_relax(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldeor8_relax(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldeor8_relax(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_relaxed);
}
-uint64_t ghc___aarch64_ldeor8_acq(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldeor8_acq(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldeor8_acq(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldeor8_acq(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_acquire);
}
-uint64_t ghc___aarch64_ldeor8_rel(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldeor8_rel(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldeor8_rel(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldeor8_rel(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_release);
}
-uint64_t ghc___aarch64_ldeor8_acq_rel(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldeor8_acq_rel(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldeor8_acq_rel(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldeor8_acq_rel(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_acq_rel);
}
-uint64_t ghc___aarch64_ldeor8_sync(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldeor8_sync(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldeor8_sync(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldeor8_sync(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_xor_explicit(p, v, memory_order_seq_cst);
}
-uint8_t ghc___aarch64_ldset1_relax(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldset1_relax(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldset1_relax(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldset1_relax(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_relaxed);
}
-uint8_t ghc___aarch64_ldset1_acq(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldset1_acq(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldset1_acq(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldset1_acq(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_acquire);
}
-uint8_t ghc___aarch64_ldset1_rel(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldset1_rel(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldset1_rel(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldset1_rel(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_release);
}
-uint8_t ghc___aarch64_ldset1_acq_rel(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldset1_acq_rel(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldset1_acq_rel(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldset1_acq_rel(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_acq_rel);
}
-uint8_t ghc___aarch64_ldset1_sync(uint8_t v, uint8_t* p);
-uint8_t ghc___aarch64_ldset1_sync(uint8_t v, uint8_t* p) {
+uint8_t ghc___aarch64_ldset1_sync(uint8_t v, _Atomic uint8_t* p);
+uint8_t ghc___aarch64_ldset1_sync(uint8_t v, _Atomic uint8_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_seq_cst);
}
-uint16_t ghc___aarch64_ldset2_relax(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldset2_relax(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldset2_relax(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldset2_relax(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_relaxed);
}
-uint16_t ghc___aarch64_ldset2_acq(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldset2_acq(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldset2_acq(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldset2_acq(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_acquire);
}
-uint16_t ghc___aarch64_ldset2_rel(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldset2_rel(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldset2_rel(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldset2_rel(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_release);
}
-uint16_t ghc___aarch64_ldset2_acq_rel(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldset2_acq_rel(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldset2_acq_rel(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldset2_acq_rel(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_acq_rel);
}
-uint16_t ghc___aarch64_ldset2_sync(uint16_t v, uint16_t* p);
-uint16_t ghc___aarch64_ldset2_sync(uint16_t v, uint16_t* p) {
+uint16_t ghc___aarch64_ldset2_sync(uint16_t v, _Atomic uint16_t* p);
+uint16_t ghc___aarch64_ldset2_sync(uint16_t v, _Atomic uint16_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_seq_cst);
}
-uint32_t ghc___aarch64_ldset4_relax(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldset4_relax(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldset4_relax(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldset4_relax(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_relaxed);
}
-uint32_t ghc___aarch64_ldset4_acq(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldset4_acq(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldset4_acq(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldset4_acq(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_acquire);
}
-uint32_t ghc___aarch64_ldset4_rel(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldset4_rel(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldset4_rel(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldset4_rel(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_release);
}
-uint32_t ghc___aarch64_ldset4_acq_rel(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldset4_acq_rel(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldset4_acq_rel(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldset4_acq_rel(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_acq_rel);
}
-uint32_t ghc___aarch64_ldset4_sync(uint32_t v, uint32_t* p);
-uint32_t ghc___aarch64_ldset4_sync(uint32_t v, uint32_t* p) {
+uint32_t ghc___aarch64_ldset4_sync(uint32_t v, _Atomic uint32_t* p);
+uint32_t ghc___aarch64_ldset4_sync(uint32_t v, _Atomic uint32_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_seq_cst);
}
-uint64_t ghc___aarch64_ldset8_relax(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldset8_relax(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldset8_relax(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldset8_relax(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_relaxed);
}
-uint64_t ghc___aarch64_ldset8_acq(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldset8_acq(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldset8_acq(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldset8_acq(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_acquire);
}
-uint64_t ghc___aarch64_ldset8_rel(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldset8_rel(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldset8_rel(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldset8_rel(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_release);
}
-uint64_t ghc___aarch64_ldset8_acq_rel(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldset8_acq_rel(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldset8_acq_rel(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldset8_acq_rel(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_acq_rel);
}
-uint64_t ghc___aarch64_ldset8_sync(uint64_t v, uint64_t* p);
-uint64_t ghc___aarch64_ldset8_sync(uint64_t v, uint64_t* p) {
+uint64_t ghc___aarch64_ldset8_sync(uint64_t v, _Atomic uint64_t* p);
+uint64_t ghc___aarch64_ldset8_sync(uint64_t v, _Atomic uint64_t* p) {
return atomic_fetch_or_explicit(p, v, memory_order_seq_cst);
}
=====================================
testsuite/tests/codeGen/should_run/T24507.hs
=====================================
@@ -0,0 +1,15 @@
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE GHCForeignImportPrim #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+
+module Main where
+
+import GHC.Exts
+
+foreign import prim "foo" foo :: Int# -> Int#
+
+main = do
+
+ let f x = case x of I# x' -> case foo x' of x -> print (I# x)
+ mapM_ f [1..7]
\ No newline at end of file
=====================================
testsuite/tests/codeGen/should_run/T24507.stdout
=====================================
@@ -0,0 +1,7 @@
+1
+2
+2
+2
+2
+2
+2
=====================================
testsuite/tests/codeGen/should_run/T24507_cmm.cmm
=====================================
@@ -0,0 +1,35 @@
+#include "Cmm.h"
+
+bar() {
+ return (2);
+}
+
+foo(W_ x) {
+
+ switch(x) {
+ case 1: goto a;
+ case 2: goto b;
+ case 3: goto c;
+ case 4: goto d;
+ case 5: goto e;
+ case 6: goto f;
+ case 7: goto g;
+ }
+ return (1);
+
+ a:
+ return (1);
+ b:
+ jump bar();
+ c:
+ jump bar();
+ d:
+ jump bar();
+ e:
+ jump bar();
+ f:
+ jump bar();
+ g:
+ jump bar();
+
+}
=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -243,3 +243,6 @@ test('MulMayOflo_full',
test('T24264run', normal, compile_and_run, [''])
test('T24295a', normal, compile_and_run, ['-O -floopification'])
test('T24295b', normal, compile_and_run, ['-O -floopification -fpedantic-bottoms'])
+
+test('T24507', [req_cmm], multi_compile_and_run,
+ ['T24507', [('T24507_cmm.cmm', '')], '-O2'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/646d254a2a64f26db6638ea2c4ef78a434b7e967...70398925624c2fc615db98eab4ba337e7099d01f
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/646d254a2a64f26db6638ea2c4ef78a434b7e967...70398925624c2fc615db98eab4ba337e7099d01f
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/20240325/17263b8b/attachment-0001.html>
More information about the ghc-commits
mailing list