summaryrefslogtreecommitdiff
path: root/libraries/ghc-heap/tests
diff options
context:
space:
mode:
authorSven Tennie <sven.tennie@gmail.com>2023-05-08 18:29:32 +0000
committerSven Tennie <sven.tennie@gmail.com>2023-05-08 18:29:32 +0000
commite778d8320606726a820f7f351b87f94e0f5a9888 (patch)
tree000d130b73c71b71e58c550979cb8a3bcf1ab5c4 /libraries/ghc-heap/tests
parent2c9f1a364f278299d2a89fb884c471d2d7883e8c (diff)
downloadhaskell-wip/decode_cloned_stack.tar.gz
ghc-heap: Decode StgStack and its stack frameswip/decode_cloned_stack
Previously, ghc-heap could only decode heap closures. The approach is explained in detail in note [Decoding the stack].
Diffstat (limited to 'libraries/ghc-heap/tests')
-rw-r--r--libraries/ghc-heap/tests/TestUtils.hs53
-rw-r--r--libraries/ghc-heap/tests/all.T45
-rw-r--r--libraries/ghc-heap/tests/stack_big_ret.hs142
-rw-r--r--libraries/ghc-heap/tests/stack_misc_closures.hs526
-rw-r--r--libraries/ghc-heap/tests/stack_misc_closures_c.c357
-rw-r--r--libraries/ghc-heap/tests/stack_misc_closures_prim.cmm231
-rw-r--r--libraries/ghc-heap/tests/stack_stm_frames.hs38
-rw-r--r--libraries/ghc-heap/tests/stack_underflow.hs49
8 files changed, 1438 insertions, 3 deletions
diff --git a/libraries/ghc-heap/tests/TestUtils.hs b/libraries/ghc-heap/tests/TestUtils.hs
index 4f297cae3a..7193a4ac80 100644
--- a/libraries/ghc-heap/tests/TestUtils.hs
+++ b/libraries/ghc-heap/tests/TestUtils.hs
@@ -1,7 +1,54 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MagicHash #-}
-module TestUtils where
+{-# LANGUAGE UnliftedFFITypes #-}
-assertEqual :: (Show a, Eq a) => a -> a -> IO ()
+module TestUtils
+ ( assertEqual,
+ assertThat,
+ assertStackInvariants,
+ getDecodedStack,
+ unbox,
+ )
+where
+
+import Control.Monad.IO.Class
+import Data.Array.Byte
+import Data.Foldable
+import Debug.Trace
+import GHC.Exts
+import GHC.Exts.Heap
+import GHC.Exts.Heap.Closures
+import GHC.Exts.Stack.Decode
+import GHC.Records
+import GHC.Stack (HasCallStack)
+import GHC.Stack.CloneStack
+import Unsafe.Coerce (unsafeCoerce)
+
+getDecodedStack :: IO (StackSnapshot, [StackFrame])
+getDecodedStack = do
+ stack <- cloneMyStack
+ stackClosure <- decodeStack stack
+
+ pure (stack, ssc_stack stackClosure)
+
+assertEqual :: (HasCallStack, Monad m, Show a, Eq a) => a -> a -> m ()
assertEqual a b
| a /= b = error (show a ++ " /= " ++ show b)
- | otherwise = return ()
+ | otherwise = pure ()
+
+assertThat :: (HasCallStack, Monad m) => String -> (a -> Bool) -> a -> m ()
+assertThat s f a = if f a then pure () else error s
+
+assertStackInvariants :: (HasCallStack, MonadIO m) => [StackFrame] -> m ()
+assertStackInvariants decodedStack =
+ assertThat
+ "Last frame is stop frame"
+ ( \case
+ StopFrame info -> tipe info == STOP_FRAME
+ _ -> False
+ )
+ (last decodedStack)
+
+unbox :: Box -> IO Closure
+unbox = getBoxedClosureData
diff --git a/libraries/ghc-heap/tests/all.T b/libraries/ghc-heap/tests/all.T
index 78cb925021..b0f32e978f 100644
--- a/libraries/ghc-heap/tests/all.T
+++ b/libraries/ghc-heap/tests/all.T
@@ -57,3 +57,48 @@ test('parse_tso_flags',
test('T21622',
only_ways(['normal']),
compile_and_run, [''])
+
+test('stack_big_ret',
+ [
+ extra_files(['TestUtils.hs']),
+ ignore_stdout,
+ ignore_stderr
+ ],
+ compile_and_run,
+ [''])
+
+# Options:
+# - `-kc512B -kb64B`: Make stack chunk size small to provoke underflow
+# stack frames.
+test('stack_underflow',
+ [
+ extra_files(['TestUtils.hs']),
+ extra_run_opts('+RTS -kc512B -kb64B -RTS'),
+ ignore_stdout,
+ ignore_stderr
+ ],
+ compile_and_run,
+ [''])
+
+test('stack_stm_frames',
+ [
+ extra_files(['TestUtils.hs']),
+ ignore_stdout,
+ ignore_stderr
+ ],
+ compile_and_run,
+ [''])
+
+test('stack_misc_closures',
+ [
+ extra_files(['stack_misc_closures_c.c', 'stack_misc_closures_prim.cmm', 'TestUtils.hs']),
+ ignore_stdout,
+ ignore_stderr
+ ],
+ multi_compile_and_run,
+ ['stack_misc_closures',
+ [ ('stack_misc_closures_c.c', '')
+ ,('stack_misc_closures_prim.cmm', '')
+ ]
+ , '-debug' # Debug RTS to use checkSTACK() (Sanity.c)
+ ])
diff --git a/libraries/ghc-heap/tests/stack_big_ret.hs b/libraries/ghc-heap/tests/stack_big_ret.hs
new file mode 100644
index 0000000000..845c560abc
--- /dev/null
+++ b/libraries/ghc-heap/tests/stack_big_ret.hs
@@ -0,0 +1,142 @@
+{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+
+module Main where
+
+import Control.Concurrent
+import Data.IORef
+import Data.Maybe
+import GHC.Exts (StackSnapshot#)
+import GHC.Exts.Heap
+import GHC.Exts.Heap.ClosureTypes
+import GHC.Exts.Heap.Closures
+import GHC.Exts.Heap.InfoTable.Types
+import GHC.Exts.Stack.Decode
+import GHC.IO.Unsafe
+import GHC.Stack (HasCallStack)
+import GHC.Stack.CloneStack
+import System.IO (hPutStrLn, stderr)
+import System.Mem
+import TestUtils
+
+cloneStackReturnInt :: IORef (Maybe StackSnapshot) -> Int
+cloneStackReturnInt ioRef = unsafePerformIO $ do
+ stackSnapshot <- cloneMyStack
+
+ writeIORef ioRef (Just stackSnapshot)
+
+ pure 42
+
+-- | Clone a stack with a RET_BIG closure and decode it.
+main :: HasCallStack => IO ()
+main = do
+ stackRef <- newIORef Nothing
+
+ bigFun (cloneStackReturnInt stackRef) 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64
+
+ mbStackSnapshot <- readIORef stackRef
+ let stackSnapshot = fromJust mbStackSnapshot
+ stackClosure <- decodeStack stackSnapshot
+ let stackFrames = ssc_stack stackClosure
+
+ assertStackInvariants stackFrames
+ assertThat
+ "Stack contains one big return frame"
+ (== 1)
+ (length $ filter isBigReturnFrame stackFrames)
+ let cs = (stack_payload . head) $ filter isBigReturnFrame stackFrames
+ let xs = zip [1 ..] cs
+ mapM_ (uncurry checkArg) xs
+
+checkArg :: Word -> StackField -> IO ()
+checkArg w sf =
+ case sf of
+ StackWord _ -> error "Unexpected payload type from bitmap."
+ StackBox b -> do
+ c <- getBoxedClosureData b
+ assertEqual CONSTR_0_1 $ (tipe . info) c
+ assertEqual "I#" (name c)
+ assertEqual "ghc-prim" (pkg c)
+ assertEqual "GHC.Types" (modl c)
+ assertEqual True $ (null . ptrArgs) c
+ assertEqual [w] (dataArgs c)
+ pure ()
+
+isBigReturnFrame :: StackFrame -> Bool
+isBigReturnFrame (RetBig info _) = tipe info == RET_BIG
+isBigReturnFrame _ = False
+
+{-# NOINLINE bigFun #-}
+bigFun ::
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ Int ->
+ IO ()
+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
+
+ pure ()
diff --git a/libraries/ghc-heap/tests/stack_misc_closures.hs b/libraries/ghc-heap/tests/stack_misc_closures.hs
new file mode 100644
index 0000000000..821b85f674
--- /dev/null
+++ b/libraries/ghc-heap/tests/stack_misc_closures.hs
@@ -0,0 +1,526 @@
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE GHCForeignImportPrim #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE UnliftedDatatypes #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+
+module Main where
+
+import Data.Functor
+import Debug.Trace
+import GHC.Exts
+import GHC.Exts.Heap
+import GHC.Exts.Heap (getBoxedClosureData)
+import GHC.Exts.Heap.Closures
+import GHC.Exts.Heap.Closures (GenStackFrame (retFunFun), StackField)
+import GHC.Exts.Stack
+import GHC.Exts.Stack.Decode
+import GHC.IO (IO (..))
+import GHC.Stack (HasCallStack)
+import GHC.Stack.CloneStack (StackSnapshot (..))
+import System.Info
+import System.Mem
+import TestUtils
+import Unsafe.Coerce (unsafeCoerce)
+
+foreign import prim "any_update_framezh" any_update_frame# :: SetupFunction
+
+foreign import prim "any_catch_framezh" any_catch_frame# :: SetupFunction
+
+foreign import prim "any_catch_stm_framezh" any_catch_stm_frame# :: SetupFunction
+
+foreign import prim "any_catch_retry_framezh" any_catch_retry_frame# :: SetupFunction
+
+foreign import prim "any_atomically_framezh" any_atomically_frame# :: SetupFunction
+
+foreign import prim "any_ret_small_prim_framezh" any_ret_small_prim_frame# :: SetupFunction
+
+foreign import prim "any_ret_small_prims_framezh" any_ret_small_prims_frame# :: SetupFunction
+
+foreign import prim "any_ret_small_closure_framezh" any_ret_small_closure_frame# :: SetupFunction
+
+foreign import prim "any_ret_small_closures_framezh" any_ret_small_closures_frame# :: SetupFunction
+
+foreign import prim "any_ret_big_prims_min_framezh" any_ret_big_prims_min_frame# :: SetupFunction
+
+foreign import prim "any_ret_big_closures_min_framezh" any_ret_big_closures_min_frame# :: SetupFunction
+
+foreign import prim "any_ret_big_closures_two_words_framezh" any_ret_big_closures_two_words_frame# :: SetupFunction
+
+foreign import prim "any_ret_fun_arg_n_prim_framezh" any_ret_fun_arg_n_prim_frame# :: SetupFunction
+
+foreign import prim "any_ret_fun_arg_gen_framezh" any_ret_fun_arg_gen_frame# :: SetupFunction
+
+foreign import prim "any_ret_fun_arg_gen_big_framezh" any_ret_fun_arg_gen_big_frame# :: SetupFunction
+
+foreign import prim "any_bco_framezh" any_bco_frame# :: SetupFunction
+
+foreign import prim "any_underflow_framezh" any_underflow_frame# :: SetupFunction
+
+foreign import ccall "maxSmallBitmapBits" maxSmallBitmapBits_c :: Word
+
+foreign import ccall "bitsInWord" bitsInWord :: Word
+
+{- Test stategy
+ ~~~~~~~~~~~~
+
+- Create @StgStack@s in C that contain two frames: A stop frame and the frame
+which's decoding should be tested.
+
+- Cmm primops are used to get `StackSnapshot#` values. (This detour ensures that
+the closures are referenced by `StackSnapshot#` and not garbage collected right
+away.)
+
+- These can then be decoded and checked.
+
+This strategy may look pretty complex for a test. But, it can provide very
+specific corner cases that would be hard to (reliably!) produce in Haskell.
+
+N.B. `StackSnapshots` are managed by the garbage collector. It's important to
+know that the GC may rewrite parts of the stack and that the stack must be sound
+(otherwise, the GC may fail badly.) To find subtle garbage collection related
+bugs, the GC is triggered several times.
+
+The decission to make `StackSnapshots`s (and their closures) being managed by the
+GC isn't accidential. It's closer to the reality of decoding stacks.
+
+N.B. the test data stack are only meant be de decoded. They are not executable
+(the result would likely be a crash or non-sense.)
+
+- Due to the implementation details of the test framework, the Debug.Trace calls
+are only shown when the test fails. They are used as markers to see where the
+test fails on e.g. a segfault (where the HasCallStack constraint isn't helpful.)
+-}
+main :: HasCallStack => IO ()
+main = do
+ traceM "Test 1"
+ test any_update_frame# $
+ \case
+ UpdateFrame {..} -> do
+ assertEqual (tipe info_tbl) UPDATE_FRAME
+ assertEqual 1 =<< getWordFromBlackhole updatee
+ e -> error $ "Wrong closure type: " ++ show e
+ traceM "Test 2"
+ testSize any_update_frame# 2
+ traceM "Test 3"
+ test any_catch_frame# $
+ \case
+ CatchFrame {..} -> do
+ assertEqual (tipe info_tbl) CATCH_FRAME
+ assertEqual exceptions_blocked 1
+ assertConstrClosure 1 handler
+ e -> error $ "Wrong closure type: " ++ show e
+ traceM "Test 4"
+ testSize any_catch_frame# 3
+ traceM "Test 5"
+ test any_catch_stm_frame# $
+ \case
+ CatchStmFrame {..} -> do
+ assertEqual (tipe info_tbl) CATCH_STM_FRAME
+ assertConstrClosure 1 catchFrameCode
+ assertConstrClosure 2 handler
+ e -> error $ "Wrong closure type: " ++ show e
+ traceM "Test 6"
+ testSize any_catch_stm_frame# 3
+ traceM "Test 7"
+ test any_catch_retry_frame# $
+ \case
+ CatchRetryFrame {..} -> do
+ assertEqual (tipe info_tbl) CATCH_RETRY_FRAME
+ assertEqual running_alt_code 1
+ assertConstrClosure 2 first_code
+ assertConstrClosure 3 alt_code
+ e -> error $ "Wrong closure type: " ++ show e
+ traceM "Test 8"
+ testSize any_catch_retry_frame# 4
+ traceM "Test 9"
+ test any_atomically_frame# $
+ \case
+ AtomicallyFrame {..} -> do
+ assertEqual (tipe info_tbl) ATOMICALLY_FRAME
+ assertConstrClosure 1 atomicallyFrameCode
+ assertConstrClosure 2 result
+ e -> error $ "Wrong closure type: " ++ show e
+ traceM "Test 10"
+ testSize any_atomically_frame# 3
+ traceM "Test 11"
+ test any_ret_small_prim_frame# $
+ \case
+ RetSmall {..} -> do
+ assertEqual (tipe info_tbl) RET_SMALL
+ assertEqual (length stack_payload) 1
+ assertUnknownTypeWordSizedPrimitive 1 (head stack_payload)
+ e -> error $ "Wrong closure type: " ++ show e
+ traceM "Test 12"
+ testSize any_ret_small_prim_frame# 2
+ traceM "Test 13"
+ test any_ret_small_closure_frame# $
+ \case
+ RetSmall {..} -> do
+ assertEqual (tipe info_tbl) RET_SMALL
+ assertEqual (length stack_payload) 1
+ assertConstrClosure 1 $ (stackFieldClosure . head) stack_payload
+ e -> error $ "Wrong closure type: " ++ show e
+ traceM "Test 14"
+ testSize any_ret_small_closure_frame# 2
+ traceM "Test 15"
+ test any_ret_small_closures_frame# $
+ \case
+ RetSmall {..} -> do
+ assertEqual (tipe info_tbl) RET_SMALL
+ assertEqual (length stack_payload) maxSmallBitmapBits
+ wds <- mapM (getWordFromConstr01 . stackFieldClosure) stack_payload
+ assertEqual wds [1 .. maxSmallBitmapBits]
+ e -> error $ "Wrong closure type: " ++ show e
+ traceM "Test 16"
+ testSize any_ret_small_closures_frame# (1 + fromIntegral maxSmallBitmapBits_c)
+ traceM "Test 17"
+ test any_ret_small_prims_frame# $
+ \case
+ RetSmall {..} -> do
+ assertEqual (tipe info_tbl) RET_SMALL
+ assertEqual (length stack_payload) maxSmallBitmapBits
+ let wds = map stackFieldWord stack_payload
+ assertEqual wds [1 .. maxSmallBitmapBits]
+ e -> error $ "Wrong closure type: " ++ show e
+ traceM "Test 18"
+ testSize any_ret_small_prims_frame# (1 + fromIntegral maxSmallBitmapBits_c)
+ traceM "Test 19"
+ test any_ret_big_prims_min_frame# $
+ \case
+ RetBig {..} -> do
+ assertEqual (tipe info_tbl) RET_BIG
+ assertEqual (length stack_payload) minBigBitmapBits
+ let wds = map stackFieldWord stack_payload
+ assertEqual wds [1 .. minBigBitmapBits]
+ e -> error $ "Wrong closure type: " ++ show e
+ traceM "Test 20"
+ testSize any_ret_big_prims_min_frame# (minBigBitmapBits + 1)
+ traceM "Test 21"
+ test any_ret_big_closures_min_frame# $
+ \case
+ RetBig {..} -> do
+ assertEqual (tipe info_tbl) RET_BIG
+ assertEqual (length stack_payload) minBigBitmapBits
+ wds <- mapM (getWordFromConstr01 . stackFieldClosure) stack_payload
+ assertEqual wds [1 .. minBigBitmapBits]
+ e -> error $ "Wrong closure type: " ++ show e
+ traceM "Test 22"
+ testSize any_ret_big_closures_min_frame# (minBigBitmapBits + 1)
+ traceM "Test 23"
+ test any_ret_big_closures_two_words_frame# $
+ \case
+ RetBig {..} -> do
+ assertEqual (tipe info_tbl) RET_BIG
+ let closureCount = fromIntegral $ bitsInWord + 1
+ assertEqual (length stack_payload) closureCount
+ wds <- mapM (getWordFromConstr01 . stackFieldClosure) stack_payload
+ assertEqual wds [1 .. (fromIntegral closureCount)]
+ e -> error $ "Wrong closure type: " ++ show e
+ traceM "Test 24"
+ testSize any_ret_big_closures_two_words_frame# (fromIntegral bitsInWord + 1 + 1)
+ traceM "Test 25"
+ test any_ret_fun_arg_n_prim_frame# $
+ \case
+ RetFun {..} -> do
+ assertEqual (tipe info_tbl) RET_FUN
+ assertEqual retFunType ARG_N
+ assertEqual retFunSize 1
+ assertFun01Closure 1 retFunFun
+ assertEqual (length retFunPayload) 1
+ let wds = map stackFieldWord retFunPayload
+ assertEqual wds [1]
+ e -> error $ "Wrong closure type: " ++ show e
+ traceM "Test 26"
+ test any_ret_fun_arg_gen_frame# $
+ \case
+ RetFun {..} -> do
+ assertEqual (tipe info_tbl) RET_FUN
+ assertEqual retFunType ARG_GEN
+ assertEqual retFunSize 9
+ retFunFun' <- getBoxedClosureData retFunFun
+ case retFunFun' of
+ FunClosure {..} -> do
+ assertEqual (tipe info) FUN_STATIC
+ assertEqual (null dataArgs) True
+ -- Darwin seems to have a slightly different layout regarding
+ -- function `argGenFun`
+ assertEqual (null ptrArgs) (os /= "darwin")
+ e -> error $ "Wrong closure type: " ++ show e
+ assertEqual (length retFunPayload) 9
+ wds <- mapM (getWordFromConstr01 . stackFieldClosure) retFunPayload
+ assertEqual wds [1 .. 9]
+ e -> error $ "Wrong closure type: " ++ show e
+ traceM "Test 27"
+ testSize any_ret_fun_arg_gen_frame# (3 + 9)
+ traceM "Test 28"
+ test any_ret_fun_arg_gen_big_frame# $
+ \case
+ RetFun {..} -> do
+ assertEqual (tipe info_tbl) RET_FUN
+ assertEqual retFunType ARG_GEN_BIG
+ assertEqual retFunSize 59
+ retFunFun' <- getBoxedClosureData retFunFun
+ case retFunFun' of
+ FunClosure {..} -> do
+ assertEqual (tipe info) FUN_STATIC
+ assertEqual (null dataArgs) True
+ assertEqual (null ptrArgs) True
+ e -> error $ "Wrong closure type: " ++ show e
+ assertEqual (length retFunPayload) 59
+ wds <- mapM (getWordFromConstr01 . stackFieldClosure) retFunPayload
+ assertEqual wds [1 .. 59]
+ traceM "Test 29"
+ testSize any_ret_fun_arg_gen_big_frame# (3 + 59)
+ traceM "Test 30"
+ test any_bco_frame# $
+ \case
+ RetBCO {..} -> do
+ assertEqual (tipe info_tbl) RET_BCO
+ assertEqual (length bcoArgs) 1
+ wds <- mapM (getWordFromConstr01 . stackFieldClosure) bcoArgs
+ assertEqual wds [3]
+ bco' <- getBoxedClosureData bco
+ case bco' of
+ BCOClosure {..} -> do
+ assertEqual (tipe info) BCO
+ assertEqual arity 3
+ assertEqual size 7
+ assertArrWordsClosure [1] instrs
+ assertArrWordsClosure [2] literals
+ assertMutArrClosure [3] bcoptrs
+ assertEqual
+ [ 1, -- StgLargeBitmap size in words
+ 0 -- StgLargeBitmap first words
+ ]
+ bitmap
+ e -> error $ "Wrong closure type: " ++ show e
+ e -> error $ "Wrong closure type: " ++ show e
+ traceM "Test 31"
+ testSize any_bco_frame# 3
+ traceM "Test 32"
+ test any_underflow_frame# $
+ \case
+ UnderflowFrame {..} -> do
+ assertEqual (tipe info_tbl) UNDERFLOW_FRAME
+ assertEqual (tipe (ssc_info nextChunk)) STACK
+ assertEqual (ssc_stack_size nextChunk) 27
+ assertEqual (ssc_stack_dirty nextChunk) 0
+ assertEqual (ssc_stack_marking nextChunk) 0
+ assertEqual (length (ssc_stack nextChunk)) 2
+ case head (ssc_stack nextChunk) of
+ RetSmall {..} ->
+ assertEqual (tipe info_tbl) RET_SMALL
+ e -> error $ "Wrong closure type: " ++ show e
+ case last (ssc_stack nextChunk) of
+ StopFrame {..} ->
+ assertEqual (tipe info_tbl) STOP_FRAME
+ e -> error $ "Wrong closure type: " ++ show e
+ e -> error $ "Wrong closure type: " ++ show e
+ testSize any_underflow_frame# 2
+
+type SetupFunction = State# RealWorld -> (# State# RealWorld, StackSnapshot# #)
+
+test :: HasCallStack => SetupFunction -> (StackFrame -> IO ()) -> IO ()
+test setup assertion = do
+ stackSnapshot <- getStackSnapshot setup
+ performGC
+ traceM $ "entertainGC - " ++ entertainGC 100
+ -- Run garbage collection now, to prevent later surprises: It's hard to debug
+ -- when the GC suddenly does it's work and there were bad closures or pointers.
+ -- Better fail early, here.
+ performGC
+ stackClosure <- decodeStack stackSnapshot
+ performGC
+ let stack = ssc_stack stackClosure
+ performGC
+ assert stack
+ where
+ assert :: [StackFrame] -> IO ()
+ assert stack = do
+ assertStackInvariants stack
+ assertEqual (length stack) 2
+ assertion $ head stack
+
+entertainGC :: Int -> String
+entertainGC 0 = "0"
+entertainGC x = show x ++ entertainGC (x - 1)
+
+testSize :: HasCallStack => SetupFunction -> Int -> IO ()
+testSize setup expectedSize = do
+ stackSnapshot <- getStackSnapshot setup
+ stackClosure <- decodeStack stackSnapshot
+ assertEqual expectedSize $ (stackFrameSize . head . ssc_stack) stackClosure
+
+-- | Get a `StackSnapshot` from test setup
+--
+-- This function mostly resembles `cloneStack`. Though, it doesn't clone, but
+-- just pulls a @StgStack@ from RTS to Haskell land.
+getStackSnapshot :: SetupFunction -> IO StackSnapshot
+getStackSnapshot action# = IO $ \s ->
+ case action# s of (# s1, stack #) -> (# s1, StackSnapshot stack #)
+
+assertConstrClosure :: HasCallStack => Word -> Box -> IO ()
+assertConstrClosure w c =
+ getBoxedClosureData c >>= \case
+ ConstrClosure {..} -> do
+ assertEqual (tipe info) CONSTR_0_1
+ assertEqual dataArgs [w]
+ assertEqual (null ptrArgs) True
+ e -> error $ "Wrong closure type: " ++ show e
+
+assertArrWordsClosure :: HasCallStack => [Word] -> Box -> IO ()
+assertArrWordsClosure wds c =
+ getBoxedClosureData c >>= \case
+ ArrWordsClosure {..} -> do
+ assertEqual (tipe info) ARR_WORDS
+ assertEqual arrWords wds
+ e -> error $ "Wrong closure type: " ++ show e
+
+assertMutArrClosure :: HasCallStack => [Word] -> Box -> IO ()
+assertMutArrClosure wds c =
+ getBoxedClosureData c >>= \case
+ MutArrClosure {..} -> do
+ assertEqual (tipe info) MUT_ARR_PTRS_FROZEN_CLEAN
+ assertEqual wds =<< mapM getWordFromConstr01 mccPayload
+ e -> error $ "Wrong closure type: " ++ show e
+
+assertFun01Closure :: HasCallStack => Word -> Box -> IO ()
+assertFun01Closure w c =
+ getBoxedClosureData c >>= \case
+ FunClosure {..} -> do
+ assertEqual (tipe info) FUN_0_1
+ assertEqual dataArgs [w]
+ assertEqual (null ptrArgs) True
+ e -> error $ "Wrong closure type: " ++ show e
+
+getWordFromConstr01 :: HasCallStack => Box -> IO Word
+getWordFromConstr01 c =
+ getBoxedClosureData c >>= \case
+ ConstrClosure {..} -> pure $ head dataArgs
+ e -> error $ "Wrong closure type: " ++ show e
+
+getWordFromBlackhole :: HasCallStack => Box -> IO Word
+getWordFromBlackhole c =
+ getBoxedClosureData c >>= \case
+ BlackholeClosure {..} -> getWordFromConstr01 indirectee
+ -- For test stability reasons: Expect that the blackhole might have been
+ -- resolved.
+ ConstrClosure {..} -> pure $ head dataArgs
+ e -> error $ "Wrong closure type: " ++ show e
+
+assertUnknownTypeWordSizedPrimitive :: HasCallStack => Word -> StackField -> IO ()
+assertUnknownTypeWordSizedPrimitive w stackField =
+ assertEqual (stackFieldWord stackField) w
+
+unboxSingletonTuple :: (# StackSnapshot# #) -> StackSnapshot#
+unboxSingletonTuple (# s# #) = s#
+
+minBigBitmapBits :: Num a => a
+minBigBitmapBits = 1 + maxSmallBitmapBits
+
+maxSmallBitmapBits :: Num a => a
+maxSmallBitmapBits = fromIntegral maxSmallBitmapBits_c
+
+stackFieldClosure :: HasCallStack => StackField -> Box
+stackFieldClosure (StackBox b) = b
+stackFieldClosure w = error $ "Expected closure in a Box, got: " ++ show w
+
+stackFieldWord :: HasCallStack => StackField -> Word
+stackFieldWord (StackWord w) = w
+stackFieldWord c = error $ "Expected word, got: " ++ show c
+
+-- | A function with 59 arguments
+--
+-- A small bitmap has @64 - 6 = 58@ entries on 64bit machines. On 32bit machines
+-- it's less (for obvious reasons.) I.e. this function's bitmap a large one;
+-- function type is @ARG_GEN_BIG@.
+{-# NOINLINE argGenBigFun #-}
+argGenBigFun ::
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word
+argGenBigFun 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 =
+ 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
+
+-- | A function with more arguments than the pre-generated (@ARG_PPPPPPPP -> 8@) ones
+-- have
+--
+-- This results in a @ARG_GEN@ function (the number of arguments still fits in a
+-- small bitmap).
+{-# NOINLINE argGenFun #-}
+argGenFun ::
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word ->
+ Word
+argGenFun a1 a2 a3 a4 a5 a6 a7 a8 a9 = a1 + a2 + a3 + a4 + a5 + a6 + a7 + a8 + a9
diff --git a/libraries/ghc-heap/tests/stack_misc_closures_c.c b/libraries/ghc-heap/tests/stack_misc_closures_c.c
new file mode 100644
index 0000000000..81cd64431b
--- /dev/null
+++ b/libraries/ghc-heap/tests/stack_misc_closures_c.c
@@ -0,0 +1,357 @@
+#include "Rts.h"
+
+// See rts/Threads.c
+#define MIN_STACK_WORDS (RESERVED_STACK_WORDS + sizeofW(StgStopFrame) + 3)
+
+// Copied from Cmm.h
+#define SIZEOF_W SIZEOF_VOID_P
+#define WDS(n) ((n)*SIZEOF_W)
+
+// Update frames are interpreted by the garbage collector. We play it some
+// tricks here with a fake blackhole.
+RTS_RET(test_fake_blackhole);
+void create_any_update_frame(Capability *cap, StgStack *stack, StgWord w) {
+ StgUpdateFrame *updF = (StgUpdateFrame *)stack->sp;
+ SET_HDR(updF, &stg_upd_frame_info, CCS_SYSTEM);
+ // StgInd and a BLACKHOLE have the same structure
+ StgInd *blackhole = (StgInd *)allocate(cap, sizeofW(StgInd));
+ SET_HDR(blackhole, &test_fake_blackhole_info, CCS_SYSTEM);
+ StgClosure *payload = rts_mkWord(cap, w);
+ blackhole->indirectee = payload;
+ updF->updatee = (StgClosure *)blackhole;
+}
+
+void create_any_catch_frame(Capability *cap, StgStack *stack, StgWord w) {
+ StgCatchFrame *catchF = (StgCatchFrame *)stack->sp;
+ SET_HDR(catchF, &stg_catch_frame_info, CCS_SYSTEM);
+ StgClosure *payload = rts_mkWord(cap, w);
+ catchF->exceptions_blocked = 1;
+ catchF->handler = payload;
+}
+
+void create_any_catch_stm_frame(Capability *cap, StgStack *stack, StgWord w) {
+ StgCatchSTMFrame *catchF = (StgCatchSTMFrame *)stack->sp;
+ SET_HDR(catchF, &stg_catch_stm_frame_info, CCS_SYSTEM);
+ StgClosure *payload1 = rts_mkWord(cap, w);
+ catchF->code = payload1;
+ StgClosure *payload2 = rts_mkWord(cap, w + 1);
+ catchF->handler = payload2;
+}
+
+void create_any_catch_retry_frame(Capability *cap, StgStack *stack, StgWord w) {
+ StgCatchRetryFrame *catchRF = (StgCatchRetryFrame *)stack->sp;
+ SET_HDR(catchRF, &stg_catch_retry_frame_info, CCS_SYSTEM);
+ catchRF->running_alt_code = w++;
+ StgClosure *payload1 = rts_mkWord(cap, w++);
+ catchRF->first_code = payload1;
+ StgClosure *payload2 = rts_mkWord(cap, w);
+ catchRF->alt_code = payload2;
+}
+
+void create_any_atomically_frame(Capability *cap, StgStack *stack, StgWord w) {
+ StgAtomicallyFrame *aF = (StgAtomicallyFrame *)stack->sp;
+ SET_HDR(aF, &stg_atomically_frame_info, CCS_SYSTEM);
+ StgClosure *payload1 = rts_mkWord(cap, w);
+ aF->code = payload1;
+ StgClosure *payload2 = rts_mkWord(cap, w + 1);
+ aF->result = payload2;
+}
+
+void create_any_ret_small_prim_frame(Capability *cap, StgStack *stack,
+ StgWord w) {
+ StgClosure *c = (StgClosure *)stack->sp;
+ SET_HDR(c, &stg_ret_n_info, CCS_SYSTEM);
+ // The cast is a lie (w is interpreted as plain Word, not as pointer), but the
+ // memory layout fits.
+ c->payload[0] = (StgClosure *)w;
+}
+
+void create_any_ret_small_closure_frame(Capability *cap, StgStack *stack,
+ StgWord w) {
+ StgClosure *c = (StgClosure *)stack->sp;
+ SET_HDR(c, &stg_ret_p_info, CCS_SYSTEM);
+ StgClosure *payload = rts_mkWord(cap, w);
+ c->payload[0] = payload;
+}
+
+#define MAX_SMALL_BITMAP_BITS (BITS_IN(W_) - BITMAP_BITS_SHIFT)
+
+StgWord maxSmallBitmapBits() { return MAX_SMALL_BITMAP_BITS; }
+
+StgWord bitsInWord() { return BITS_IN(W_); }
+
+RTS_RET(test_small_ret_full_p);
+void create_any_ret_small_closures_frame(Capability *cap, StgStack *stack,
+ StgWord w) {
+ StgClosure *c = (StgClosure *)stack->sp;
+ SET_HDR(c, &test_small_ret_full_p_info, CCS_SYSTEM);
+ for (int i = 0; i < MAX_SMALL_BITMAP_BITS; i++) {
+ StgClosure *payload1 = UNTAG_CLOSURE(rts_mkWord(cap, w));
+ w++;
+ c->payload[i] = payload1;
+ }
+}
+
+RTS_RET(test_small_ret_full_n);
+void create_any_ret_small_prims_frame(Capability *cap, StgStack *stack,
+ StgWord w) {
+ StgClosure *c = (StgClosure *)stack->sp;
+ SET_HDR(c, &test_small_ret_full_n_info, CCS_SYSTEM);
+ for (int i = 0; i < MAX_SMALL_BITMAP_BITS; i++) {
+ c->payload[i] = (StgClosure *)w;
+ w++;
+ }
+}
+
+#define MIN_LARGE_BITMAP_BITS (MAX_SMALL_BITMAP_BITS + 1)
+
+RTS_RET(test_big_ret_min_n);
+void create_any_ret_big_prims_min_frame(Capability *cap, StgStack *stack,
+ StgWord w) {
+ StgClosure *c = (StgClosure *)stack->sp;
+ SET_HDR(c, &test_big_ret_min_n_info, CCS_SYSTEM);
+
+ for (int i = 0; i < MIN_LARGE_BITMAP_BITS; i++) {
+ c->payload[i] = (StgClosure *)w;
+ w++;
+ }
+}
+
+RTS_RET(test_big_ret_min_p);
+void create_any_ret_big_closures_min_frame(Capability *cap, StgStack *stack,
+ StgWord w) {
+ StgClosure *c = (StgClosure *)stack->sp;
+ SET_HDR(c, &test_big_ret_min_p_info, CCS_SYSTEM);
+
+ for (int i = 0; i < MIN_LARGE_BITMAP_BITS; i++) {
+ c->payload[i] = UNTAG_CLOSURE(rts_mkWord(cap, w));
+ w++;
+ }
+}
+
+#define TWO_WORDS_LARGE_BITMAP_BITS (BITS_IN(W_) + 1)
+
+RTS_RET(test_big_ret_two_words_p);
+void create_any_ret_big_closures_two_words_frame(Capability *cap,
+ StgStack *stack, StgWord w) {
+ StgClosure *c = (StgClosure *)stack->sp;
+ SET_HDR(c, &test_big_ret_two_words_p_info, CCS_SYSTEM);
+
+ for (int i = 0; i < TWO_WORDS_LARGE_BITMAP_BITS; i++) {
+ c->payload[i] = UNTAG_CLOSURE(rts_mkWord(cap, w));
+ w++;
+ }
+}
+
+RTS_RET(test_ret_fun);
+RTS_RET(test_arg_n_fun_0_1);
+void create_any_ret_fun_arg_n_prim_frame(Capability *cap, StgStack *stack,
+ StgWord w) {
+ StgRetFun *c = (StgRetFun *)stack->sp;
+ c->info = &test_ret_fun_info;
+ StgClosure *f =
+ (StgClosure *)allocate(cap, sizeofW(StgClosure) + sizeofW(StgWord));
+ SET_HDR(f, &test_arg_n_fun_0_1_info, ccs)
+ c->fun = f;
+ const StgFunInfoTable *fun_info = get_fun_itbl(UNTAG_CLOSURE(c->fun));
+ c->size = BITMAP_SIZE(stg_arg_bitmaps[fun_info->f.fun_type]);
+ // The cast is a lie (w is interpreted as plain Word, not as pointer), but the
+ // memory layout fits.
+ c->payload[0] = (StgClosure *)w;
+ f->payload[0] = (StgClosure *)w;
+}
+
+RTS_CLOSURE(Main_argGenFun_closure);
+void create_any_ret_fun_arg_gen_frame(Capability *cap, StgStack *stack,
+ StgWord w) {
+ StgRetFun *c = (StgRetFun *)stack->sp;
+ c->info = &test_ret_fun_info;
+ c->fun = &Main_argGenFun_closure;
+ const StgFunInfoTable *fun_info = get_fun_itbl(UNTAG_CLOSURE(c->fun));
+ c->size = BITMAP_SIZE(fun_info->f.b.bitmap);
+ for (int i = 0; i < c->size; i++) {
+ c->payload[i] = rts_mkWord(cap, w++);
+ }
+}
+
+RTS_CLOSURE(Main_argGenBigFun_closure);
+void create_any_ret_fun_arg_gen_big_frame(Capability *cap, StgStack *stack,
+ StgWord w) {
+ StgRetFun *c = (StgRetFun *)stack->sp;
+ c->info = &test_ret_fun_info;
+ c->fun = &Main_argGenBigFun_closure;
+ const StgFunInfoTable *fun_info = get_fun_itbl(UNTAG_CLOSURE(c->fun));
+ c->size = GET_FUN_LARGE_BITMAP(fun_info)->size;
+ for (int i = 0; i < c->size; i++) {
+ c->payload[i] = rts_mkWord(cap, w++);
+ }
+}
+
+RTS_RET(test_ret_bco);
+void create_any_bco_frame(Capability *cap, StgStack *stack, StgWord w) {
+ StgClosure *c = (StgClosure *)stack->sp;
+ SET_HDR(c, &test_ret_bco_info, CCS_SYSTEM);
+ StgWord bcoSizeWords =
+ sizeofW(StgBCO) + sizeofW(StgLargeBitmap) + sizeofW(StgWord);
+ StgBCO *bco = (StgBCO *)allocate(cap, bcoSizeWords);
+ SET_HDR(bco, &stg_BCO_info, CCS_MAIN);
+ c->payload[0] = (StgClosure *)bco;
+
+ bco->size = bcoSizeWords;
+ bco->arity = 3;
+
+ StgArrBytes *instrs =
+ (StgArrBytes *)allocate(cap, sizeofW(StgArrBytes) + sizeofW(StgWord));
+ SET_HDR(instrs, &stg_ARR_WORDS_info, CCCS);
+ instrs->bytes = WDS(1);
+ instrs->payload[0] = w++;
+ bco->instrs = instrs;
+
+ StgArrBytes *literals =
+ (StgArrBytes *)allocate(cap, sizeofW(StgArrBytes) + sizeofW(StgWord));
+ SET_HDR(literals, &stg_ARR_WORDS_info, CCCS);
+ bco->literals = literals;
+ literals->bytes = WDS(1);
+ literals->payload[0] = w++;
+ bco->literals = literals;
+
+ StgWord ptrsSize = 1 + mutArrPtrsCardTableSize(1);
+ StgMutArrPtrs *ptrs =
+ (StgMutArrPtrs *)allocate(cap, sizeofW(StgMutArrPtrs) + ptrsSize);
+ SET_HDR(ptrs, &stg_MUT_ARR_PTRS_FROZEN_CLEAN_info, ccs);
+ ptrs->ptrs = 1;
+ ptrs->size = ptrsSize;
+ ptrs->payload[0] = rts_mkWord(cap, w);
+ bco->ptrs = ptrs;
+
+ StgLargeBitmap *bitmap = (StgLargeBitmap *)bco->bitmap;
+ bitmap->size = 1;
+ bitmap->bitmap[0] = 0; // set bit 0 to 0 indicating a closure
+ c->payload[1] = (StgClosure *)rts_mkWord(cap, w);
+}
+
+StgStack *any_ret_small_prim_frame(Capability *cap);
+
+void create_any_underflow_frame(Capability *cap, StgStack *stack, StgWord w) {
+ StgUnderflowFrame *underflowF = (StgUnderflowFrame *)stack->sp;
+ underflowF->info = &stg_stack_underflow_frame_info;
+ underflowF->next_chunk = any_ret_small_prim_frame(cap);
+}
+
+// Import from Sanity.c - This implies that the test must be run with debug RTS
+// only!
+extern void checkSTACK(StgStack *stack);
+
+// Basically, a stripped down version of createThread() (regarding stack
+// creation)
+StgStack *setup(Capability *cap, StgWord closureSizeWords,
+ void (*f)(Capability *, StgStack *, StgWord)) {
+ StgWord totalSizeWords =
+ sizeofW(StgStack) + closureSizeWords + MIN_STACK_WORDS;
+ StgStack *stack = (StgStack *)allocate(cap, totalSizeWords);
+ SET_HDR(stack, &stg_STACK_info, CCS_SYSTEM);
+ stack->stack_size = totalSizeWords - sizeofW(StgStack);
+ stack->dirty = 0;
+ stack->marking = 0;
+
+ StgPtr spBottom = stack->stack + stack->stack_size;
+ stack->sp = spBottom;
+ stack->sp -= sizeofW(StgStopFrame);
+ SET_HDR((StgClosure *)stack->sp, &stg_stop_thread_info, CCS_SYSTEM);
+ stack->sp -= closureSizeWords;
+
+ // Pointers can easíly be confused with each other. Provide a start value for
+ // values (1) in closures and increment it after every usage. The goal is to
+ // have distinct values in the closure to ensure nothing gets mixed up.
+ f(cap, stack, 1);
+
+ // Make a sanitiy check to find unsound closures before the GC and the decode
+ // code.
+ checkSTACK(stack);
+ return stack;
+}
+
+StgStack *any_update_frame(Capability *cap) {
+ return setup(cap, sizeofW(StgUpdateFrame), &create_any_update_frame);
+}
+
+StgStack *any_catch_frame(Capability *cap) {
+ return setup(cap, sizeofW(StgCatchFrame), &create_any_catch_frame);
+}
+
+StgStack *any_catch_stm_frame(Capability *cap) {
+ return setup(cap, sizeofW(StgCatchSTMFrame), &create_any_catch_stm_frame);
+}
+
+StgStack *any_catch_retry_frame(Capability *cap) {
+ return setup(cap, sizeofW(StgCatchRetryFrame), &create_any_catch_retry_frame);
+}
+
+StgStack *any_atomically_frame(Capability *cap) {
+ return setup(cap, sizeofW(StgAtomicallyFrame), &create_any_atomically_frame);
+}
+
+StgStack *any_ret_small_prim_frame(Capability *cap) {
+ return setup(cap, sizeofW(StgClosure) + sizeofW(StgWord),
+ &create_any_ret_small_prim_frame);
+}
+
+StgStack *any_ret_small_closure_frame(Capability *cap) {
+ return setup(cap, sizeofW(StgClosure) + sizeofW(StgClosurePtr),
+ &create_any_ret_small_closure_frame);
+}
+
+StgStack *any_ret_small_closures_frame(Capability *cap) {
+ return setup(
+ cap, sizeofW(StgClosure) + MAX_SMALL_BITMAP_BITS * sizeofW(StgClosurePtr),
+ &create_any_ret_small_closures_frame);
+}
+
+StgStack *any_ret_small_prims_frame(Capability *cap) {
+ return setup(cap,
+ sizeofW(StgClosure) + MAX_SMALL_BITMAP_BITS * sizeofW(StgWord),
+ &create_any_ret_small_prims_frame);
+}
+
+StgStack *any_ret_big_closures_min_frame(Capability *cap) {
+ return setup(
+ cap, sizeofW(StgClosure) + MIN_LARGE_BITMAP_BITS * sizeofW(StgClosure),
+ &create_any_ret_big_closures_min_frame);
+}
+
+StgStack *any_ret_big_closures_two_words_frame(Capability *cap) {
+ return setup(cap,
+ sizeofW(StgClosure) +
+ TWO_WORDS_LARGE_BITMAP_BITS * sizeofW(StgClosure),
+ &create_any_ret_big_closures_two_words_frame);
+}
+
+StgStack *any_ret_big_prims_min_frame(Capability *cap) {
+ return setup(cap,
+ sizeofW(StgClosure) + MIN_LARGE_BITMAP_BITS * sizeofW(StgWord),
+ &create_any_ret_big_prims_min_frame);
+}
+
+StgStack *any_ret_fun_arg_n_prim_frame(Capability *cap) {
+ return setup(cap, sizeofW(StgRetFun) + sizeofW(StgWord),
+ &create_any_ret_fun_arg_n_prim_frame);
+}
+
+StgStack *any_ret_fun_arg_gen_frame(Capability *cap) {
+ return setup(cap, sizeofW(StgRetFun) + 9 * sizeofW(StgClosure),
+ &create_any_ret_fun_arg_gen_frame);
+}
+
+StgStack *any_ret_fun_arg_gen_big_frame(Capability *cap) {
+ return setup(cap, sizeofW(StgRetFun) + 59 * sizeofW(StgWord),
+ &create_any_ret_fun_arg_gen_big_frame);
+}
+
+StgStack *any_bco_frame(Capability *cap) {
+ return setup(cap, sizeofW(StgClosure) + 2 * sizeofW(StgWord),
+ &create_any_bco_frame);
+}
+
+StgStack *any_underflow_frame(Capability *cap) {
+ return setup(cap, sizeofW(StgUnderflowFrame), &create_any_underflow_frame);
+}
diff --git a/libraries/ghc-heap/tests/stack_misc_closures_prim.cmm b/libraries/ghc-heap/tests/stack_misc_closures_prim.cmm
new file mode 100644
index 0000000000..480810a77e
--- /dev/null
+++ b/libraries/ghc-heap/tests/stack_misc_closures_prim.cmm
@@ -0,0 +1,231 @@
+#include "Cmm.h"
+
+any_update_framezh() {
+ P_ stack;
+ (stack) = ccall any_update_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_catch_framezh() {
+ P_ stack;
+ (stack) = ccall any_catch_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_catch_stm_framezh() {
+ P_ stack;
+ (stack) = ccall any_catch_stm_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_catch_retry_framezh() {
+ P_ stack;
+ (stack) = ccall any_catch_retry_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_atomically_framezh() {
+ P_ stack;
+ (stack) = ccall any_atomically_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_ret_small_prim_framezh() {
+ P_ stack;
+ (stack) = ccall any_ret_small_prim_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_ret_small_prims_framezh() {
+ P_ stack;
+ (stack) = ccall any_ret_small_prims_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_ret_small_closure_framezh() {
+ P_ stack;
+ (stack) = ccall any_ret_small_closure_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_ret_small_closures_framezh() {
+ P_ stack;
+ (stack) = ccall any_ret_small_closures_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_ret_big_prims_min_framezh() {
+ P_ stack;
+ (stack) = ccall any_ret_big_prims_min_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_ret_big_closures_min_framezh() {
+ P_ stack;
+ (stack) = ccall any_ret_big_closures_min_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_ret_big_closures_two_words_framezh() {
+ P_ stack;
+ (stack) = ccall any_ret_big_closures_two_words_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_ret_fun_arg_n_prim_framezh() {
+ P_ stack;
+ (stack) = ccall any_ret_fun_arg_n_prim_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_ret_fun_arg_gen_framezh() {
+ P_ stack;
+ (stack) = ccall any_ret_fun_arg_gen_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_ret_fun_arg_gen_big_framezh() {
+ P_ stack;
+ (stack) = ccall any_ret_fun_arg_gen_big_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_bco_framezh() {
+ P_ stack;
+ (stack) = ccall any_bco_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+any_underflow_framezh() {
+ P_ stack;
+ (stack) = ccall any_underflow_frame(MyCapability() "ptr");
+ return (stack);
+}
+
+INFO_TABLE_RET ( test_small_ret_full_p, RET_SMALL, W_ info_ptr,
+#if SIZEOF_VOID_P == 4
+P_ ptr1, P_ ptr2, P_ ptr3, P_ ptr4, P_ ptr5, P_ ptr6, P_ ptr7, P_ ptr8, P_ ptr9, P_ ptr10,
+P_ ptr11, P_ ptr12, P_ ptr13, P_ ptr14, P_ ptr15, P_ ptr16, P_ ptr17, P_ ptr18, P_ ptr19, P_ ptr20,
+P_ ptr21, P_ ptr22, P_ ptr23, P_ ptr24, P_ ptr25, P_ ptr26, P_ ptr27
+)
+#elif SIZEOF_VOID_P == 8
+P_ ptr1, P_ ptr2, P_ ptr3, P_ ptr4, P_ ptr5, P_ ptr6, P_ ptr7, P_ ptr8, P_ ptr9, P_ ptr10,
+P_ ptr11, P_ ptr12, P_ ptr13, P_ ptr14, P_ ptr15, P_ ptr16, P_ ptr17, P_ ptr18, P_ ptr19, P_ ptr20,
+P_ ptr21, P_ ptr22, P_ ptr23, P_ ptr24, P_ ptr25, P_ ptr26, P_ ptr27, P_ ptr28, P_ ptr29, P_ ptr30,
+P_ ptr31, P_ ptr32, P_ ptr33, P_ ptr34, P_ ptr35, P_ ptr36, P_ ptr37, P_ ptr38, P_ ptr39, P_ ptr40,
+P_ ptr41, P_ ptr42, P_ ptr43, P_ ptr44, P_ ptr45, P_ ptr46, P_ ptr47, P_ ptr48, P_ ptr49, P_ ptr50,
+P_ ptr51, P_ ptr52, P_ ptr53, P_ ptr54, P_ ptr55, P_ ptr56, P_ ptr57, P_ ptr58
+)
+#endif
+ return (/* no return values */)
+{
+ return ();
+}
+
+INFO_TABLE_RET ( test_small_ret_full_n, RET_SMALL, W_ info_ptr,
+#if SIZEOF_VOID_P == 4
+W_ n1, W_ n2, W_ n3, W_ n4, W_ n5, W_ n6, W_ n7, W_ n8, W_ n9, W_ n10,
+W_ n11, W_ n12, W_ n13, W_ n14, W_ n15, W_ n16, W_ n17, W_ n18, W_ n19, W_ n20,
+W_ n21, W_ n22, W_ n23, W_ n24, W_ n25, W_ n26, W_ n27
+)
+#elif SIZEOF_VOID_P == 8
+W_ n1, W_ n2, W_ n3, W_ n4, W_ n5, W_ n6, W_ n7, W_ n8, W_ n9, W_ n10,
+W_ n11, W_ n12, W_ n13, W_ n14, W_ n15, W_ n16, W_ n17, W_ n18, W_ n19, W_ n20,
+W_ n21, W_ n22, W_ n23, W_ n24, W_ n25, W_ n26, W_ n27, W_ n28, W_ n29, W_ n30,
+W_ n31, W_ n32, W_ n33, W_ n34, W_ n35, W_ n36, W_ n37, W_ n38, W_ n39, W_ n40,
+W_ n41, W_ n42, W_ n43, W_ n44, W_ n45, W_ n46, W_ n47, W_ n48, W_ n49, W_ n50,
+W_ n51, W_ n52, W_ n53, W_ n54, W_ n55, W_ n56, W_ n57, W_ n58
+)
+#endif
+ return (/* no return values */)
+{
+ return ();
+}
+
+// Size of this large bitmap closure is: max size of small bitmap + 1
+INFO_TABLE_RET ( test_big_ret_min_n, RET_BIG, W_ info_ptr,
+#if SIZEOF_VOID_P == 4
+W_ n1, W_ n2, W_ n3, W_ n4, W_ n5, W_ n6, W_ n7, W_ n8, W_ n9, W_ n10,
+W_ n11, W_ n12, W_ n13, W_ n14, W_ n15, W_ n16, W_ n17, W_ n18, W_ n19, W_ n20,
+W_ n21, W_ n22, W_ n23, W_ n24, W_ n25, W_ n26, W_ n27, W_ n28
+#elif SIZEOF_VOID_P == 8
+W_ n1, W_ n2, W_ n3, W_ n4, W_ n5, W_ n6, W_ n7, W_ n8, W_ n9, W_ n10,
+W_ n11, W_ n12, W_ n13, W_ n14, W_ n15, W_ n16, W_ n17, W_ n18, W_ n19, W_ n20,
+W_ n21, W_ n22, W_ n23, W_ n24, W_ n25, W_ n26, W_ n27, W_ n28, W_ n29, W_ n30,
+W_ n31, W_ n32, W_ n33, W_ n34, W_ n35, W_ n36, W_ n37, W_ n38, W_ n39, W_ n40,
+W_ n41, W_ n42, W_ n43, W_ n44, W_ n45, W_ n46, W_ n47, W_ n48, W_ n49, W_ n50,
+W_ n51, W_ n52, W_ n53, W_ n54, W_ n55, W_ n56, W_ n57, W_ n58, W_ n59
+#endif
+)
+ return (/* no return values */)
+{
+ return ();
+}
+
+// Size of this large bitmap closure is: max size of small bitmap + 1
+INFO_TABLE_RET ( test_big_ret_min_p, RET_BIG, W_ info_ptr,
+#if SIZEOF_VOID_P == 4
+P_ p1, P_ p2, P_ p3, P_ p4, P_ p5, P_ p6, P_ p7, P_ p8, P_ p9, P_ p10,
+P_ p11, P_ p12, P_ p13, P_ p14, P_ p15, P_ p16, P_ p17, P_ p18, P_ p19, P_ p20,
+P_ p21, P_ p22, P_ p23, P_ p24, P_ p25, P_ p26, P_ p27, P_ p28
+#elif SIZEOF_VOID_P == 8
+P_ p1, P_ p2, P_ p3, P_ p4, P_ p5, P_ p6, P_ p7, P_ p8, P_ p9, P_ p10,
+P_ p11, P_ p12, P_ p13, P_ p14, P_ p15, P_ p16, P_ p17, P_ p18, P_ p19, P_ p20,
+P_ p21, P_ p22, P_ p23, P_ p24, P_ p25, P_ p26, P_ p27, P_ p28, P_ p29, P_ p30,
+P_ p31, P_ p32, P_ p33, P_ p34, P_ p35, P_ p36, P_ p37, P_ p38, P_ p39, P_ p40,
+P_ p41, P_ p42, P_ p43, P_ p44, P_ p45, P_ p46, P_ p47, P_ p48, P_ p49, P_ p50,
+P_ p51, P_ p52, P_ p53, P_ p54, P_ p55, P_ p56, P_ p57, P_ p58, P_ p59
+#endif
+)
+ return (/* no return values */)
+{
+ return ();
+}
+
+// Size of this large bitmap closure is: max size of bits in machine word + 1.
+// This results in a two word StgLargeBitmap.
+INFO_TABLE_RET ( test_big_ret_two_words_p, RET_BIG, W_ info_ptr,
+#if SIZEOF_VOID_P == 4
+P_ p1, P_ p2, P_ p3, P_ p4, P_ p5, P_ p6, P_ p7, P_ p8, P_ p9, P_ p10,
+P_ p11, P_ p12, P_ p13, P_ p14, P_ p15, P_ p16, P_ p17, P_ p18, P_ p19, P_ p20,
+P_ p21, P_ p22, P_ p23, P_ p24, P_ p25, P_ p26, P_ p27, P_ p28, P_ p29, P_ p30,
+P_ p31, P_ p32, P_ p33
+#elif SIZEOF_VOID_P == 8
+P_ p1, P_ p2, P_ p3, P_ p4, P_ p5, P_ p6, P_ p7, P_ p8, P_ p9, P_ p10,
+P_ p11, P_ p12, P_ p13, P_ p14, P_ p15, P_ p16, P_ p17, P_ p18, P_ p19, P_ p20,
+P_ p21, P_ p22, P_ p23, P_ p24, P_ p25, P_ p26, P_ p27, P_ p28, P_ p29, P_ p30,
+P_ p31, P_ p32, P_ p33, P_ p34, P_ p35, P_ p36, P_ p37, P_ p38, P_ p39, P_ p40,
+P_ p41, P_ p42, P_ p43, P_ p44, P_ p45, P_ p46, P_ p47, P_ p48, P_ p49, P_ p50,
+P_ p51, P_ p52, P_ p53, P_ p54, P_ p55, P_ p56, P_ p57, P_ p58, P_ p59, P_ p60,
+P_ p61, P_ p62, P_ p63, P_ p64, P_ p65
+#endif
+)
+ return (/* no return values */)
+{
+ return ();
+}
+
+// A BLACKHOLE without any code. Just a placeholder to keep the GC happy.
+INFO_TABLE( test_fake_blackhole, 1, 0, BLACKHOLE, "BLACKHOLE", "BLACKHOLE")
+ (P_ node)
+{
+ return ();
+}
+
+INFO_TABLE_RET ( test_ret_fun, RET_FUN, W_ info_ptr, W_ size, P_ fun, P_ payload)
+ return (/* no return values */)
+{
+ return ();
+}
+
+INFO_TABLE_FUN ( test_arg_n_fun_0_1, 0 , 0, FUN_0_1, "FUN_0_1", "FUN_0_1", 1, ARG_N)
+ return (/* no return values */)
+{
+ return ();
+}
+
+INFO_TABLE_RET( test_ret_bco, RET_BCO)
+ return (/* no return values */)
+{
+ return ();
+}
diff --git a/libraries/ghc-heap/tests/stack_stm_frames.hs b/libraries/ghc-heap/tests/stack_stm_frames.hs
new file mode 100644
index 0000000000..cdead7c7ec
--- /dev/null
+++ b/libraries/ghc-heap/tests/stack_stm_frames.hs
@@ -0,0 +1,38 @@
+{-# LANGUAGE RecordWildCards #-}
+
+module Main where
+
+import Control.Concurrent.STM
+import Control.Exception
+import GHC.Conc
+import GHC.Exts.Heap
+import GHC.Exts.Heap.ClosureTypes
+import GHC.Exts.Heap.Closures
+import GHC.Exts.Heap.InfoTable.Types
+import GHC.Exts.Stack.Decode
+import GHC.Stack.CloneStack
+import TestUtils
+
+main :: IO ()
+main = do
+ (stackSnapshot, decodedStack) <-
+ atomically $
+ catchSTM @SomeException (unsafeIOToSTM getDecodedStack) throwSTM
+
+ assertStackInvariants decodedStack
+ assertThat
+ "Stack contains one catch stm frame"
+ (== 1)
+ (length $ filter isCatchStmFrame decodedStack)
+ assertThat
+ "Stack contains one atomically frame"
+ (== 1)
+ (length $ filter isAtomicallyFrame decodedStack)
+
+isCatchStmFrame :: StackFrame -> Bool
+isCatchStmFrame (CatchStmFrame {..}) = tipe info_tbl == CATCH_STM_FRAME
+isCatchStmFrame _ = False
+
+isAtomicallyFrame :: StackFrame -> Bool
+isAtomicallyFrame (AtomicallyFrame {..}) = tipe info_tbl == ATOMICALLY_FRAME
+isAtomicallyFrame _ = False
diff --git a/libraries/ghc-heap/tests/stack_underflow.hs b/libraries/ghc-heap/tests/stack_underflow.hs
new file mode 100644
index 0000000000..7da5fb1d34
--- /dev/null
+++ b/libraries/ghc-heap/tests/stack_underflow.hs
@@ -0,0 +1,49 @@
+{-# LANGUAGE RecordWildCards #-}
+
+module Main where
+
+import Control.Monad
+import Data.Bool (Bool (True))
+import GHC.Exts.Heap
+import GHC.Exts.Heap.ClosureTypes
+import GHC.Exts.Heap.Closures
+import GHC.Exts.Heap.InfoTable.Types
+import GHC.Exts.Stack.Decode
+import GHC.Stack (HasCallStack)
+import GHC.Stack.CloneStack
+import TestUtils
+
+main = loop 256
+
+{-# NOINLINE loop #-}
+loop 0 = Control.Monad.void getStack
+loop n = print "x" >> loop (n - 1) >> print "x"
+
+getStack :: HasCallStack => IO ()
+getStack = do
+ (s, decodedStack) <- getDecodedStack
+ assertStackInvariants decodedStack
+ assertThat
+ "Stack contains underflow frames"
+ (== True)
+ (any isUnderflowFrame decodedStack)
+ assertStackChunksAreDecodable decodedStack
+ return ()
+
+isUnderflowFrame :: StackFrame -> Bool
+isUnderflowFrame (UnderflowFrame {..}) = tipe info_tbl == UNDERFLOW_FRAME
+isUnderflowFrame _ = False
+
+assertStackChunksAreDecodable :: HasCallStack => [StackFrame] -> IO ()
+assertStackChunksAreDecodable s = do
+ let underflowFrames = filter isUnderflowFrame s
+ assertThat
+ ("Expect some underflow frames. Got " ++ show (length underflowFrames))
+ (>= 2)
+ (length underflowFrames)
+ let stackFrames = map (ssc_stack . nextChunk) underflowFrames
+ assertThat
+ "No empty stack chunks"
+ (== True)
+ ( not (any null stackFrames)
+ )