[Git][ghc/ghc][wip/decode_cloned_stack] Rely on ghc and not on base version
Sven Tennie (@supersven)
gitlab at gitlab.haskell.org
Sat Jan 14 10:22:48 UTC 2023
Sven Tennie pushed to branch wip/decode_cloned_stack at Glasgow Haskell Compiler / GHC
Commits:
f8ebf0e1 by Sven Tennie at 2023-01-14T10:22:23+00:00
Rely on ghc and not on base version
- - - - -
3 changed files:
- libraries/ghc-heap/GHC/Exts/DecodeStack.hs
- libraries/ghc-heap/GHC/Exts/Heap.hs
- libraries/ghc-heap/GHC/Exts/StackConstants.hsc
Changes:
=====================================
libraries/ghc-heap/GHC/Exts/DecodeStack.hs
=====================================
@@ -1,5 +1,5 @@
{-# LANGUAGE CPP #-}
-#if MIN_VERSION_base(4,17,0)
+#if MIN_TOOL_VERSION_ghc(9,5,0)
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GHCForeignImportPrim #-}
{-# LANGUAGE MagicHash #-}
=====================================
libraries/ghc-heap/GHC/Exts/Heap.hs
=====================================
@@ -74,7 +74,7 @@ import GHC.Exts.DecodeHeap
import GHC.Exts
import GHC.Int
import GHC.Word
-#if MIN_VERSION_base(4,17,0)
+#if MIN_TOOL_VERSION_ghc(9,5,0)
import GHC.Stack.CloneStack
import GHC.Exts.DecodeStack
#endif
@@ -133,7 +133,7 @@ instance Double# ~ a => HasHeapRep (a :: TYPE 'DoubleRep) where
getClosureData x = return $
DoubleClosure { ptipe = PDouble, doubleVal = D# x }
-#if MIN_VERSION_base(4,17,0)
+#if MIN_TOOL_VERSION_ghc(9,5,0)
instance {-# OVERLAPPING #-} HasHeapRep StackSnapshot# where
getClosureData s# = decodeStack (StackSnapshot s#)
#endif
@@ -174,6 +174,6 @@ getClosureDataFromHeapObject x = do
-- | Like 'getClosureData', but taking a 'Box', so it is easier to work with.
getBoxedClosureData :: Box -> IO Closure
getBoxedClosureData (Box a) = getClosureData a
-#if MIN_VERSION_base(4,17,0)
+#if MIN_TOOL_VERSION_ghc(9,5,0)
getBoxedClosureData (DecodedClosureBox a) = pure a
#endif
=====================================
libraries/ghc-heap/GHC/Exts/StackConstants.hsc
=====================================
@@ -2,7 +2,7 @@
module GHC.Exts.StackConstants where
-- TODO: Better expression to allow is only for the latest (this branch) GHC?
-#if MIN_VERSION_base(4,17,0)
+#if MIN_TOOL_VERSION_ghc(9,5,0)
import Prelude
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f8ebf0e1cbd7e1156ac702801773a3b90d0341a8
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f8ebf0e1cbd7e1156ac702801773a3b90d0341a8
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/20230114/3a0918cf/attachment-0001.html>
More information about the ghc-commits
mailing list