[Git][ghc/ghc][wip/stack_cloning] Assure that cloned RET_BIG closures are valid (#18741)

Sven Tennie gitlab at gitlab.haskell.org
Sun Nov 15 16:08:28 UTC 2020



Sven Tennie pushed to branch wip/stack_cloning at Glasgow Haskell Compiler / GHC


Commits:
c34fe9ab by Sven Tennie at 2020-11-15T17:08:05+01:00
Assure that cloned RET_BIG closures are valid (#18741)

- - - - -


3 changed files:

- testsuite/tests/rts/all.T
- + testsuite/tests/rts/cloneMyStack_retBigStackFrame.hs
- testsuite/tests/rts/cloneStackLib.c


Changes:

=====================================
testsuite/tests/rts/all.T
=====================================
@@ -421,5 +421,6 @@ test('T15427', normal, compile_and_run, [''])
 
 test('cloneMyStack', [extra_files(['cloneStackLib.c'])], compile_and_run, ['cloneStackLib.c'])
 test('cloneMyStack2', ignore_stdout, compile_and_run, [''])
+test('cloneMyStack_retBigStackFrame', [extra_files(['cloneStackLib.c']), ignore_stdout], compile_and_run, ['cloneStackLib.c'])
 
 test('cloneThreadStack', [only_ways(['threaded1']), extra_ways(['threaded1']), extra_files(['cloneStackLib.c'])], compile_and_run, ['cloneStackLib.c -threaded'])


=====================================
testsuite/tests/rts/cloneMyStack_retBigStackFrame.hs
=====================================
@@ -0,0 +1,42 @@
+{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE ForeignFunctionInterface #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+
+module Main where
+
+import Control.Concurrent
+import Data.IORef
+import GHC.IO.Unsafe
+import GHC.Prim (StackSnapshot#)
+import GHC.Stack.CloneStack
+import System.Mem
+
+foreign import ccall "expectSixtyFourOnesInRetBigFrame" expectSixtyFourOnesInRetBigFrame :: StackSnapshot# -> IO ()
+
+cloneStack_returnInt :: IORef (Maybe StackSnapshot) -> Int
+cloneStack_returnInt ioRef = unsafePerformIO $ do
+  stackSnapshot <- cloneMyStack
+  writeIORef ioRef (Just stackSnapshot)
+  return 42
+
+main :: IO ()
+main = do
+  stackRef <- newIORef Nothing
+
+  bigFun (cloneStack_returnInt stackRef) 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1
+
+  Just (StackSnapshot stackSnapshot) <- readIORef stackRef
+
+  -- Ensure no old data is found.
+  performMajorGC
+
+  expectSixtyFourOnesInRetBigFrame stackSnapshot
+
+  return ()
+
+bigFun !a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19 a20 a21 a22 a23 a24 a25 a26 a27 a28 a29 a30 a31 a32 a33 a34 a35 a36 a37 a38 a39 a40 a41 a42 a43 a44 a45 a46 a47 a48 a49 a50 a51 a52 a53 a54 a55 a56 a57 a58 a59 a60 a61 a62 a63 a64 a65 =
+  do
+    print $ a1 + a2 + a3 + a4 + a5 + a6 + a7 + a8 + a9 + a10 + a11 + a12 + a13 + a14 + a15 + a16 + a17 + a18 + a19 + a20 + a21 + a22 + a23 + a24 + a25 + a26 + a27 + a28 + a29 + a30 + a31 + a32 + a33 + a34 + a35 + a36 + a37 + a38 + a39 + a40 + a41 + a42 + a43 + a44 + a45 + a46 + a47 + a48 + a49 + a50 + a51 + a52 + a53 + a54 + a55 + a56 + a57 + a58 + a59 + a60 + a61 + a62 + a63 + a64 + a65
+
+    return ()


=====================================
testsuite/tests/rts/cloneStackLib.c
=====================================
@@ -1,6 +1,7 @@
 #include "Rts.h"
 #include "RtsAPI.h"
 #include "rts/Messages.h"
+#include <string.h>
 
 
 void expectStacksToBeEqual(StgStack *clonedStack, StgTSO *tso) {
@@ -53,3 +54,58 @@ void expectClosureTypes(StgStack *stack, unsigned int types[], size_t typesSize)
         }
     }
 }
+
+// Count all (#I 1) closures of the RET_BIG closure's payload.
+static int countOnes(StgPtr spBottom, StgPtr payload,
+                     StgLargeBitmap *large_bitmap, uint32_t size) {
+  StgWord bmp;
+  uint32_t i, j;
+  int ones = 0;
+
+  i = 0;
+  for (bmp = 0; i < size; bmp++) {
+    StgWord bitmap = large_bitmap->bitmap[bmp];
+    j = 0;
+    for (; i < size && j < BITS_IN(W_); j++, i++, bitmap >>= 1) {
+      if ((bitmap & 1) == 0) {
+        const StgClosure *closure = UNTAG_CLOSURE((StgClosure *)payload[i]);
+        const StgInfoTable *info = get_itbl(closure);
+
+        switch (info->type) {
+        case CONSTR_0_1: {
+          StgConInfoTable *con_info = get_con_itbl(closure);
+          if (strcmp(GET_CON_DESC(con_info), "ghc-prim:GHC.Types.I#") == 0 &&
+              closure->payload[0] == 1) {
+            ones++;
+          }
+          break;
+        }
+        default: {
+          break;
+        }
+        }
+      }
+    }
+  }
+
+  return ones;
+}
+
+void expectSixtyFourOnesInRetBigFrame(StgStack *stack) {
+  StgPtr sp = stack->sp;
+  StgPtr spBottom = stack->stack + stack->stack_size;
+
+  for (; sp < spBottom; sp += stack_frame_sizeW((StgClosure *)sp)) {
+    const StgInfoTable *info = get_itbl((StgClosure *)sp);
+
+    if (info->type == RET_BIG) {
+      StgLargeBitmap *bitmap = GET_LARGE_BITMAP(info);
+      int ones = countOnes(spBottom, (StgPtr)((StgClosure *)sp)->payload,
+                           bitmap, bitmap->size);
+
+      if (ones != 64) {
+        barf("Expected 64 ones, got %i!", ones);
+      }
+    }
+  }
+}



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c34fe9ab19a868ffcef8e6fe7927ef0ebd1f7126

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c34fe9ab19a868ffcef8e6fe7927ef0ebd1f7126
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/20201115/46a43e6e/attachment-0001.html>


More information about the ghc-commits mailing list