[commit: ghc] wip/nfs-locking: Get rid of gmpLibNameCache. (d4b6ee5)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:01:36 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/nfs-locking
Link       : http://ghc.haskell.org/trac/ghc/changeset/d4b6ee52c1d31c19e71ce4b70f65618d5222dfdd/ghc

>---------------------------------------------------------------

commit d4b6ee52c1d31c19e71ce4b70f65618d5222dfdd
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Wed Feb 10 23:40:49 2016 +0000

    Get rid of gmpLibNameCache.
    
    Fix #206.


>---------------------------------------------------------------

d4b6ee52c1d31c19e71ce4b70f65618d5222dfdd
 src/Rules/Gmp.hs             | 17 +++++------------
 src/Settings/Builders/Ghc.hs | 10 +++++-----
 src/Settings/Paths.hs        |  8 ++------
 3 files changed, 12 insertions(+), 23 deletions(-)

diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs
index ab25495..3e1acea 100644
--- a/src/Rules/Gmp.hs
+++ b/src/Rules/Gmp.hs
@@ -7,7 +7,6 @@ import Expression
 import GHC
 import Oracles.Config.Setting
 import Rules.Actions
-import Settings.Builders.Ghc
 import Settings.Packages.IntegerGmp
 import Settings.User
 
@@ -67,7 +66,7 @@ gmpRules :: Rules ()
 gmpRules = do
 
     -- TODO: split into multiple rules
-    [gmpLibraryH, gmpLibNameCache] &%> \_ -> do
+    gmpLibraryH %> \_ -> do
         when trackBuildSystem $ need [sourcePath -/- "Rules/Gmp.hs"]
 
         liftIO $ removeFiles gmpBuildPath ["//*"]
@@ -83,22 +82,16 @@ gmpRules = do
 
         createDirectory $ takeDirectory gmpLibraryH
         -- We don't use system GMP on Windows. TODO: fix?
-        -- TODO: we do not track "config.mk" and "integer-gmp.buildinfo", see #173
-        windows <- windowsHost
+        -- TODO: we don't track "config.mk" & "integer-gmp.buildinfo", see #173
+        windows  <- windowsHost
         configMk <- liftIO . readFile $ gmpBase -/- "config.mk"
-        if not windows && any (`isInfixOf` configMk) [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ]
+        if not windows && any (`isInfixOf` configMk)
+            [ "HaveFrameworkGMP = YES", "HaveLibGmp = YES" ]
         then do
             putBuild "| GMP library/framework detected and will be used"
             copyFile gmpLibraryFakeH gmpLibraryH
-            buildInfo <- liftIO . readFile $ pkgPath integerGmp -/- "integer-gmp.buildinfo"
-            let prefix = "extra-libraries: "
-                libs s = case stripPrefix prefix s of
-                    Nothing    -> []
-                    Just value -> words value
-            writeFileChanged gmpLibNameCache . unlines . concatMap libs $ lines buildInfo
         else do
             putBuild "| No GMP library/framework detected; in tree GMP will be built"
-            writeFileChanged gmpLibNameCache ""
 
             -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is
             -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents.
diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs
index b3bca31..c9f8ddc 100644
--- a/src/Settings/Builders/Ghc.hs
+++ b/src/Settings/Builders/Ghc.hs
@@ -1,5 +1,5 @@
 module Settings.Builders.Ghc (
-    ghcBuilderArgs, ghcMBuilderArgs, commonGhcArgs, gmpLibNameCache
+    ghcBuilderArgs, ghcMBuilderArgs, commonGhcArgs
     ) where
 
 import Base
@@ -23,12 +23,12 @@ ghcBuilderArgs = stagedBuilder Ghc ? do
     stage  <- getStage
     way    <- getWay
     when (stage > Stage0) . lift $ needTouchy
-    let buildObj  = ("//*." ++  osuf way) ?== output || ("//*." ++  obootsuf way) ?== output
-        buildHi   = ("//*." ++ hisuf way) ?== output || ("//*." ++ hibootsuf way) ?== output
+    let buildObj  = any (\s -> ("//*." ++ s way) ?== output) [ osuf,  obootsuf]
+        buildHi   = any (\s -> ("//*." ++ s way) ?== output) [hisuf, hibootsuf]
         buildProg = not (buildObj || buildHi)
     libs    <- getPkgDataList DepExtraLibs
     gmpLibs <- if stage > Stage0 && buildProg
-               then lift $ readFileLines gmpLibNameCache -- TODO: use oracles
+               then words <$> getSetting GmpLibDir
                else return []
     libDirs <- getPkgDataList DepLibDirs
     mconcat [ commonGhcArgs
@@ -47,7 +47,7 @@ ghcBuilderArgs = stagedBuilder Ghc ? do
             , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ]
 
 needTouchy :: Action ()
-needTouchy = whenM windowsHost $ need [fromJust $ programPath Stage0 touchy ]
+needTouchy = whenM windowsHost $ need [fromJust $ programPath Stage0 touchy]
 
 splitObjectsArgs :: Args
 splitObjectsArgs = splitObjects ? do
diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs
index 20f4721..99a4962 100644
--- a/src/Settings/Paths.hs
+++ b/src/Settings/Paths.hs
@@ -1,7 +1,7 @@
 module Settings.Paths (
     targetDirectory, targetPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile,
-    pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpLibNameCache,
-    packageDbDirectory, pkgConfFile
+    pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, packageDbDirectory,
+    pkgConfFile
     ) where
 
 import Base
@@ -51,10 +51,6 @@ pkgFile stage pkg prefix suffix = do
 gmpBuildPath :: FilePath
 gmpBuildPath = buildRootPath -/- "stage1/gmp"
 
--- GMP library names extracted from integer-gmp.buildinfo
-gmpLibNameCache :: FilePath
-gmpLibNameCache = gmpBuildPath -/- "gmp-lib-names"
-
 -- TODO: move to buildRootPath, see #113
 -- StageN, N > 0, share the same packageDbDirectory
 packageDbDirectory :: Stage -> FilePath



More information about the ghc-commits mailing list