[Git][ghc/ghc][wip/T22010] 2 commits: Make GHCi work with 64-bit uniques

Jaro Reinders (@Noughtmare) gitlab at gitlab.haskell.org
Mon Jun 5 12:26:22 UTC 2023



Jaro Reinders pushed to branch wip/T22010 at Glasgow Haskell Compiler / GHC


Commits:
c962ef3b by Jaro Reinders at 2023-06-05T14:17:37+02:00
Make GHCi work with 64-bit uniques

- - - - -
4cea7411 by Jaro Reinders at 2023-06-05T14:26:10+02:00
Remove unused top-level bindings and fix linter errors

- - - - -


3 changed files:

- compiler/GHC/CmmToAsm/CFG/Dominators.hs
- libraries/ghci/GHCi/Run.hs
- testsuite/tests/linters/notes.stdout


Changes:

=====================================
compiler/GHC/CmmToAsm/CFG/Dominators.hs
=====================================
@@ -131,7 +131,6 @@ rpddfs = concat . levels . pdomTree
 -----------------------------------------------------------------------------
 
 type Dom s a = S s (Env s) a
-type NodeSet    = IntSet
 type NodeMap a  = Word64Map a
 data Env s = Env
   {succE      :: !Graph
@@ -511,13 +510,6 @@ reachable f a = go (WS.singleton a) a
                         as = WS.toList (s `WS.difference` seen)
                     in foldl' go (s `WS.union` seen) as
 
-collectI :: (c -> c -> c)
-        -> (a -> Int) -> (a -> c) -> [a] -> IntMap c
-collectI (<>) f g
-  = foldl' (\m a -> IM.insertWith (<>)
-                                  (f a)
-                                  (g a) m) mempty
-
 collectW :: (c -> c -> c)
         -> (a -> Word64) -> (a -> c) -> [a] -> Word64Map c
 collectW (<>) f g


=====================================
libraries/ghci/GHCi/Run.hs
=====================================
@@ -40,6 +40,7 @@ import GHC.Conc.Sync
 import GHC.IO hiding ( bracket )
 import System.Mem.Weak  ( deRefWeak )
 import Unsafe.Coerce
+import GHC.Word
 
 -- -----------------------------------------------------------------------------
 -- Implement messages
@@ -293,7 +294,11 @@ withBreakAction opts breakMVar statusMVar act
      resume_r <- mkRemoteRef resume
      apStack_r <- mkRemoteRef apStack
      ccs <- toRemotePtr <$> getCCSOf apStack
-     putMVar statusMVar $ EvalBreak is_exception apStack_r (I# ix#) (undefined uniq#) resume_r ccs
+#if !MIN_VERSION_GLASGOW_HASKELL(9,3,0,0) || WORD_SIZE_IN_BITS < 64
+     putMVar statusMVar $ EvalBreak is_exception apStack_r (I# ix#) (W64# uniq#) resume_r ccs
+#else
+     putMVar statusMVar $ EvalBreak is_exception apStack_r (I# ix#) (W64# (word64ToWord# uniq#)) resume_r ccs
+#endif
      takeMVar breakMVar
 
    resetBreakAction stablePtr = do
@@ -342,7 +347,7 @@ resetStepFlag = poke stepFlag 0
 
 type BreakpointCallback
      = Int#    -- the breakpoint index
-    -> Int#    -- the module uniq
+    -> Word64# -- the module uniq
     -> Bool    -- exception?
     -> HValue  -- the AP_STACK, or exception
     -> IO ()


=====================================
testsuite/tests/linters/notes.stdout
=====================================
@@ -6,6 +6,8 @@ ref    compiler/GHC/Core/Opt/Simplify/Iteration.hs:4018:8:     Note [Lambda-boun
 ref    compiler/GHC/Core/Opt/Simplify/Utils.hs:1343:37:     Note [Gentle mode]
 ref    compiler/GHC/Core/Opt/Specialise.hs:1765:29:     Note [Arity decrease]
 ref    compiler/GHC/Core/TyCo/Rep.hs:1565:31:     Note [What prevents a constraint from floating]
+ref    compiler/GHC/Data/Word64Map/Internal.hs:330:7:     Note [ Template Haskell Dependencies ]
+ref    compiler/GHC/Data/Word64Set/Internal.hs:226:7:     Note [ Template Haskell Dependencies ]
 ref    compiler/GHC/Driver/DynFlags.hs:1245:49:     Note [Eta-reduction in -O0]
 ref    compiler/GHC/Driver/Main.hs:1762:34:     Note [simpleTidyPgm - mkBootModDetailsTc]
 ref    compiler/GHC/Hs/Expr.hs:194:63:     Note [Pending Splices]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/221eef2810fc94715f6716d8293c7af4f8062f09...4cea741119d81b8d4b43e4dfb8344a8c13cb26ab

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/221eef2810fc94715f6716d8293c7af4f8062f09...4cea741119d81b8d4b43e4dfb8344a8c13cb26ab
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/20230605/9dd9f18e/attachment-0001.html>


More information about the ghc-commits mailing list