[Git][ghc/ghc][wip/orig-thunk-info] 6 commits: Adjust AArch64 stackFrameHeaderSize

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Wed May 10 17:53:49 UTC 2023



Ben Gamari pushed to branch wip/orig-thunk-info at Glasgow Haskell Compiler / GHC


Commits:
0657b482 by Sven Tennie at 2023-05-09T22:22:42-04:00
Adjust AArch64 stackFrameHeaderSize

The prologue of each stack frame are the saved LR and FP registers, 8
byte each. I.e. the size of the stack frame header is 2 * 8 byte.

- - - - -
7788c09c by konsumlamm at 2023-05-09T22:23:23-04:00
Make `(&)` representation polymorphic in the return type

- - - - -
b3195922 by Ben Gamari at 2023-05-10T05:06:45-04:00
ghc-prim: Generalize keepAlive#/touch# in state token type

Closes #23163.

- - - - -
1e6861dd by Cheng Shao at 2023-05-10T05:07:25-04:00
Bump hsc2hs submodule

Fixes #22981.

- - - - -
37f7aaa8 by Ben Gamari at 2023-05-10T13:53:40-04:00
compiler: Fingerprint more code generation flags

Previously our recompilation check was quite inconsistent in its
coverage of non-optimisation code generation flags. Specifically, we
failed to account for most flags that would affect the behavior of
generated code in ways that might affect the result of a program's
execution (e.g. `-feager-blackholing`, `-fstrict-dicts`)

Closes #23369.

- - - - -
a02756b5 by Ben Gamari at 2023-05-10T13:53:40-04:00
compiler: Record original thunk info tables on stack

- - - - -


17 changed files:

- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/Driver/Config/StgToCmm.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Recomp/Flags.hs
- compiler/GHC/StgToCmm/Bind.hs
- compiler/GHC/StgToCmm/Config.hs
- docs/users_guide/debugging.rst
- libraries/base/Data/Function.hs
- libraries/base/changelog.md
- libraries/ghc-prim/changelog.md
- rts/StgMiscClosures.cmm
- rts/include/rts/storage/Closures.h
- utils/deriveConstants/Main.hs
- utils/hsc2hs


Changes:

=====================================
compiler/GHC/Builtin/primops.txt.pp
=====================================
@@ -3407,7 +3407,7 @@ primop  FinalizeWeakOp "finalizeWeak#" GenPrimOp
    out_of_line      = True
 
 primop TouchOp "touch#" GenPrimOp
-   v -> State# RealWorld -> State# RealWorld
+   v -> State# s -> State# s
    with
    code_size = { 0 }
    has_side_effects = True
@@ -3723,7 +3723,7 @@ section "Controlling object lifetime"
 -- and "p" is the same as "b" except representation-polymorphic.
 -- See Note [Levity and representation polymorphic primops]
 primop KeepAliveOp "keepAlive#" GenPrimOp
-   v -> State# RealWorld -> (State# RealWorld -> p) -> p
+   v -> State# s -> (State# s -> p) -> p
    { @'keepAlive#' x s k@ keeps the value @x@ alive during the execution
      of the computation @k at .
 


=====================================
compiler/GHC/Cmm/CLabel.hs
=====================================
@@ -53,6 +53,7 @@ module GHC.Cmm.CLabel (
         mkDirty_MUT_VAR_Label,
         mkMUT_VAR_CLEAN_infoLabel,
         mkNonmovingWriteBarrierEnabledLabel,
+        mkOrigThunkInfoLabel,
         mkUpdInfoLabel,
         mkBHUpdInfoLabel,
         mkIndStaticInfoLabel,
@@ -641,7 +642,7 @@ mkBlockInfoTableLabel name c = IdLabel name c BlockInfoTable
 -- Constructing Cmm Labels
 mkDirty_MUT_VAR_Label,
     mkNonmovingWriteBarrierEnabledLabel,
-    mkUpdInfoLabel,
+    mkOrigThunkInfoLabel, mkUpdInfoLabel,
     mkBHUpdInfoLabel, mkIndStaticInfoLabel, mkMainCapabilityLabel,
     mkMAP_FROZEN_CLEAN_infoLabel, mkMAP_FROZEN_DIRTY_infoLabel,
     mkMAP_DIRTY_infoLabel,
@@ -655,6 +656,7 @@ mkDirty_MUT_VAR_Label,
 mkDirty_MUT_VAR_Label           = mkForeignLabel (fsLit "dirty_MUT_VAR") Nothing ForeignLabelInExternalPackage IsFunction
 mkNonmovingWriteBarrierEnabledLabel
                                 = CmmLabel rtsUnitId (NeedExternDecl False) (fsLit "nonmoving_write_barrier_enabled") CmmData
+mkOrigThunkInfoLabel            = CmmLabel rtsUnitId (NeedExternDecl False) (fsLit "stg_orig_thunk_info_frame") CmmInfo
 mkUpdInfoLabel                  = CmmLabel rtsUnitId (NeedExternDecl False) (fsLit "stg_upd_frame")         CmmInfo
 mkBHUpdInfoLabel                = CmmLabel rtsUnitId (NeedExternDecl False) (fsLit "stg_bh_upd_frame" )     CmmInfo
 mkIndStaticInfoLabel            = CmmLabel rtsUnitId (NeedExternDecl False) (fsLit "stg_IND_STATIC")        CmmInfo


=====================================
compiler/GHC/CmmToAsm/AArch64/Instr.hs
=====================================
@@ -32,9 +32,9 @@ import Data.Maybe (fromMaybe)
 
 import GHC.Stack
 
--- | TODO: verify this!
-stackFrameHeaderSize :: Platform -> Int
-stackFrameHeaderSize _ = 64
+-- | LR and FP (8 byte each) are the prologue of each stack frame
+stackFrameHeaderSize :: Int
+stackFrameHeaderSize = 2 * 8
 
 -- | All registers are 8 byte wide.
 spillSlotSize :: Int
@@ -49,14 +49,13 @@ stackAlign = 16
 maxSpillSlots :: NCGConfig -> Int
 maxSpillSlots config
 --  = 0 -- set to zero, to see when allocMoreStack has to fire.
-    = let platform = ncgPlatform config
-      in ((ncgSpillPreallocSize config - stackFrameHeaderSize platform)
+    = ((ncgSpillPreallocSize config - stackFrameHeaderSize)
          `div` spillSlotSize) - 1
 
 -- | Convert a spill slot number to a *byte* offset, with no sign.
 spillSlotToOffset :: NCGConfig -> Int -> Int
-spillSlotToOffset config slot
-   = stackFrameHeaderSize (ncgPlatform config) + spillSlotSize * slot
+spillSlotToOffset _ slot
+   = stackFrameHeaderSize + spillSlotSize * slot
 
 -- | Get the registers that are being used by this instruction.
 -- regUsage doesn't need to do any trickery for jumps and such.


=====================================
compiler/GHC/Driver/Config/StgToCmm.hs
=====================================
@@ -37,6 +37,7 @@ initStgToCmmConfig dflags mod = StgToCmmConfig
   , stgToCmmFastPAPCalls  = gopt Opt_FastPAPCalls          dflags
   , stgToCmmSCCProfiling  = sccProfilingEnabled            dflags
   , stgToCmmEagerBlackHole = gopt Opt_EagerBlackHoling     dflags
+  , stgToCmmOrigThunkInfo = gopt Opt_OrigThunkInfo         dflags
   , stgToCmmInfoTableMap  = gopt Opt_InfoTableMap          dflags
   , stgToCmmOmitYields    = gopt Opt_OmitYields            dflags
   , stgToCmmOmitIfPragmas = gopt Opt_OmitInterfacePragmas  dflags


=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -5,6 +5,7 @@ module GHC.Driver.Flags
    , GeneralFlag(..)
    , Language(..)
    , optimisationFlags
+   , codeGenFlags
 
    -- * Warnings
    , WarningGroup(..)
@@ -328,6 +329,7 @@ data GeneralFlag
    | Opt_IgnoreHpcChanges
    | Opt_ExcessPrecision
    | Opt_EagerBlackHoling
+   | Opt_OrigThunkInfo
    | Opt_NoHsMain
    | Opt_SplitSections
    | Opt_StgStats
@@ -473,15 +475,11 @@ data GeneralFlag
    | Opt_G_NoOptCoercion
    deriving (Eq, Show, Enum)
 
--- Check whether a flag should be considered an "optimisation flag"
--- for purposes of recompilation avoidance (see
--- Note [Ignoring some flag changes] in GHC.Iface.Recomp.Flags). Being listed here is
--- not a guarantee that the flag has no other effect. We could, and
--- perhaps should, separate out the flags that have some minor impact on
--- program semantics and/or error behavior (e.g., assertions), but
--- then we'd need to go to extra trouble (and an additional flag)
--- to allow users to ignore the optimisation level even though that
--- means ignoring some change.
+-- | The set of flags which affect optimisation for the purposes of
+-- recompilation avoidance. Specifically, these include flags which
+-- affect code generation but not the semantics of the program.
+--
+-- See Note [Ignoring some flag changes] in GHC.Iface.Recomp.Flags)
 optimisationFlags :: EnumSet GeneralFlag
 optimisationFlags = EnumSet.fromList
    [ Opt_CallArity
@@ -513,16 +511,12 @@ optimisationFlags = EnumSet.fromList
    , Opt_EnableRewriteRules
    , Opt_RegsGraph
    , Opt_RegsIterative
-   , Opt_PedanticBottoms
    , Opt_LlvmTBAA
-   , Opt_LlvmFillUndefWithGarbage
    , Opt_IrrefutableTuples
    , Opt_CmmSink
    , Opt_CmmElimCommonBlocks
    , Opt_AsmShortcutting
-   , Opt_OmitYields
    , Opt_FunToThunk
-   , Opt_DictsStrict
    , Opt_DmdTxDictSel
    , Opt_Loopification
    , Opt_CfgBlocklayout
@@ -531,8 +525,48 @@ optimisationFlags = EnumSet.fromList
    , Opt_WorkerWrapper
    , Opt_WorkerWrapperUnlift
    , Opt_SolveConstantDicts
+   ]
+
+-- | The set of flags which affect code generation and can change a program's
+-- runtime behavior (other than performance). These include flags which affect:
+--
+--  * user visible debugging information (e.g. info table provenance)
+--  * the ability to catch runtime errors (e.g. -fignore-asserts)
+--  * the runtime result of the program (e.g. -fomit-yields)
+--  * which code or interface file declarations are emitted
+--
+-- We also considered placing flags which affect asympototic space behavior
+-- (e.g. -ffull-laziness) however this would mean that changing optimisation
+-- levels would trigger recompilation even with -fignore-optim-changes,
+-- regressing #13604.
+--
+-- Also, arguably Opt_IgnoreAsserts should be here as well; however, we place
+-- it instead in 'optimisationFlags' since it is implied by @-O[12]@ and
+-- therefore would also break #13604.
+--
+-- See #23369.
+codeGenFlags :: EnumSet GeneralFlag
+codeGenFlags = EnumSet.fromList
+   [ -- Flags that affect runtime result
+     Opt_EagerBlackHoling
+   , Opt_ExcessPrecision
+   , Opt_DictsStrict
+   , Opt_PedanticBottoms
+   , Opt_OmitYields
+
+     -- Flags that affect generated code
+   , Opt_ExposeAllUnfoldings
+   , Opt_NoTypeableBinds
+
+     -- Flags that affect catching of runtime errors
    , Opt_CatchNonexhaustiveCases
-   , Opt_IgnoreAsserts
+   , Opt_LlvmFillUndefWithGarbage
+   , Opt_DoTagInferenceChecks
+
+     -- Flags that affect debugging information
+   , Opt_DistinctConstructorTables
+   , Opt_InfoTableMap
+   , Opt_OrigThunkInfo
    ]
 
 data WarningFlag =


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -66,6 +66,7 @@ module GHC.Driver.Session (
         makeDynFlagsConsistent,
         positionIndependent,
         optimisationFlags,
+        codeGenFlags,
         setFlagsFromEnvFile,
         pprDynFlagsDiff,
         flagSpecOf,
@@ -3481,6 +3482,7 @@ fFlagsDeps = [
   flagSpec "do-eta-reduction"                 Opt_DoEtaReduction,
   flagSpec "do-lambda-eta-expansion"          Opt_DoLambdaEtaExpansion,
   flagSpec "eager-blackholing"                Opt_EagerBlackHoling,
+  flagSpec "orig-thunk-info"                  Opt_OrigThunkInfo,
   flagSpec "embed-manifest"                   Opt_EmbedManifest,
   flagSpec "enable-rewrite-rules"             Opt_EnableRewriteRules,
   flagSpec "enable-th-splice-warnings"        Opt_EnableThSpliceWarnings,


=====================================
compiler/GHC/Iface/Recomp/Flags.hs
=====================================
@@ -67,7 +67,10 @@ fingerprintDynFlags hsc_env this_mod nameio =
         ticky =
           map (`gopt` dflags) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk, Opt_Ticky_Tag]
 
-        flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel, callerCcFilters))
+        -- Other flags which affect code generation
+        codegen = map (`gopt` dflags) (EnumSet.toList codeGenFlags)
+
+        flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, codegen, debugLevel, callerCcFilters))
 
     in -- pprTrace "flags" (ppr flags) $
        computeFingerprint nameio flags


=====================================
compiler/GHC/StgToCmm/Bind.hs
=====================================
@@ -730,7 +730,8 @@ setupUpdate closure_info node body
               lbl | bh        = mkBHUpdInfoLabel
                   | otherwise = mkUpdInfoLabel
 
-          pushUpdateFrame lbl (CmmReg (CmmLocal node)) body
+          pushOrigThunkInfoFrame closure_info
+            $ pushUpdateFrame lbl (CmmReg (CmmLocal node)) body
 
   | otherwise   -- A static closure
   = do  { tickyUpdateBhCaf closure_info
@@ -738,7 +739,8 @@ setupUpdate closure_info node body
         ; if closureUpdReqd closure_info
           then do       -- Blackhole the (updatable) CAF:
                 { upd_closure <- link_caf node
-                ; pushUpdateFrame mkBHUpdInfoLabel upd_closure body }
+                ; pushOrigThunkInfoFrame closure_info
+                    $ pushUpdateFrame mkBHUpdInfoLabel upd_closure body }
           else do {tickyUpdateFrameOmitted; body}
     }
 
@@ -754,8 +756,7 @@ pushUpdateFrame lbl updatee body
   = do
        updfr  <- getUpdFrameOff
        profile <- getProfile
-       let
-           hdr         = fixedHdrSize profile
+       let hdr         = fixedHdrSize profile
            frame       = updfr + hdr + pc_SIZEOF_StgUpdateFrame_NoHdr (profileConstants profile)
        --
        emitUpdateFrame (CmmStackSlot Old frame) lbl updatee
@@ -773,6 +774,47 @@ emitUpdateFrame frame lbl updatee = do
   emitStore (cmmOffset platform frame off_updatee) updatee
   initUpdFrameProf frame
 
+-----------------------------------------------------------------------------
+-- Original thunk info table frames
+--
+-- Note [Original thunk info table frames]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-- In some debugging scenarios (e.g. when debugging cyclic thunks) it can be very
+-- useful to know which thunks the program is in the process of evaluating.
+-- However, in the case of updateable thunks this can be very difficult
+-- to determine since the process of blackholing overwrites the thunk's
+-- info table pointer.
+--
+-- To help in such situations we provide the -forig-thunk-info flag. This enables
+-- code generation logic which pushes a stg_orig_thunk_info_frame stack frame to
+-- accompany each update frame. As the name suggests, this frame captures the
+-- the original info table of the thunk being updated. The entry code for these
+-- frames has no operational effects; the frames merely exist as breadcrumbs
+-- for debugging.
+
+pushOrigThunkInfoFrame :: ClosureInfo -> FCode () -> FCode ()
+pushOrigThunkInfoFrame closure_info body = do
+  cfg <- getStgToCmmConfig
+  if stgToCmmOrigThunkInfo cfg
+     then do_it
+     else body
+  where
+    orig_itbl = mkLblExpr (closureInfoLabel closure_info)
+    do_it = do
+      updfr <- getUpdFrameOff
+      profile <- getProfile
+      let platform = profilePlatform profile
+          hdr = fixedHdrSize profile
+          orig_info_frame_sz =
+              hdr + pc_SIZEOF_StgOrigThunkInfoFrame_NoHdr (profileConstants profile)
+          off_orig_info = hdr + pc_OFFSET_StgOrigThunkInfoFrame_info_ptr (profileConstants profile)
+          frame_off = updfr + orig_info_frame_sz
+          frame = CmmStackSlot Old frame_off
+      --
+      emitStore frame (mkLblExpr mkOrigThunkInfoLabel)
+      emitStore (cmmOffset platform frame off_orig_info) orig_itbl
+      withUpdFrameOff frame_off body
+
 -----------------------------------------------------------------------------
 -- Entering a CAF
 --


=====================================
compiler/GHC/StgToCmm/Config.hs
=====================================
@@ -49,6 +49,7 @@ data StgToCmmConfig = StgToCmmConfig
   , stgToCmmFastPAPCalls   :: !Bool              -- ^
   , stgToCmmSCCProfiling   :: !Bool              -- ^ Check if cost-centre profiling is enabled
   , stgToCmmEagerBlackHole :: !Bool              -- ^
+  , stgToCmmOrigThunkInfo  :: !Bool              -- ^ Push @stg_orig_thunk_info@ frames during thunk update.
   , stgToCmmInfoTableMap   :: !Bool              -- ^ true means generate C Stub for IPE map, See note [Mapping
                                                  -- Info Tables to Source Positions]
   , stgToCmmOmitYields     :: !Bool              -- ^ true means omit heap checks when no allocation is performed


=====================================
docs/users_guide/debugging.rst
=====================================
@@ -1072,6 +1072,18 @@ Checking for consistency
     cases. This is helpful when debugging demand analysis or type checker bugs
     which can sometimes manifest as segmentation faults.
 
+.. ghc-flag:: -forig-thunk-info
+    :shortdesc: Generate ``stg_orig_thunk_info`` stack frames on thunk entry
+    :type: dynamic
+
+    When debugging cyclic thunks it can be helpful to know the original
+    info table of a thunk being evaluated. This flag enables code generation logic
+    to facilitate this, producing a ``stg_orig_thunk_info`` stack frame alongside
+    the usual update frame; such ``orig_thunk`` frames have no operational
+    effect but capture the original info table of the updated thunk for inspection
+    by debugging tools. See ``Note [Original thunk info table frames]`` in
+    ``GHC.StgToCmm.Bind`` for details.
+
 .. ghc-flag:: -fcheck-prim-bounds
     :shortdesc: Instrument array primops with bounds checks.
     :type: dynamic


=====================================
libraries/base/Data/Function.hs
=====================================
@@ -1,3 +1,5 @@
+{-# LANGUAGE ExplicitForAll #-}
+{-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE Trustworthy #-}
 {-# LANGUAGE NoImplicitPrelude #-}
 {-# OPTIONS_HADDOCK print-explicit-runtime-reps #-}
@@ -28,7 +30,7 @@ module Data.Function
   , applyWhen
   ) where
 
-import GHC.Base ( ($), (.), id, const, flip )
+import GHC.Base ( TYPE, ($), (.), id, const, flip )
 import Data.Bool ( Bool(..) )
 
 infixl 0 `on`
@@ -120,7 +122,7 @@ on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
 -- "6"
 --
 -- @since 4.8.0.0
-(&) :: a -> (a -> b) -> b
+(&) :: forall r a (b :: TYPE r). a -> (a -> b) -> b
 x & f = f x
 
 -- | 'applyWhen' applies a function to a value if a condition is true,


=====================================
libraries/base/changelog.md
=====================================
@@ -21,9 +21,10 @@
       ([CLC proposal #149](https://github.com/haskell/core-libraries-committee/issues/149))
   * Make `($)` representation polymorphic ([CLC proposal #132](https://github.com/haskell/core-libraries-committee/issues/132))
   * Implemented [GHC Proposal #433](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0433-unsatisfiable.rst),
-    adding the class `Unsatisfiable :: ErrorMessage -> TypeError`` to `GHC.TypeError`,
+    adding the class `Unsatisfiable :: ErrorMessage -> TypeError` to `GHC.TypeError`,
     which provides a mechanism for custom type errors that reports the errors in
-    a more predictable behaviour than ``TypeError``.
+    a more predictable behaviour than `TypeError`.
+  * Make `(&)` representation polymorphic in the return type ([CLC proposal #158](https://github.com/haskell/core-libraries-committee/issues/158))
 
 ## 4.18.0.0 *March 2023*
   * Shipped with GHC 9.6.1


=====================================
libraries/ghc-prim/changelog.md
=====================================
@@ -14,6 +14,8 @@
     - `sameMutVar#`, `sameTVar#`, `sameMVar#`
     - `sameIOPort#`, `eqStableName#`.
 
+- `keepAlive#` and `touch#` are now polymorphic in their state token (#23163; [CLC#152](https://github.com/haskell/core-libraries-committee/issues/152))
+
 - Several new primops were added:
 
   - `copyMutableByteArrayNonOverlapping#`


=====================================
rts/StgMiscClosures.cmm
=====================================
@@ -45,6 +45,17 @@ import CLOSURE stg_ret_t_info;
 import CLOSURE stg_ret_v_info;
 #endif
 
+/* See Note [Original thunk info table frames] in GHC.StgToCmm.Bind. */
+INFO_TABLE_RET (stg_orig_thunk_info_frame, RET_SMALL,
+                W_ info_ptr,
+                W_ thunk_info_ptr)
+    /* no args => explicit stack */
+{
+    unwind Sp = W_[Sp + WDS(2)];
+    Sp_adj(2);
+    jump %ENTRY_CODE(Sp(0)) [*]; // NB. all registers live!
+}
+
 /* ----------------------------------------------------------------------------
    Stack underflow
    ------------------------------------------------------------------------- */


=====================================
rts/include/rts/storage/Closures.h
=====================================
@@ -261,6 +261,13 @@ typedef struct _StgUpdateFrame {
     StgClosure *updatee;
 } StgUpdateFrame;
 
+// Thunk update frame
+//
+// Closure types: RET_SMALL
+typedef struct _StgOrigThunkInfoFrame {
+    StgHeader  header;
+    StgInfoTable *info_ptr;
+} StgOrigThunkInfoFrame;
 
 // Closure types: RET_SMALL
 typedef struct {


=====================================
utils/deriveConstants/Main.hs
=====================================
@@ -437,6 +437,7 @@ wanteds os = concat
           ,structField  Both "StgEntCounter" "entry_count"
 
           ,closureSize  Both "StgUpdateFrame"
+          ,closureSize  Both "StgOrigThunkInfoFrame"
           ,closureSize  C    "StgCatchFrame"
           ,closureSize  C    "StgStopFrame"
           ,closureSize  C    "StgDeadThreadFrame"
@@ -479,6 +480,7 @@ wanteds os = concat
           ,structSize C "StgTSOProfInfo"
 
           ,closureField Both "StgUpdateFrame" "updatee"
+          ,closureField Both "StgOrigThunkInfoFrame" "info_ptr"
 
           ,closureField C "StgCatchFrame" "handler"
           ,closureField C "StgCatchFrame" "exceptions_blocked"


=====================================
utils/hsc2hs
=====================================
@@ -1 +1 @@
-Subproject commit 1ba092932f86c1fda15091d355ba7975b8554437
+Subproject commit f70b360b295298e4da10afe02ebf022b21342008



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/40f8200ee17575021c336c0aba14b684980415dc...a02756b537b75acba0942381789850662ed6eab3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/40f8200ee17575021c336c0aba14b684980415dc...a02756b537b75acba0942381789850662ed6eab3
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/20230510/b6ad3e72/attachment-0001.html>


More information about the ghc-commits mailing list