[Git][ghc/ghc][wip/romes/rts-linker-direct-symbol-lookup] 4 commits: Use IORef instead of MVar for symbol cache

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Mon Mar 25 11:09:20 UTC 2024



Rodrigo Mesquita pushed to branch wip/romes/rts-linker-direct-symbol-lookup at Glasgow Haskell Compiler / GHC


Commits:
a04c1215 by Rodrigo Mesquita at 2024-03-25T10:43:43+00:00
Use IORef instead of MVar for symbol cache

- - - - -
4f780458 by Rodrigo Mesquita at 2024-03-25T10:43:47+00:00
Revert "Use IORef instead of MVar for symbol cache"

This reverts commit a04c121534b41850f248edfabf62727ed9e38305.

- - - - -
cadad5fe by Rodrigo Mesquita at 2024-03-25T11:01:59+00:00
Reapply "Use IORef instead of MVar for symbol cache"

This reverts commit 4f78045848b742654a420f4a488aae749002e215.

- - - - -
20d8dcdf by Rodrigo Mesquita at 2024-03-25T11:09:12+00:00
Improve debug message

- - - - -


4 changed files:

- compiler/GHC.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/Types.hs


Changes:

=====================================
compiler/GHC.hs
=====================================
@@ -674,7 +674,7 @@ setTopSessionDynFlags :: GhcMonad m => DynFlags -> m ()
 setTopSessionDynFlags dflags = do
   hsc_env <- getSession
   logger  <- getLogger
-  lookup_cache  <- liftIO $ newMVar emptyUFM
+  lookup_cache  <- liftIO $ newIORef emptyUFM
 
   -- Interpreter
   interp <- if


=====================================
compiler/GHC/ByteCode/Linker.hs
=====================================
@@ -180,7 +180,7 @@ lookupHsSymbol interp pkgs_loaded nm sym_suffix = do
         case mb_ptr of
           Just ptr -> pure (Just ptr)
           Nothing -> go dlls
-      go [] = panic "lookupHsSymbol: symbol not found in the loaded_dlls associated with this pkg_id"
+      go [] = panic "lookupHsSymbol: symbol " ++ show (ppr nm) ++ " not found in the loaded_dlls associated with this pkg_id (" ++ show (ppr pkgs_loaded) ++ ")"
 
   go loaded_dlls
 


=====================================
compiler/GHC/Runtime/Interpreter.hs
=====================================
@@ -491,7 +491,7 @@ withSymbolCache interp str determine_addr = do
   -- The analysis in #23415 further showed this cache should also benefit the
   -- internal interpreter's loading times, and needn't be used by the external
   -- interpreter only.
-  cache <- readMVar (interpLookupSymbolCache interp)
+  cache <- readIORef (interpLookupSymbolCache interp)
   case lookupUFM cache str of
     Just p -> return (Just p)
     Nothing -> do
@@ -500,12 +500,12 @@ withSymbolCache interp str determine_addr = do
       case maddr of
         Nothing -> return Nothing
         Just p -> do
-          let cache' = addToUFM cache str p
-          modifyMVar_ (interpLookupSymbolCache interp) (const (pure cache'))
+          let upd_cache cache' = addToUFM cache' str p
+          _ <- atomicModifyIORef (interpLookupSymbolCache interp) (pure . upd_cache)
           return (Just p)
 
 purgeLookupSymbolCache :: Interp -> IO ()
-purgeLookupSymbolCache interp = modifyMVar_ (interpLookupSymbolCache interp) (const (pure emptyUFM))
+purgeLookupSymbolCache interp = atomicWriteIORef (interpLookupSymbolCache interp) emptyUFM
 
 -- | loadDLL loads a dynamic library using the OS's native linker
 -- (i.e. dlopen() on Unix, LoadLibrary() on Windows).  It takes either


=====================================
compiler/GHC/Runtime/Interpreter/Types.hs
=====================================
@@ -40,6 +40,7 @@ import GHC.StgToJS.Types
 import GHC.StgToJS.Linker.Types
 
 import Control.Concurrent
+import Data.IORef
 import System.Process   ( ProcessHandle, CreateProcess )
 import System.IO
 import GHC.Unit.Finder.Types (FinderCache, FinderOpts)
@@ -52,7 +53,7 @@ data Interp = Interp
   , interpLoader   :: !Loader
       -- ^ Interpreter loader
 
-  , interpLookupSymbolCache :: !(MVar (UniqFM FastString (Ptr ())))
+  , interpLookupSymbolCache :: !(IORef (UniqFM FastString (Ptr ())))
       -- ^ LookupSymbol cache
   }
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/10ad50a248b98dc0e1f9a2973564492d0f0db292...20d8dcdf53b6fe31ec5e58bd5574f0b4818d7f04

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/10ad50a248b98dc0e1f9a2973564492d0f0db292...20d8dcdf53b6fe31ec5e58bd5574f0b4818d7f04
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/20240325/a1eec7ee/attachment-0001.html>


More information about the ghc-commits mailing list