[Git][ghc/ghc][wip/torsten.schmits/parallel-depanal-downsweep] 2 commits: Make addToFinderCache monotonic
Sjoerd Visscher (@trac-sjoerd_visscher)
gitlab at gitlab.haskell.org
Thu Aug 29 15:00:39 UTC 2024
Sjoerd Visscher pushed to branch wip/torsten.schmits/parallel-depanal-downsweep at Glasgow Haskell Compiler / GHC
Commits:
d3ee9c49 by Sjoerd Visscher at 2024-08-29T17:00:27+02:00
Make addToFinderCache monotonic
- - - - -
04a3a9e6 by Sjoerd Visscher at 2024-08-29T17:00:28+02:00
Fix tests that call downsweep
- - - - -
3 changed files:
- compiler/GHC/Unit/Finder.hs
- testsuite/tests/ghc-api/downsweep/OldModLocation.hs
- testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs
Changes:
=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -104,9 +104,29 @@ flushFinderCaches (FinderCache ref file_ref) ue = do
where
is_ext mod _ = not (isUnitEnvInstalledModule ue mod)
+{-
+[Note: Monotonic addToFinderCache]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+addToFinderCache is only used by functions that return the cached value
+if there is one, or by functions that always write an InstalledFound value.
+Without multithreading it is then safe to always directly write the value
+without checking the previously cached value.
+
+However, with multithreading, it is possible that another function has
+written a value into cache between the lookup and the addToFinderCache call.
+in this case we should check to not overwrite an InstalledFound with an
+InstalledNotFound.
+-}
+
addToFinderCache :: FinderCache -> InstalledModule -> InstalledFindResult -> IO ()
addToFinderCache (FinderCache ref _) key val =
- atomicModifyIORef' ref $ \c -> (extendInstalledModuleEnv c key val, ())
+ atomicModifyIORef' ref $ \c ->
+ case (lookupInstalledModuleEnv c key, val) of
+ -- Don't overwrite an InstalledFound with an InstalledNotFound
+ -- See [Note Monotonic addToFinderCache]
+ (Just InstalledFound{}, InstalledNotFound{}) -> (c, ())
+ _ -> (extendInstalledModuleEnv c key val, ())
removeFromFinderCache :: FinderCache -> InstalledModule -> IO ()
removeFromFinderCache (FinderCache ref _) key =
=====================================
testsuite/tests/ghc-api/downsweep/OldModLocation.hs
=====================================
@@ -6,6 +6,7 @@ import GHC
import GHC.Driver.Make
import GHC.Driver.Session
import GHC.Driver.Env
+import GHC.Types.Error (mkUnknownDiagnostic)
import GHC.Unit.Module.Graph
import GHC.Unit.Finder
@@ -47,13 +48,13 @@ main = do
liftIO $ do
- _emss <- downsweep hsc_env [] [] False
+ _emss <- downsweep hsc_env mkUnknownDiagnostic Nothing [] [] False
flushFinderCaches (hsc_FC hsc_env) (hsc_unit_env hsc_env)
createDirectoryIfMissing False "mydir"
renameFile "B.hs" "mydir/B.hs"
- (_, nodes) <- downsweep hsc_env [] [] False
+ (_, nodes) <- downsweep hsc_env mkUnknownDiagnostic Nothing [] [] False
-- If 'checkSummaryTimestamp' were to call 'addHomeModuleToFinder' with
-- (ms_location old_summary) like summariseFile used to instead of
=====================================
testsuite/tests/ghc-api/downsweep/PartialDownsweep.hs
=====================================
@@ -6,6 +6,7 @@
import GHC
import GHC.Driver.Make
import GHC.Driver.Session
+import GHC.Types.Error (mkUnknownDiagnostic)
import GHC.Utils.Outputable
import GHC.Utils.Exception (ExceptionMonad)
import GHC.Data.Bag
@@ -168,7 +169,7 @@ go label mods cnd =
setTargets [tgt]
hsc_env <- getSession
- (_, nodes) <- liftIO $ downsweep hsc_env [] [] False
+ (_, nodes) <- liftIO $ downsweep hsc_env mkUnknownDiagnostic Nothing [] [] False
it label $ cnd (mapMaybe moduleGraphNodeModSum nodes)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7dff0159f196ad7d5ac8f188d79f148b0d80676a...04a3a9e61d0cc14865b445af3220d93e15a1e29f
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7dff0159f196ad7d5ac8f188d79f148b0d80676a...04a3a9e61d0cc14865b445af3220d93e15a1e29f
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/20240829/7b897d95/attachment-0001.html>
More information about the ghc-commits
mailing list