[Git][ghc/ghc][wip/decode_cloned_stack] Use ghc version based #if
Sven Tennie (@supersven)
gitlab at gitlab.haskell.org
Sat Feb 4 16:52:43 UTC 2023
Sven Tennie pushed to branch wip/decode_cloned_stack at Glasgow Haskell Compiler / GHC
Commits:
df6421b1 by Sven Tennie at 2023-02-04T16:52:15+00:00
Use ghc version based #if
- - - - -
1 changed file:
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
Changes:
=====================================
libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
=====================================
@@ -24,7 +24,7 @@ module GHC.Exts.Heap.Closures (
, Box(..)
, areBoxesEqual
, asBox
-#if MIN_VERSION_base(4,17,0)
+#if MIN_TOOL_VERSION_ghc(9,5,0)
, SfiKind(..)
, StackFrameIter(..)
#endif
@@ -54,7 +54,7 @@ import GHC.Exts
import GHC.Generics
import Numeric
-#if MIN_VERSION_base(4,17,0)
+#if MIN_TOOL_VERSION_ghc(9,5,0)
import GHC.Stack.CloneStack (StackSnapshot(..))
import GHC.Exts.StackConstants
import Unsafe.Coerce (unsafeCoerce)
@@ -69,16 +69,11 @@ foreign import prim "aToWordzh" aToWord# :: Any -> Word#
foreign import prim "reallyUnsafePtrEqualityUpToTag"
reallyUnsafePtrEqualityUpToTag# :: Any -> Any -> Int#
-#if MIN_VERSION_base(4,17,0)
+#if MIN_TOOL_VERSION_ghc(9,5,0)
foreign import prim "stackSnapshotToWordzh" stackSnapshotToWord# :: StackSnapshot# -> Word#
foreign import prim "eqStackSnapshotszh" eqStackSnapshots# :: StackSnapshot# -> StackSnapshot# -> Word#
-#endif
--- | An arbitrary Haskell value in a safe Box. The point is that even
--- unevaluated thunks can safely be moved around inside the Box, and when
--- required, e.g. in 'getBoxedClosureData', the function knows how far it has
--- to evaluate the argument.
-#if MIN_VERSION_base(4,17,0)
+
data SfiKind = SfiClosure | SfiPrimitive | SfiStack
deriving (Eq, Show)
@@ -104,8 +99,25 @@ instance Show StackSnapshot where
addr = W# (stackSnapshotToWord# s#)
pad_out ls = '0':'x':ls
-data Box = Box Any | StackFrameBox StackFrameIter
+-- | An arbitrary Haskell value in a safe Box.
+--
+-- The point is that even unevaluated thunks can safely be moved around inside
+-- the Box, and when required, e.g. in 'getBoxedClosureData', the function knows
+-- how far it has to evaluate the argument.
+--
+-- `Box`es can be used to increase (and enforce) laziness: In a graph of
+-- closures they can act as a barrier of evaluation. `Closure` is an example for
+-- this.
+data Box =
+ -- | A heap located closure.
+ Box Any
+ -- | A value or reference to a value on the stack.
+ | StackFrameBox StackFrameIter
#else
+-- | An arbitrary Haskell value in a safe Box. The point is that even
+-- unevaluated thunks can safely be moved around inside the Box, and when
+-- required, e.g. in 'getBoxedClosureData', the function knows how far it has
+-- to evaluate the argument.
data Box = Box Any
#endif
@@ -120,7 +132,7 @@ instance Show Box where
tag = ptr .&. fromIntegral tAG_MASK -- ((1 `shiftL` TAG_BITS) -1)
addr = ptr - tag
pad_out ls = '0':'x':ls
-#if MIN_VERSION_base(4,17,0)
+#if MIN_TOOL_VERSION_ghc(9,5,0)
showsPrec _ (StackFrameBox sfi) rs =
-- TODO: Record syntax could be nicer to read
"(StackFrameBox StackFrameIter(" ++ show sfi ++ ")" ++ rs
@@ -133,7 +145,7 @@ areBoxesEqual :: Box -> Box -> IO Bool
areBoxesEqual (Box a) (Box b) = case reallyUnsafePtrEqualityUpToTag# a b of
0# -> pure False
_ -> pure True
-#if MIN_VERSION_base(4,17,0)
+#if MIN_TOOL_VERSION_ghc(9,5,0)
-- TODO: Could be used for `instance Eq StackFrameIter`
areBoxesEqual
(StackFrameBox (StackFrameIter s1# i1 p1))
@@ -635,4 +647,3 @@ allClosures (RetFun {..}) = retFunFun : retFunPayload
allClosures (RetBCO {..}) = bco : bcoArgs
#endif
allClosures _ = []
-
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/df6421b1079ef20551a5b3fff4a719a1309dd32b
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/df6421b1079ef20551a5b3fff4a719a1309dd32b
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/20230204/2542dd6d/attachment-0001.html>
More information about the ghc-commits
mailing list