[Git][ghc/ghc][wip/gc/refactor-mark-thread] 2 commits: testsuite: Skip T23221 in nonmoving GC ways
Ben Gamari (@bgamari)
gitlab at gitlab.haskell.org
Tue Aug 15 04:49:41 UTC 2023
Ben Gamari pushed to branch wip/gc/refactor-mark-thread at Glasgow Haskell Compiler / GHC
Commits:
ff073e15 by Ben Gamari at 2023-08-15T00:49:34-04:00
testsuite: Skip T23221 in nonmoving GC ways
This test is very dependent upon GC behavior.
- - - - -
049d5483 by Ben Gamari at 2023-08-15T00:49:34-04:00
ghc-heap: Don't expose stack dirty and marking fields
These are GC metadata and are not relevant to the end-user. Moreover,
they are unstable which makes ghc-heap harder to test than necessary.
- - - - -
5 changed files:
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/Stack/Decode.hs
- libraries/ghc-heap/cbits/Stack.cmm
- libraries/ghc-heap/tests/stack_misc_closures.hs
- testsuite/tests/rts/all.T
Changes:
=====================================
libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
=====================================
@@ -387,8 +387,6 @@ type StgStackClosure = GenStgStackClosure Box
data GenStgStackClosure b = GenStgStackClosure
{ ssc_info :: !StgInfoTable
, ssc_stack_size :: !Word32 -- ^ stack size in *words*
- , ssc_stack_dirty :: !Word8 -- ^ non-zero => dirty
- , ssc_stack_marking :: !Word8
, ssc_stack :: ![GenStackFrame b]
}
deriving (Foldable, Functor, Generic, Show, Traversable)
=====================================
libraries/ghc-heap/GHC/Exts/Stack/Decode.hs
=====================================
@@ -170,13 +170,12 @@ foreign import prim "getStackClosurezh"
foreign import prim "getStackFieldszh"
getStackFields# ::
- StackSnapshot# -> (# Word32#, Word8#, Word8# #)
+ StackSnapshot# -> Word32#
-getStackFields :: StackSnapshot# -> (Word32, Word8, Word8)
+getStackFields :: StackSnapshot# -> Word32
getStackFields stackSnapshot# =
case getStackFields# stackSnapshot# of
- (# sSize#, sDirty#, sMarking# #) ->
- (W32# sSize#, W8# sDirty#, W8# sMarking#)
+ (# sSize# #) -> W32# sSize#
-- | `StackFrameLocation` of the top-most stack frame
stackHead :: StackSnapshot# -> StackFrameLocation
@@ -409,15 +408,13 @@ decodeStack (StackSnapshot stack#) = do
info <- getInfoTableForStack stack#
case tipe info of
STACK -> do
- let (stack_size', stack_dirty', stack_marking') = getStackFields stack#
+ let stack_size' = getStackFields stack#
sfls = stackFrameLocations stack#
stack' <- mapM unpackStackFrame sfls
pure $
GenStgStackClosure
{ ssc_info = info,
ssc_stack_size = stack_size',
- ssc_stack_dirty = stack_dirty',
- ssc_stack_marking = stack_marking',
ssc_stack = stack'
}
_ -> error $ "Expected STACK closure, got " ++ show info
=====================================
libraries/ghc-heap/cbits/Stack.cmm
=====================================
@@ -173,15 +173,10 @@ getStackClosurezh(P_ stack, W_ offsetWords) {
return (closure);
}
-// (bits32, bits8, bits8) getStackFieldszh(StgStack* stack)
+// (bits32) getStackFieldszh(StgStack* stack)
getStackFieldszh(P_ stack){
bits32 size;
- bits8 dirty, marking;
-
size = StgStack_stack_size(stack);
- dirty = StgStack_dirty(stack);
- marking = StgStack_marking(stack);
-
- return (size, dirty, marking);
+ return (size);
}
#endif
=====================================
libraries/ghc-heap/tests/stack_misc_closures.hs
=====================================
@@ -308,8 +308,6 @@ main = 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 {..} ->
=====================================
testsuite/tests/rts/all.T
=====================================
@@ -589,7 +589,16 @@ test('T22795c', [only_ways(['normal']), js_skip], compile_and_run, ['-threaded -
test('T17574', [js_skip], compile_and_run, ['-with-rtsopts -T'])
-test('T23221', [js_skip, high_memory_usage, extra_run_opts('1500000'), unless(wordsize(64), skip), omit_ghci], compile_and_run, ['-O -with-rtsopts -T'])
+test('T23221',
+ [js_skip,
+ # This test is highly dependent upon GC behavior
+ skip_ways(['nonmoving', 'nonmoving_thr', 'nonmoving_thr_sanity', 'nonmoving_thr_ghc']),
+ high_memory_usage,
+ extra_run_opts('1500000'),
+ unless(wordsize(64), skip),
+ omit_ghci],
+ compile_and_run,
+ ['-O -with-rtsopts -T'])
test('T23142', [unless(debug_rts(), skip), req_interp], makefile_test, ['T23142'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/92aa06a33b4c66035aba2232aaa186410878d299...049d5483c1e4e174ca3f1572b686e227caf9d6c8
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/92aa06a33b4c66035aba2232aaa186410878d299...049d5483c1e4e174ca3f1572b686e227caf9d6c8
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/20230815/786928ab/attachment-0001.html>
More information about the ghc-commits
mailing list