[Git][ghc/ghc][wip/decode_cloned_stack] 3 commits: Smaller diff

Sven Tennie (@supersven) gitlab at gitlab.haskell.org
Sat Apr 1 08:23:24 UTC 2023



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


Commits:
976a17b4 by Sven Tennie at 2023-03-31T13:42:06+00:00
Smaller diff

- - - - -
2ebcbc40 by Sven Tennie at 2023-03-31T13:48:04+00:00
Add comment

- - - - -
dee3ad94 by Sven Tennie at 2023-04-01T08:23:02+00:00
Add comment

- - - - -


1 changed file:

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


Changes:

=====================================
libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
=====================================
@@ -77,13 +77,6 @@ instance Show Box where
        addr = ptr - tag
        pad_out ls = '0':'x':ls
 
--- | Boxes can be compared, but this is not pure, as different heap objects can,
--- after garbage collection, become the same object.
-areBoxesEqual :: Box -> Box -> IO Bool
-areBoxesEqual (Box a) (Box b) = case reallyUnsafePtrEqualityUpToTag# a b of
-    0# -> pure False
-    _  -> pure True
-
 -- |This takes an arbitrary value and puts it into a box.
 -- Note that calls like
 --
@@ -96,6 +89,14 @@ areBoxesEqual (Box a) (Box b) = case reallyUnsafePtrEqualityUpToTag# a b of
 asBox :: a -> Box
 asBox x = Box (unsafeCoerce# x)
 
+-- | Boxes can be compared, but this is not pure, as different heap objects can,
+-- after garbage collection, become the same object.
+areBoxesEqual :: Box -> Box -> IO Bool
+areBoxesEqual (Box a) (Box b) = case reallyUnsafePtrEqualityUpToTag# a b of
+    0# -> pure False
+    _  -> pure True
+
+
 ------------------------------------------------------------------------
 -- Closures
 type Closure = GenClosure Box
@@ -357,6 +358,10 @@ data GenClosure b
         { info       :: !StgInfoTable
         }
 
+    -- | A primitive word from a bitmap encoded stack frame payload
+    --
+    -- The type itself cannot be restored (i.e. it might also represent a byte
+    -- or an int).
   |  UnknownTypeWordSizedPrimitive
         { wordVal :: !Word }
   deriving (Show, Generic, Functor, Foldable, Traversable)
@@ -446,6 +451,8 @@ data StackFrame =
       }
   deriving (Show, Generic)
 
+-- | Fun types according to @FunTypes.h@
+-- This `Enum` must be aligned with the values in @FunTypes.h at .
 data RetFunType =
       ARG_GEN     |
       ARG_GEN_BIG |
@@ -545,5 +552,4 @@ allClosures (FunClosure {..}) = ptrArgs
 allClosures (BlockingQueueClosure {..}) = [link, blackHole, owner, queue]
 allClosures (WeakClosure {..}) = [cfinalizers, key, value, finalizer] ++ Data.Foldable.toList weakLink
 allClosures (OtherClosure {..}) = hvalues
-allClosures (StackClosure {}) = []
 allClosures _ = []



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1f07b2836603e11324171cc0b37b9b52423aca4f...dee3ad94ebb5572a5a110d804afbcfcb453cfb12

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1f07b2836603e11324171cc0b37b9b52423aca4f...dee3ad94ebb5572a5a110d804afbcfcb453cfb12
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/20230401/81cbf54b/attachment-0001.html>


More information about the ghc-commits mailing list