[Git][ghc/ghc][wip/decode_cloned_stack] Solve GetClosure issue with error
Sven Tennie (@supersven)
gitlab at gitlab.haskell.org
Sun Feb 26 16:46:08 UTC 2023
Sven Tennie pushed to branch wip/decode_cloned_stack at Glasgow Haskell Compiler / GHC
Commits:
ba5114af by Sven Tennie at 2023-02-26T16:44:50+00:00
Solve GetClosure issue with error
- - - - -
4 changed files:
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- − testsuite/tests/ghci/should_run/BinaryStackSnapshot.hs
- testsuite/tests/ghci/should_run/all.T
Changes:
=====================================
libraries/ghci/GHCi/Message.hs
=====================================
@@ -1,6 +1,6 @@
{-# LANGUAGE GADTs, DeriveGeneric, StandaloneDeriving, ScopedTypeVariables,
GeneralizedNewtypeDeriving, ExistentialQuantification, RecordWildCards,
- CPP, MagicHash, TypeApplications #-}
+ CPP #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-orphans #-}
-- |
@@ -53,11 +53,7 @@ import qualified Language.Haskell.TH.Syntax as TH
import System.Exit
import System.IO
import System.IO.Error
-#if MIN_VERSION_base(4,17,0)
-import GHC.Stack.CloneStack
-import GHC.Word (Word(W#))
-import GHC.Exts (Word#, unsafeCoerce#, StackSnapshot#)
-#endif
+
-- -----------------------------------------------------------------------------
-- The RPC protocol between GHC and the interactive server
@@ -477,15 +473,6 @@ instance Binary Heap.TsoFlags
#if MIN_VERSION_base(4,17,0)
instance Binary Heap.RetFunType
-
-instance Binary StackSnapshot where
- get = do
- v <- get @Word
- pure $ StackSnapshot (toPrim v)
- where
- toPrim :: Word -> StackSnapshot#
- toPrim (W# w#) = unsafeCoerce# w#
- put (StackSnapshot s#) = put (W# ((unsafeCoerce# s#) :: Word#))
#endif
instance Binary Heap.StgInfoTable
=====================================
libraries/ghci/GHCi/Run.hs
=====================================
@@ -96,8 +96,7 @@ run m = case m of
clos <- Heap.getClosureData =<< localRef ref
mapM (\case
Heap.Box x -> mkRemoteRef (HValue x)
- -- TODO: Is this unsafeCoerce really necessary?
- Heap.StackFrameBox d -> mkRemoteRef (HValue (unsafeCoerce d))
+ r -> error $ "Unsupported Box: " ++ show r
) clos
Seq ref -> doSeq ref
ResumeSeq ref -> resumeSeq ref
=====================================
testsuite/tests/ghci/should_run/BinaryStackSnapshot.hs deleted
=====================================
@@ -1,19 +0,0 @@
-module Main where
-
-import Data.Binary
-import GHC.Stack.CloneStack (cloneMyStack)
-import GHCi.Message ()
-
-main :: IO ()
-main = do
- stack <- cloneMyStack
- let stack' = (decode . encode) stack
-
- if stack == stack'
- then pure ()
- else
- error $
- "Encoding/decoding roundtrip went wrong! stack "
- ++ show stack
- ++ ", stack' "
- ++ show stack'
=====================================
testsuite/tests/ghci/should_run/all.T
=====================================
@@ -34,7 +34,6 @@ test('T12525', just_ghci, ghci_script, ['T12525.script'])
test('T12549', just_ghci, ghci_script, ['T12549.script'])
test('T13456', [just_ghci, combined_output], ghci_script, ['T13456.script'])
test('BinaryArray', normal, compile_and_run, [''])
-test('BinaryStackSnapshot', normal, compile_and_run, [''])
test('T14125a', just_ghci, ghci_script, ['T14125a.script'])
test('T13825-ghci',just_ghci, ghci_script, ['T13825-ghci.script'])
test('T14608', just_ghci, ghci_script, ['T14608.script'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ba5114af67821b50b4404d601824d34030959326
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ba5114af67821b50b4404d601824d34030959326
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/20230226/85266240/attachment-0001.html>
More information about the ghc-commits
mailing list