[Git][ghc/ghc][wip/ghc-debug] Make StgTSO and StgStack decoding downwards compatible

Sven Tennie gitlab at gitlab.haskell.org
Fri May 22 10:50:01 UTC 2020



Sven Tennie pushed to branch wip/ghc-debug at Glasgow Haskell Compiler / GHC


Commits:
76907eaa by Sven Tennie at 2020-05-22T12:49:33+02:00
Make StgTSO and StgStack decoding downwards compatible

This is especially needed for hadrian/ghci.

- - - - -


3 changed files:

- libraries/ghc-heap/GHC/Exts/Heap.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hsc


Changes:

=====================================
libraries/ghc-heap/GHC/Exts/Heap.hs
=====================================
@@ -345,7 +345,9 @@ getClosureX get_closure_raw x = do
                     , stack_dirty = FFIClosures.stack_dirty fields
                     , stackPointer = (pts !! 0)
                     , stack  = FFIClosures.stack fields
+#if __GLASGOW_HASKELL__ >= 811
                     , stack_marking = FFIClosures.stack_marking fields
+#endif
                     }
                 )
         _ ->


=====================================
libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
=====================================
@@ -287,7 +287,9 @@ data GenClosure b
      { info :: !StgInfoTable
      , size :: !Word32 -- ^ stack size in *words*
      , stack_dirty :: !Word8 -- ^ non-zero => dirty
+#if __GLASGOW_HASKELL__ >= 811
      , stack_marking :: Word8
+#endif
      , stackPointer :: !b -- ^ current stack pointer
      , stack :: [Word]
      }


=====================================
libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hsc
=====================================
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
 module GHC.Exts.Heap.FFIClosures where
 
 #include "Rts.h"
@@ -47,7 +48,9 @@ peekTSOFields ptr = do
 data StackFields = StackFields {
     stack_size :: Word32,
     stack_dirty :: Word8,
+#if __GLASGOW_HASKELL__ >= 811
     stack_marking :: Word8,
+#endif
     stack :: [Word]
 }
 
@@ -56,7 +59,9 @@ peekStackFields :: Ptr a -> IO StackFields
 peekStackFields ptr = do
     stack_size' <- (#peek struct StgStack_, stack_size) ptr ::IO Word32
     dirty' <- (#peek struct StgStack_, dirty) ptr
+#if __GLASGOW_HASKELL__ >= 811
     marking' <- (#peek struct StgStack_, marking) ptr
+#endif
 
     let stackPtr = (#ptr struct StgStack_, stack) ptr
     stack' <- peekArray (fromIntegral stack_size') stackPtr
@@ -64,6 +69,8 @@ peekStackFields ptr = do
     return StackFields {
         stack_size = stack_size',
         stack_dirty = dirty',
+#if __GLASGOW_HASKELL__ >= 811
         stack_marking = marking',
+#endif
         stack = stack'
     }



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/76907eaa4eb77c406e952ffb1680030e194e5003
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/20200522/f92e49e4/attachment-0001.html>


More information about the ghc-commits mailing list