[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: rts: fix small argument passing on big-endian arch (fix #23387)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sun Oct 22 00:48:08 UTC 2023



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
4f02d3c1 by Sylvain Henry at 2023-10-20T04:01:32-04:00
rts: fix small argument passing on big-endian arch (fix #23387)

- - - - -
b86243b4 by Sylvain Henry at 2023-10-20T04:02:13-04:00
Interpreter: fix literal alignment on big-endian architectures (fix #19261)

Literals weren't correctly aligned on big-endian, despite what the
comment said.

- - - - -
a4b2ec47 by Sylvain Henry at 2023-10-20T04:02:54-04:00
Testsuite: recomp011 and recomp015 are fixed on powerpc

These tests have been fixed but not tested and re-enabled on big-endian
powerpc (see comments in #11260 and #11323)

- - - - -
fded7dd4 by Sebastian Graf at 2023-10-20T04:03:30-04:00
CorePrep: Allow floating dictionary applications in -O0 into a Rec (#24102)
- - - - -
8cf7500a by Cheng Shao at 2023-10-21T20:47:52-04:00
rts: drop stale mentions of MIN_UPD_SIZE

We used to have MIN_UPD_SIZE macro that describes the minimum reserved
size for thunks, so that the thunk can be overwritten in place as
indirections or blackholes. However, this macro has not been actually
defined or used anywhere since a long time ago; StgThunkHeader already
reserves a padding word for this purpose. Hence this patch which drops
stale mentions of MIN_UPD_SIZE.

- - - - -
c3ca6215 by Andrew Lelechenko at 2023-10-21T20:47:56-04:00
base changelog: move non-backported entries from 4.19 section to 4.20

Neither !10933 (check https://hackage.haskell.org/package/base-4.19.0.0/docs/src/Text.Read.Lex.html#numberToRangedRational)
nor !10189 (check https://hackage.haskell.org/package/base-4.19.0.0/docs/src/Data.List.NonEmpty.html#unzip)
were backported to `base-4.19.0.0`. Moving them to `base-4.20.0.0` section.

Also minor stylistic changes to other entries, bringing them to a uniform form.

- - - - -


8 changed files:

- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/CoreToStg/Prep.hs
- docs/rts/rts.tex
- libraries/base/changelog.md
- rts/Interpreter.c
- rts/PrimOps.cmm
- testsuite/tests/driver/recomp011/all.T
- testsuite/tests/driver/recomp015/all.T


Changes:

=====================================
compiler/GHC/ByteCode/Asm.hs
=====================================
@@ -43,23 +43,19 @@ import GHC.Platform
 import GHC.Platform.Profile
 
 import Control.Monad
-import Control.Monad.ST ( runST )
 import Control.Monad.Trans.Class
 import Control.Monad.Trans.State.Strict
 
-import Data.Array.MArray
-
 import qualified Data.Array.Unboxed as Array
 import Data.Array.Base  ( UArray(..) )
 
-import Data.Array.Unsafe( castSTUArray )
-
 import Foreign hiding (shiftL, shiftR)
 import Data.Char        ( ord )
 import Data.List        ( genericLength )
 import Data.Map.Strict (Map)
 import Data.Maybe (fromMaybe)
 import qualified Data.Map.Strict as Map
+import GHC.Float (castFloatToWord32, castDoubleToWord64)
 
 -- -----------------------------------------------------------------------------
 -- Unlinked BCOs
@@ -416,7 +412,7 @@ assembleI platform i = case i of
                                                                 tuple_proto
                                  p <- ioptr (liftM BCOPtrBCO ul_bco)
                                  p_tup <- ioptr (liftM BCOPtrBCO ul_tuple_bco)
-                                 info <- int (fromIntegral $
+                                 info <- word (fromIntegral $
                                               mkNativeCallInfoSig platform call_info)
                                  emit bci_PUSH_ALTS_T
                                       [Op p, Op info, Op p_tup]
@@ -466,21 +462,21 @@ assembleI platform i = case i of
                                  emit bci_TESTLT_W [Op np, LabelOp l]
   TESTEQ_W  w l            -> do np <- word w
                                  emit bci_TESTEQ_W [Op np, LabelOp l]
-  TESTLT_I64  i l          -> do np <- int64 i
+  TESTLT_I64  i l          -> do np <- word64 (fromIntegral i)
                                  emit bci_TESTLT_I64 [Op np, LabelOp l]
-  TESTEQ_I64  i l          -> do np <- int64 i
+  TESTEQ_I64  i l          -> do np <- word64 (fromIntegral i)
                                  emit bci_TESTEQ_I64 [Op np, LabelOp l]
-  TESTLT_I32  i l          -> do np <- int (fromIntegral i)
+  TESTLT_I32  i l          -> do np <- word (fromIntegral i)
                                  emit bci_TESTLT_I32 [Op np, LabelOp l]
-  TESTEQ_I32 i l           -> do np <- int (fromIntegral i)
+  TESTEQ_I32 i l           -> do np <- word (fromIntegral i)
                                  emit bci_TESTEQ_I32 [Op np, LabelOp l]
-  TESTLT_I16  i l          -> do np <- int (fromIntegral i)
+  TESTLT_I16  i l          -> do np <- word (fromIntegral i)
                                  emit bci_TESTLT_I16 [Op np, LabelOp l]
-  TESTEQ_I16 i l           -> do np <- int (fromIntegral i)
+  TESTEQ_I16 i l           -> do np <- word (fromIntegral i)
                                  emit bci_TESTEQ_I16 [Op np, LabelOp l]
-  TESTLT_I8  i l           -> do np <- int (fromIntegral i)
+  TESTLT_I8  i l           -> do np <- word (fromIntegral i)
                                  emit bci_TESTLT_I8 [Op np, LabelOp l]
-  TESTEQ_I8 i l            -> do np <- int (fromIntegral i)
+  TESTEQ_I8 i l            -> do np <- word (fromIntegral i)
                                  emit bci_TESTEQ_I8 [Op np, LabelOp l]
   TESTLT_W64  w l          -> do np <- word64 w
                                  emit bci_TESTLT_W64 [Op np, LabelOp l]
@@ -530,42 +526,80 @@ assembleI platform i = case i of
      -- On Windows, stdcall labels have a suffix indicating the no. of
      -- arg words, e.g. foo at 8.  testcase: ffi012(ghci)
     literal (LitLabel fs _ _) = litlabel fs
-    literal LitNullAddr       = int 0
+    literal LitNullAddr       = word 0
     literal (LitFloat r)      = float (fromRational r)
     literal (LitDouble r)     = double (fromRational r)
     literal (LitChar c)       = int (ord c)
     literal (LitString bs)    = lit [BCONPtrStr bs]
        -- LitString requires a zero-terminator when emitted
     literal (LitNumber nt i) = case nt of
-      LitNumInt     -> int (fromIntegral i)
-      LitNumWord    -> int (fromIntegral i)
-      LitNumInt8    -> int8 (fromIntegral i)
-      LitNumWord8   -> int8 (fromIntegral i)
-      LitNumInt16   -> int16 (fromIntegral i)
-      LitNumWord16  -> int16 (fromIntegral i)
-      LitNumInt32   -> int32 (fromIntegral i)
-      LitNumWord32  -> int32 (fromIntegral i)
-      LitNumInt64   -> int64 (fromIntegral i)
-      LitNumWord64  -> int64 (fromIntegral i)
+      LitNumInt     -> word (fromIntegral i)
+      LitNumWord    -> word (fromIntegral i)
+      LitNumInt8    -> word8 (fromIntegral i)
+      LitNumWord8   -> word8 (fromIntegral i)
+      LitNumInt16   -> word16 (fromIntegral i)
+      LitNumWord16  -> word16 (fromIntegral i)
+      LitNumInt32   -> word32 (fromIntegral i)
+      LitNumWord32  -> word32 (fromIntegral i)
+      LitNumInt64   -> word64 (fromIntegral i)
+      LitNumWord64  -> word64 (fromIntegral i)
       LitNumBigNat  -> panic "GHC.ByteCode.Asm.literal: LitNumBigNat"
 
     -- We can lower 'LitRubbish' to an arbitrary constant, but @NULL@ is most
     -- likely to elicit a crash (rather than corrupt memory) in case absence
     -- analysis messed up.
-    literal (LitRubbish {}) = int 0
+    literal (LitRubbish {}) = word 0
 
     litlabel fs = lit [BCONPtrLbl fs]
     addr (RemotePtr a) = words [fromIntegral a]
-    float = words . mkLitF platform
-    double = words . mkLitD platform
-    int = words . mkLitI
-    int8 = words . mkLitI64 platform
-    int16 = words . mkLitI64 platform
-    int32 = words . mkLitI64 platform
-    int64 = words . mkLitI64 platform
-    word64 = words . mkLitW64 platform
     words ws = lit (map BCONPtrWord ws)
     word w = words [w]
+    word_size  = platformWordSize platform
+    word_size_bits = platformWordSizeInBits platform
+
+    -- Make lists of host-sized words for literals, so that when the
+    -- words are placed in memory at increasing addresses, the
+    -- bit pattern is correct for the host's word size and endianness.
+    --
+    -- Note that we only support host endianness == target endianness for now,
+    -- even with the external interpreter. This would need to be fixed to
+    -- support host endianness /= target endianness
+    int :: Int -> Assembler Word
+    int  i = word (fromIntegral i)
+
+    float :: Float -> Assembler Word
+    float f = word32 (castFloatToWord32 f)
+
+    double :: Double -> Assembler Word
+    double d = word64 (castDoubleToWord64 d)
+
+    word64 :: Word64 -> Assembler Word
+    word64 ww = case word_size of
+       PW4 ->
+        let !wl = fromIntegral ww
+            !wh = fromIntegral (ww `unsafeShiftR` 32)
+        in case platformByteOrder platform of
+            LittleEndian -> words [wl,wh]
+            BigEndian    -> words [wh,wl]
+       PW8 -> word (fromIntegral ww)
+
+    word8 :: Word8 -> Assembler Word
+    word8  x = case platformByteOrder platform of
+      LittleEndian -> word (fromIntegral x)
+      BigEndian    -> word (fromIntegral x `unsafeShiftL` (word_size_bits - 8))
+
+    word16 :: Word16 -> Assembler Word
+    word16 x = case platformByteOrder platform of
+      LittleEndian -> word (fromIntegral x)
+      BigEndian    -> word (fromIntegral x `unsafeShiftL` (word_size_bits - 16))
+
+    word32 :: Word32 -> Assembler Word
+    word32 x = case platformByteOrder platform of
+      LittleEndian -> word (fromIntegral x)
+      BigEndian    -> case word_size of
+        PW4 -> word (fromIntegral x)
+        PW8 -> word (fromIntegral x `unsafeShiftL` 32)
+
 
 isLargeW :: Word -> Bool
 isLargeW n = n > 65535
@@ -648,74 +682,5 @@ mkNativeCallInfoLit :: Platform -> NativeCallInfo -> Literal
 mkNativeCallInfoLit platform call_info =
   mkLitWord platform . fromIntegral $ mkNativeCallInfoSig platform call_info
 
--- Make lists of host-sized words for literals, so that when the
--- words are placed in memory at increasing addresses, the
--- bit pattern is correct for the host's word size and endianness.
-mkLitI   ::             Int    -> [Word]
-mkLitF   :: Platform -> Float  -> [Word]
-mkLitD   :: Platform -> Double -> [Word]
-mkLitI64 :: Platform -> Int64  -> [Word]
-mkLitW64 :: Platform -> Word64 -> [Word]
-
-mkLitF platform f = case platformWordSize platform of
-  PW4 -> runST $ do
-        arr <- newArray_ ((0::Int),0)
-        writeArray arr 0 f
-        f_arr <- castSTUArray arr
-        w0 <- readArray f_arr 0
-        return [w0 :: Word]
-
-  PW8 -> runST $ do
-        arr <- newArray_ ((0::Int),1)
-        writeArray arr 0 f
-        -- on 64-bit architectures we read two (32-bit) Float cells when we read
-        -- a (64-bit) Word: so we write a dummy value in the second cell to
-        -- avoid an out-of-bound read.
-        writeArray arr 1 0.0
-        f_arr <- castSTUArray arr
-        w0 <- readArray f_arr 0
-        return [w0 :: Word]
-
-mkLitD platform d = case platformWordSize platform of
-   PW4 -> runST (do
-        arr <- newArray_ ((0::Int),1)
-        writeArray arr 0 d
-        d_arr <- castSTUArray arr
-        w0 <- readArray d_arr 0
-        w1 <- readArray d_arr 1
-        return [w0 :: Word, w1]
-     )
-   PW8 -> runST (do
-        arr <- newArray_ ((0::Int),0)
-        writeArray arr 0 d
-        d_arr <- castSTUArray arr
-        w0 <- readArray d_arr 0
-        return [w0 :: Word]
-     )
-
-mkLitI64 platform ii = case platformWordSize platform of
-   PW4 -> runST (do
-        arr <- newArray_ ((0::Int),1)
-        writeArray arr 0 ii
-        d_arr <- castSTUArray arr
-        w0 <- readArray d_arr 0
-        w1 <- readArray d_arr 1
-        return [w0 :: Word,w1]
-     )
-   PW8 -> [fromIntegral ii :: Word]
-
-mkLitW64 platform ww = case platformWordSize platform of
-   PW4 -> runST (do
-        arr <- newArray_ ((0::Word),1)
-        writeArray arr 0 ww
-        d_arr <- castSTUArray arr
-        w0 <- readArray d_arr 0
-        w1 <- readArray d_arr 1
-        return [w0 :: Word,w1]
-     )
-   PW8 -> [fromIntegral ww :: Word]
-
-mkLitI i = [fromIntegral i :: Word]
-
 iNTERP_STACK_CHECK_THRESH :: Int
 iNTERP_STACK_CHECK_THRESH = INTERP_STACK_CHECK_THRESH


=====================================
compiler/GHC/CoreToStg/Prep.hs
=====================================
@@ -643,13 +643,20 @@ cpeBind top_lvl env (Rec pairs)
   where
     (bndrs, rhss) = unzip pairs
 
-        -- Flatten all the floats, and the current
-        -- group into a single giant Rec
+    -- Flatten all the floats, and the current
+    -- group into a single giant Rec
     add_float (Float bind bound _) prs2
-      | bound /= CaseBound = case bind of
+      | bound /= CaseBound
+      || all (definitelyLiftedType . idType) (bindersOf bind)
+           -- The latter check is hit in -O0 (i.e., flavours quick, devel2)
+           -- for dictionary args which haven't been floated out yet, #24102.
+           -- They are preferably CaseBound, but since they are lifted we may
+           -- just as well put them in the Rec, in contrast to lifted bindings.
+      = case bind of
           NonRec x e -> (x,e) : prs2
           Rec prs1 -> prs1 ++ prs2
-    add_float f                       _    = pprPanic "cpeBind" (ppr f)
+    add_float f _ = pprPanic "cpeBind" (ppr f)
+
 
 ---------------
 cpePair :: TopLevelFlag -> RecFlag -> Demand -> Bool


=====================================
docs/rts/rts.tex
=====================================
@@ -1970,10 +1970,9 @@ Here the right-hand sides of @range@ and @ys@ are both thunks; the former
 is static while the latter is dynamic.
 
 The layout of a thunk is the same as that for a function closure.
-However, thunks must have a payload of at least @MIN_UPD_SIZE@
-words to allow it to be overwritten with a black hole and an
-indirection.  The compiler may have to add extra non-pointer fields to
-satisfy this constraint.
+However, a thunk header always contains an extra padding word at the
+end. This allows the thunk to be overwritten with an indirection,
+where the padding word will be repurposed as the indirectee pointer.
 
 \begin{center}
 \begin{tabular}{|l|l|l|l|l|}\hline


=====================================
libraries/base/changelog.md
=====================================
@@ -9,14 +9,16 @@
   * Always use `safe` call to `read` for regular files and block devices on unix if the RTS is multi-threaded, regardless of `O_NONBLOCK`.
     ([CLC proposal #166](https://github.com/haskell/core-libraries-committee/issues/166))
   * Export List from Data.List ([CLC proposal #182](https://github.com/haskell/core-libraries-committee/issues/182)).
+  * Deprecate `Data.List.NonEmpty.unzip` ([CLC proposal #86](https://github.com/haskell/core-libraries-committee/issues/86))
+  * Fix exponent overflow/underflow bugs in the `Read` instances for `Float` and `Double` ([CLC proposal #192](https://github.com/haskell/core-libraries-committee/issues/192))
 
-## 4.19.0.0 *TBA*
+## 4.19.0.0 *October 2023*
   * Add `{-# WARNING in "x-partial" #-}` to `Data.List.{head,tail}`.
     Use `{-# OPTIONS_GHC -Wno-x-partial #-}` to disable it.
     ([CLC proposal #87](https://github.com/haskell/core-libraries-committee/issues/87) and [#114](https://github.com/haskell/core-libraries-committee/issues/114))
-  * `GHC.Conc.Sync` now exports `fromThreadId :: ThreadId -> Word64`, which maps a thread to a per-process-unique identifier ([CLC proposal #117](https://github.com/haskell/core-libraries-committee/issues/117))
+  * Add `fromThreadId :: ThreadId -> Word64` to `GHC.Conc.Sync`, which maps a thread to a per-process-unique identifier ([CLC proposal #117](https://github.com/haskell/core-libraries-committee/issues/117))
   * Add `Data.List.!?` ([CLC proposal #110](https://github.com/haskell/core-libraries-committee/issues/110))
-  * `maximumBy`/`minimumBy` are now marked as `INLINE` improving performance for unpackable
+  * Mark `maximumBy`/`minimumBy` as `INLINE` improving performance for unpackable
     types significantly.
   * Add INLINABLE pragmas to `generic*` functions in Data.OldList ([CLC proposal #129](https://github.com/haskell/core-libraries-committee/issues/130))
   * Export `getSolo` from `Data.Tuple`.
@@ -34,20 +36,18 @@
   * Add `COMPLETE` pragmas to the `TypeRep`, `SSymbol`, `SChar`, and `SNat` pattern synonyms.
       ([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),
+  * Implement [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`,
     which provides a mechanism for custom type errors that reports the errors in
     a more predictable behaviour than `TypeError`.
   * Add more instances for `Compose`: `Enum`, `Bounded`, `Num`, `Real`, `Integral` ([CLC proposal #160](https://github.com/haskell/core-libraries-committee/issues/160))
   * Make `(&)` representation polymorphic in the return type ([CLC proposal #158](https://github.com/haskell/core-libraries-committee/issues/158))
   * Implement `GHC.IORef.atomicSwapIORef` via a new dedicated primop `atomicSwapMutVar#` ([CLC proposal #139](https://github.com/haskell/core-libraries-committee/issues/139))
-  * Change codebuffers to use an unboxed implementation, while providing a compatibility layer using pattern synonyms. ([CLC proposal #134](https://github.com/haskell/core-libraries-committee/issues/134))
-  * Add nominal role annotations to SNat/SSymbol/SChar ([CLC proposal #170](https://github.com/haskell/core-libraries-committee/issues/170))
+  * Change `BufferCodec` to use an unboxed implementation, while providing a compatibility layer using pattern synonyms. ([CLC proposal #134](https://github.com/haskell/core-libraries-committee/issues/134))
+  * Add nominal role annotations to `SNat` / `SSymbol` / `SChar` ([CLC proposal #170](https://github.com/haskell/core-libraries-committee/issues/170))
   * Make `Semigroup`'s `stimes` specializable. ([CLC proposal #8](https://github.com/haskell/core-libraries-committee/issues/8))
-  * Deprecate `Data.List.NonEmpty.unzip` ([CLC proposal #86](https://github.com/haskell/core-libraries-committee/issues/86))
-  * Fixed exponent overflow/underflow bugs in the `Read` instances for `Float` and `Double` ([CLC proposal #192](https://github.com/haskell/core-libraries-committee/issues/192))
   * Implement `copyBytes`, `fillBytes`, `moveBytes` and `stimes` for `Data.Array.Byte.ByteArray` using primops ([CLC proposal #188](https://github.com/haskell/core-libraries-committee/issues/188))
-  * Add rewrite rules for conversion between Int64/Word64 and Float/Double on 64-bit architectures ([CLC proposal #203](https://github.com/haskell/core-libraries-committee/issues/203)).
+  * Add rewrite rules for conversion between `Int64` / `Word64` and `Float` / `Double` on 64-bit architectures ([CLC proposal #203](https://github.com/haskell/core-libraries-committee/issues/203)).
 
 ## 4.18.0.0 *March 2023*
   * Shipped with GHC 9.6.1


=====================================
rts/Interpreter.c
=====================================
@@ -1275,21 +1275,21 @@ run_BCO:
 
         case bci_PUSH8_W: {
             W_ off = BCO_GET_LARGE_ARG;
-            *(StgWord*)(Sp_minusW(1)) = *(StgWord8*)(Sp_plusB(off));
+            *(StgWord8*)(Sp_minusW(1)) = *(StgWord8*)(Sp_plusB(off));
             Sp_subW(1);
             goto nextInsn;
         }
 
         case bci_PUSH16_W: {
             W_ off = BCO_GET_LARGE_ARG;
-            *(StgWord*)(Sp_minusW(1)) = *(StgWord16*)(Sp_plusB(off));
+            *(StgWord16*)(Sp_minusW(1)) = *(StgWord16*)(Sp_plusB(off));
             Sp_subW(1);
             goto nextInsn;
         }
 
         case bci_PUSH32_W: {
             W_ off = BCO_GET_LARGE_ARG;
-            *(StgWord*)(Sp_minusW(1)) = *(StgWord32*)(Sp_plusB(off));
+            *(StgWord32*)(Sp_minusW(1)) = *(StgWord32*)(Sp_plusB(off));
             Sp_subW(1);
             goto nextInsn;
         }


=====================================
rts/PrimOps.cmm
=====================================
@@ -740,25 +740,15 @@ stg_atomicModifyMutVar2zh ( gcptr mv, gcptr f )
 
         obviously we can share (f x).
 
-         z = [stg_ap_2 f x]  (max (HS + 2) MIN_UPD_SIZE)
-         y = [stg_sel_0 z]   (max (HS + 1) MIN_UPD_SIZE)
+         z = [stg_ap_2 f x]  (SIZEOF_StgThunkHeader + WDS(2))
+         y = [stg_sel_0 z]   (SIZEOF_StgThunkHeader + WDS(1))
     */
 
-#if defined(MIN_UPD_SIZE) && MIN_UPD_SIZE > 1
-#define THUNK_1_SIZE (SIZEOF_StgThunkHeader + WDS(MIN_UPD_SIZE))
-#define TICK_ALLOC_THUNK_1() TICK_ALLOC_UP_THK(WDS(1),WDS(MIN_UPD_SIZE-1))
-#else
 #define THUNK_1_SIZE (SIZEOF_StgThunkHeader + WDS(1))
 #define TICK_ALLOC_THUNK_1() TICK_ALLOC_UP_THK(WDS(1),0)
-#endif
 
-#if defined(MIN_UPD_SIZE) && MIN_UPD_SIZE > 2
-#define THUNK_2_SIZE (SIZEOF_StgThunkHeader + WDS(MIN_UPD_SIZE))
-#define TICK_ALLOC_THUNK_2() TICK_ALLOC_UP_THK(WDS(2),WDS(MIN_UPD_SIZE-2))
-#else
 #define THUNK_2_SIZE (SIZEOF_StgThunkHeader + WDS(2))
 #define TICK_ALLOC_THUNK_2() TICK_ALLOC_UP_THK(WDS(2),0)
-#endif
 
 #define SIZE (THUNK_2_SIZE + THUNK_1_SIZE)
 
@@ -815,13 +805,8 @@ stg_atomicModifyMutVarzuzh ( gcptr mv, gcptr f )
          z = [stg_ap_2 f x]  (max (HS + 2) MIN_UPD_SIZE)
     */
 
-#if defined(MIN_UPD_SIZE) && MIN_UPD_SIZE > 2
-#define THUNK_SIZE (SIZEOF_StgThunkHeader + WDS(MIN_UPD_SIZE))
-#define TICK_ALLOC_THUNK() TICK_ALLOC_UP_THK(WDS(2),WDS(MIN_UPD_SIZE-2))
-#else
 #define THUNK_SIZE (SIZEOF_StgThunkHeader + WDS(2))
 #define TICK_ALLOC_THUNK() TICK_ALLOC_UP_THK(WDS(2),0)
-#endif
 
     HP_CHK_GEN_TICKY(THUNK_SIZE);
 


=====================================
testsuite/tests/driver/recomp011/all.T
=====================================
@@ -2,7 +2,6 @@
 
 test('recomp011',
      [ extra_files(['Main.hs'])
-     , when(arch('powerpc64'), expect_broken(11260))
      , js_broken(22261)
      ],
      makefile_test, [])


=====================================
testsuite/tests/driver/recomp015/all.T
=====================================
@@ -5,7 +5,7 @@ test('recomp015',
        # See ticket:11022#comment:7
        unless(opsys('linux') or opsys('solaris2') or opsys('openbsd'), skip),
        when(arch('arm'), skip),
-       js_skip, # JS backend doesn't support .s assembly files
-       when(arch('powerpc64'), expect_broken(11323))],
+       js_skip # JS backend doesn't support .s assembly files
+     ],
      makefile_test, [])
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5cce070d396e17283528a64cc63841330b9c5020...c3ca62151a0c514e843e555cdb76ffa857a7e6fb

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5cce070d396e17283528a64cc63841330b9c5020...c3ca62151a0c514e843e555cdb76ffa857a7e6fb
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/20231021/5fb9f34c/attachment-0001.html>


More information about the ghc-commits mailing list