
Ben Gamari pushed to branch ghc-9.14 at Glasgow Haskell Compiler / GHC Commits: 4d8eec9a by Ben Gamari at 2025-09-02T08:58:18-04:00 Revert "STM: don't create a transaction in the rhs of catchRetry# (#26028)" This appears to have been the cause of runtime crashes (#26291). This reverts commit 712da3565dcdeea17f3d1fc71e026839ede56533. - - - - - 0980f3d6 by Ben Gamari at 2025-09-02T08:58:53-04:00 users-guide/relnotes: More stylistic fixes - - - - - 5f9c0b62 by Ben Gamari at 2025-09-02T08:58:53-04:00 users-guide: Various release notes additions - - - - - 7 changed files: - docs/users_guide/9.14.1-notes.rst - rts/PrimOps.cmm - rts/RaiseAsync.c - rts/STM.c - − testsuite/tests/lib/stm/T26028.hs - − testsuite/tests/lib/stm/T26028.stdout - − testsuite/tests/lib/stm/all.T Changes: ===================================== docs/users_guide/9.14.1-notes.rst ===================================== @@ -25,6 +25,14 @@ Language This deprecation is controlled by the newly introduced ``-Wdeprecated-pragmas`` flag in ``-Wdefault``. +* Visible ``GADT`` syntax can now be used in GADT data constructors (:ghc-ticket:`25127`) :: + + data KindVal a where + K :: forall k. + forall (a::k) -> -- now allowed! + k -> + KindVal a + * ``-Wincomplete-record-selectors`` is now part of `-Wall`, as specified by `GHC Proposal 516: add warning for incomplete record selectors https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0516-in...`_. Hence, if a library is compiled with ``-Werror``, compilation may now fail. Solution: fix the library. @@ -52,7 +60,7 @@ Language That will break the combination of :extension:`OverloadedRecordUpdate` with :extension:`RebindableSyntax`. -* Multiline strings are now accepted in foreign imports. (#25157) +* Multiline strings are now accepted in ``foreign import``\ s. (#25157) * GHC now does a better job at inferring types in calls to ``coerce``: instead of complaining about ambiguous type variables, GHC will consider that such type @@ -73,7 +81,7 @@ Language * The ``-Wdata-kinds-tc`` warning has been deprecated, and the use of promoted data types in kinds is now an error (rather than a warning) unless the :extension:`DataKinds` extension is enabled. For example, the following code - will be rejected unless :extension:`DataKinds` is on: + will be rejected unless :extension:`DataKinds` is on: :: import Data.Kind (Type) import GHC.TypeNats (Nat) @@ -99,6 +107,9 @@ Language See :ref:`visible-forall-in-gadts` for details. +- Explicit level import support, allowing ``import`` declarations to explicitly + state which compilation stages they are are visible to. + Compiler ~~~~~~~~ @@ -143,20 +154,27 @@ Compiler were accessed using the generated record selector functions, marking the fields as covered in coverage reports (:ghc-ticket:`17834`). -- SIMD support in the X86 native code generator has been extended with 128-bit +- SIMD support in the x86 native code generator has been extended with 128-bit integer operations. Also, ``shuffleFloatX4#`` and ``shuffleDoubleX2#`` no longer require ``-mavx``. +- Initial native code generator support for the LoongArch CPU architecture. + + GHCi ~~~~ -- :ghci-cmd:`:info` now outputs type declarations with @-binders that are +- Multiple home unit support in GHCi + +- :ghci-cmd:`:info` now outputs type declarations with ``@``-binders that are considered semantically significant. See the documentation for :ghci-cmd:`:info` itself for a more detailed explanation. - GHCi errors and warnings now have their own numeric error codes that are displayed alongside the error. +- Many performance and correctness improvements in the bytecode interpreter. + Runtime system ~~~~~~~~~~~~~~ @@ -176,40 +194,40 @@ Cmm ``ghc`` library ~~~~~~~~~~~~~~~ -* The `UnknownDiagnostic` constructor now takes an additional type argument +* The ``UnknownDiagnostic`` constructor now takes an additional type argument for the type of hints corresponding to the diagnostic, and an additional value-level argument used for existential wrapping of the hints of the inner diagnostic. * Changes to the HPT and HUG interface: - - `addToHpt` and `addListToHPT` were moved from `GHC.Unit.Home.ModInfo` to `GHC.Unit.Home.PackageTable` and deprecated in favour of `addHomeModInfoToHpt` and `addHomeModInfosToHpt`. - - `UnitEnvGraph` and operations `unitEnv_lookup_maybe`, `unitEnv_foldWithKey, `unitEnv_singleton`, `unitEnv_adjust`, `unitEnv_insert`, `unitEnv_new` were moved from `GHC.Unit.Env` to `GHC.Unit.Home.Graph`. - - The HomePackageTable (HPT) is now exported from `GHC.Unit.Home.PackageTable`, + - ``addToHpt`` and ``addListToHPT`` were moved from ``GHC.Unit.Home.ModInfo`` to ``GHC.Unit.Home.PackageTable`` and deprecated in favour of ``addHomeModInfoToHpt`` and ``addHomeModInfosToHpt``. + - ``UnitEnvGraph`` and operations ``unitEnv_lookup_maybe``, ``unitEnv_foldWithKey, ``unitEnv_singleton``, ``unitEnv_adjust``, ``unitEnv_insert``, ``unitEnv_new`` were moved from ``GHC.Unit.Env`` to ``GHC.Unit.Home.Graph``. + - The HomePackageTable (HPT) is now exported from ``GHC.Unit.Home.PackageTable``, and is now backed by an IORef to avoid by construction very bad memory leaks. This means the API to the HPT now is for the most part in IO. For instance, - `emptyHomePackageTable` and `addHomeModInfoToHpt` are now in IO. - - `mkHomeUnitEnv` was moved to `GHC.Unit.Home.PackageTable`, and now takes two - extra explicit arguments. To restore previous behaviour, pass `emptyUnitState` - and `Nothing` as the first two arguments additionally. - - `hugElts` was removed. Users should prefer `allUnits` to get the keys of the - HUG (the typical use case), or `traverse` or `unitEnv_foldWithKey` in other + ``emptyHomePackageTable`` and ``addHomeModInfoToHpt`` are now in IO. + - ``mkHomeUnitEnv`` was moved to ``GHC.Unit.Home.PackageTable``, and now takes two + extra explicit arguments. To restore previous behaviour, pass ``emptyUnitState`` + and ``Nothing`` as the first two arguments additionally. + - ``hugElts`` was removed. Users should prefer ``allUnits`` to get the keys of the + HUG (the typical use case), or ``traverse`` or ``unitEnv_foldWithKey`` in other cases. -* Changes to `Language.Haskell.Syntax.Expr` +* Changes to ``Language.Haskell.Syntax.Expr`` - - The `ParStmtBlock` list argument of the `ParStmt` constructor of `StmtLR` is now `NonEmpty`. + - The ``ParStmtBlock`` list argument of the ``ParStmt`` constructor of ``StmtLR`` is now ``NonEmpty``. -* As part of the implementation of `GHC proposal 493 https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0493-sp...`_, - the `SpecSig` constructor of `Sig` has been deprecated. It is replaced by - the constructor `SpecSigE` which supports expressions at the head, rather than +* As part of the implementation of ``GHC proposal 493 https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0493-sp...``_, + the ``SpecSig`` constructor of ``Sig`` has been deprecated. It is replaced by + the constructor ``SpecSigE`` which supports expressions at the head, rather than a lone variable. ``ghc-heap`` library ~~~~~~~~~~~~~~~~~~~~ -* The functions `getClosureInfoTbl_maybe`, `getClosureInfoTbl`, - `getClosurePtrArgs` and `getClosurePtrArgs_maybe` have been added to allow +* The functions ``getClosureInfoTbl_maybe``, ``getClosureInfoTbl``, + ``getClosurePtrArgs`` and ``getClosurePtrArgs_maybe`` have been added to allow reading of the relevant Closure attributes without reliance on incomplete selectors. @@ -225,7 +243,6 @@ Cmm ``ghc-experimental`` versions. - ``template-haskell`` library ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== rts/PrimOps.cmm ===================================== @@ -1210,27 +1210,16 @@ INFO_TABLE_RET(stg_catch_retry_frame, CATCH_RETRY_FRAME, gcptr trec, outer, arg; trec = StgTSO_trec(CurrentTSO); - if (running_alt_code != 1) { - // When exiting the lhs code of catchRetry# lhs rhs, we need to cleanup - // the nested transaction. - // See Note [catchRetry# implementation] - outer = StgTRecHeader_enclosing_trec(trec); - (r) = ccall stmCommitNestedTransaction(MyCapability() "ptr", trec "ptr"); - if (r != 0) { - // Succeeded in first branch - StgTSO_trec(CurrentTSO) = outer; - return (ret); - } else { - // Did not commit: abort and restart. - StgTSO_trec(CurrentTSO) = outer; - jump stg_abort(); - } - } - else { - // nothing to do in the rhs code of catchRetry# lhs rhs, it's already - // using the parent transaction (not a nested one). - // See Note [catchRetry# implementation] - return (ret); + outer = StgTRecHeader_enclosing_trec(trec); + (r) = ccall stmCommitNestedTransaction(MyCapability() "ptr", trec "ptr"); + if (r != 0) { + // Succeeded (either first branch or second branch) + StgTSO_trec(CurrentTSO) = outer; + return (ret); + } else { + // Did not commit: abort and restart. + StgTSO_trec(CurrentTSO) = outer; + jump stg_abort(); } } @@ -1463,26 +1452,21 @@ retry_pop_stack: outer = StgTRecHeader_enclosing_trec(trec); if (frame_type == CATCH_RETRY_FRAME) { - // The retry reaches a CATCH_RETRY_FRAME before the ATOMICALLY_FRAME - + // The retry reaches a CATCH_RETRY_FRAME before the atomic frame + ASSERT(outer != NO_TREC); + // Abort the transaction attempting the current branch + ccall stmAbortTransaction(MyCapability() "ptr", trec "ptr"); + ccall stmFreeAbortedTRec(MyCapability() "ptr", trec "ptr"); if (!StgCatchRetryFrame_running_alt_code(frame) != 0) { - // Retrying in the lhs of catchRetry# lhs rhs, i.e. in a nested - // transaction. See Note [catchRetry# implementation] - - // check that we have a parent transaction - ASSERT(outer != NO_TREC); - - // Abort the nested transaction - ccall stmAbortTransaction(MyCapability() "ptr", trec "ptr"); - ccall stmFreeAbortedTRec(MyCapability() "ptr", trec "ptr"); - - // As we are retrying in the lhs code, we must now try the rhs code - StgTSO_trec(CurrentTSO) = outer; + // Retry in the first branch: try the alternative + ("ptr" trec) = ccall stmStartTransaction(MyCapability() "ptr", outer "ptr"); + StgTSO_trec(CurrentTSO) = trec; StgCatchRetryFrame_running_alt_code(frame) = 1 :: CInt; // true; R1 = StgCatchRetryFrame_alt_code(frame); jump stg_ap_v_fast [R1]; } else { - // Retry in the rhs code: propagate the retry + // Retry in the alternative code: propagate the retry + StgTSO_trec(CurrentTSO) = outer; Sp = Sp + SIZEOF_StgCatchRetryFrame; goto retry_pop_stack; } ===================================== rts/RaiseAsync.c ===================================== @@ -1043,7 +1043,8 @@ raiseAsync(Capability *cap, StgTSO *tso, StgClosure *exception, } case CATCH_STM_FRAME: - // CATCH_STM frame within an atomically block: abort the + case CATCH_RETRY_FRAME: + // CATCH frames within an atomically block: abort the // inner transaction and continue. Eventually we will // hit the outer transaction that will get frozen (see // above). @@ -1055,40 +1056,14 @@ raiseAsync(Capability *cap, StgTSO *tso, StgClosure *exception, { StgTRecHeader *trec = tso -> trec; StgTRecHeader *outer = trec -> enclosing_trec; - debugTraceCap(DEBUG_stm, cap, "raiseAsync: traversing CATCH_STM frame"); + debugTraceCap(DEBUG_stm, cap, + "found atomically block delivering async exception"); stmAbortTransaction(cap, trec); stmFreeAbortedTRec(cap, trec); tso -> trec = outer; break; }; - case CATCH_RETRY_FRAME: - // CATCH_RETY frame within an atomically block: if we're executing - // the lhs code, abort the inner transaction and continue; if we're - // executing thr rhs, continue (no nested transaction to abort. See - // Note [catchRetry# implementation]). Eventually we will hit the - // outer transaction that will get frozen (see above). - // - // As for the CATCH_STM_FRAME case above, we do not care - // whether the transaction is valid or not because its - // possible validity cannot have caused the exception - // and will not be visible after the abort. - { - if (!((StgCatchRetryFrame *)frame) -> running_alt_code) { - debugTraceCap(DEBUG_stm, cap, "raiseAsync: traversing CATCH_RETRY frame (lhs)"); - StgTRecHeader *trec = tso -> trec; - StgTRecHeader *outer = trec -> enclosing_trec; - stmAbortTransaction(cap, trec); - stmFreeAbortedTRec(cap, trec); - tso -> trec = outer; - } - else - { - debugTraceCap(DEBUG_stm, cap, "raiseAsync: traversing CATCH_RETRY frame (rhs)"); - } - break; - }; - default: // see Note [Update async masking state on unwind] in Schedule.c if (*frame == (W_)&stg_unmaskAsyncExceptionszh_ret_info) { ===================================== rts/STM.c ===================================== @@ -1505,30 +1505,3 @@ void stmWriteTVar(Capability *cap, } /*......................................................................*/ - - - -/* - -Note [catchRetry# implementation] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -catchRetry# creates a nested transaction for its lhs: -- if the lhs transaction succeeds: - - the lhs transaction is committed - - its read-variables are merged with those of the parent transaction - - the rhs code is ignored -- if the lhs transaction retries: - - the lhs transaction is aborted - - its read-variables are merged with those of the parent transaction - - the rhs code is executed directly in the parent transaction (see #26028). - -So note that: -- lhs code uses a nested transaction -- rhs code doesn't use a nested transaction - -We have to take which case we're in into account (using the running_alt_code -field of the catchRetry frame) in catchRetry's entry code, in retry# -implementation, and also when an async exception is received (to cleanup the -right number of transactions). - -*/ ===================================== testsuite/tests/lib/stm/T26028.hs deleted ===================================== @@ -1,23 +0,0 @@ -module Main where - -import GHC.Conc - -forever :: IO String -forever = delay 10 >> forever - -terminates :: IO String -terminates = delay 1 >> pure "terminates" - -delay s = threadDelay (1000000 * s) - -async :: IO a -> IO (STM a) -async a = do - var <- atomically (newTVar Nothing) - forkIO (a >>= atomically . writeTVar var . Just) - pure (readTVar var >>= maybe retry pure) - -main :: IO () -main = do - x <- mapM async $ terminates : replicate 50000 forever - r <- atomically (foldr1 orElse x) - print r ===================================== testsuite/tests/lib/stm/T26028.stdout deleted ===================================== @@ -1 +0,0 @@ -"terminates" ===================================== testsuite/tests/lib/stm/all.T deleted ===================================== @@ -1 +0,0 @@ -test('T26028', only_ways(['threaded1']), compile_and_run, ['-O2']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fca42ecfd273c8db52f43084a9c5e5b... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fca42ecfd273c8db52f43084a9c5e5b... You're receiving this email because of your account on gitlab.haskell.org.