[Git][ghc/ghc][wip/ghc-debug] Remove stack_spOffset and test for TSO closure flags

David Eichmann gitlab at gitlab.haskell.org
Tue Oct 13 10:49:24 UTC 2020



David Eichmann pushed to branch wip/ghc-debug at Glasgow Haskell Compiler / GHC


Commits:
6e6bde03 by David Eichmann at 2020-10-13T11:47:58+01:00
Remove stack_spOffset and test for TSO closure flags

- - - - -


3 changed files:

- libraries/ghc-heap/GHC/Exts/Heap.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- libraries/ghc-heap/tests/tso_and_stack_closures.hs


Changes:

=====================================
libraries/ghc-heap/GHC/Exts/Heap.hs
=====================================
@@ -381,8 +381,6 @@ getClosureDataFromHeapRep closureAddressMay heapRep infoTablePtr pts = do
                 Nothing -> pure $ UnsupportedClosure itbl
                 Just (Ptr closureAddress) ->  withArray rawHeapWords (\ptr -> do
                             fields <- FFIClosures.peekStackFields ptr
-                            let sp = FFIClosures.stack_sp fields
-                                spOffset = I# (minusAddr# sp closureAddress)
                             pure $ StackClosure
                                 { info = itbl
                                 , stack_size = FFIClosures.stack_size fields
@@ -390,7 +388,6 @@ getClosureDataFromHeapRep closureAddressMay heapRep infoTablePtr pts = do
 #if __GLASGOW_HASKELL__ >= 811
                                 , stack_marking = FFIClosures.stack_marking fields
 #endif
-                                , stack_spOffset = spOffset
                                 })
             | otherwise
                 -> fail $ "Expected 0 ptr argument to STACK, found "


=====================================
libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
=====================================
@@ -318,11 +318,6 @@ data GenClosure b
 #if __GLASGOW_HASKELL__ >= 810
       , stack_marking   :: !Word8
 #endif
-      -- | Offset of the `StgStack::sp` pointer in *bytes*:
-      --
-      --    stgStack->sp == ((byte*)stgStack)+stack_spOffset
-      --
-      , stack_spOffset  :: !Int
       }
 
     ------------------------------------------------------------


=====================================
libraries/ghc-heap/tests/tso_and_stack_closures.hs
=====================================
@@ -22,10 +22,20 @@ main :: IO ()
 main = do
     (tso, stack) <- {-# SCC "MyCostCentre" #-} createAndUnpackTSOAndSTACKClosure
     assertEqual (getClosureType tso) TSO
-    assertEqual (getClosureType stack) STACK
     assertEqual (what_next tso) ThreadRunGHC
     assertEqual (why_blocked tso) NotBlocked
     assertEqual (saved_errno tso) 0
+    forM_ (flags tso) $ \flag -> case flag of
+        TsoFlagsUnknownValue _ -> error $ "Unknown flag: " ++ show flag
+        _ | flag `elem`
+            [ TsoLocked
+            , TsoBlockx
+            , TsoStoppedOnBreakpoint
+            , TsoSqueezed
+            ] -> error $ "Unexpected flag: " ++ show flag
+        _ -> return ()
+
+    assertEqual (getClosureType stack) STACK
 
 #if defined(PROFILING)
     let costCentre = ccs_cc <$> (cccs =<< prof tso)
@@ -71,7 +81,10 @@ foreign import ccall safe "create_tso.h create_and_unpack_tso_and_stack"
         -> Ptr (Ptr (Ptr Any))
         -> IO ()
 
-createAndUnpackTSOAndSTACKClosure :: IO (GenClosure (Ptr Any), GenClosure (Ptr Any))
+createAndUnpackTSOAndSTACKClosure
+    :: IO ( GenClosure (Ptr Any)
+          , GenClosure (Ptr Any)
+          )
 createAndUnpackTSOAndSTACKClosure = do
 
     alloca $ \ptrPtrTso -> do



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6e6bde0352bbb73c0d3d81b689f388b6b5dc07c4
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/20201013/65c434e3/attachment-0001.html>


More information about the ghc-commits mailing list