[commit: ghc] wip/nfs-locking: Move Shake files into _build/hadrian (185af60)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:27:40 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/185af600e91c5294fe8f49158ca8d73aec6ec646/ghc
>---------------------------------------------------------------
commit 185af600e91c5294fe8f49158ca8d73aec6ec646
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Sat Apr 30 23:04:41 2016 +0100
Move Shake files into _build/hadrian
>---------------------------------------------------------------
185af600e91c5294fe8f49158ca8d73aec6ec646
src/Base.hs | 13 +------------
src/Main.hs | 4 ++--
src/Oracles/PackageDeps.hs | 4 +++-
src/Rules/Clean.hs | 6 +++---
src/Settings/Paths.hs | 12 +++++++++++-
5 files changed, 20 insertions(+), 19 deletions(-)
diff --git a/src/Base.hs b/src/Base.hs
index 53bb197..a38ea51 100644
--- a/src/Base.hs
+++ b/src/Base.hs
@@ -16,8 +16,7 @@ module Base (
module Development.Shake.FilePath,
-- * Paths
- shakeFilesPath, configPath, configFile, sourcePath, programInplacePath,
- bootPackageConstraints, packageDependencies,
+ configPath, configFile, sourcePath, programInplacePath,
-- * Output
putColoured, putOracle, putBuild, putSuccess, putError,
@@ -50,10 +49,6 @@ import System.IO
shakePath :: FilePath
shakePath = "hadrian"
--- TODO: Move to buildRootPath.
-shakeFilesPath :: FilePath
-shakeFilesPath = shakePath -/- ".db"
-
configPath :: FilePath
configPath = shakePath -/- "cfg"
@@ -69,12 +64,6 @@ sourcePath = shakePath -/- "src"
programInplacePath :: FilePath
programInplacePath = "inplace/bin"
-bootPackageConstraints :: FilePath
-bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints"
-
-packageDependencies :: FilePath
-packageDependencies = shakeFilesPath -/- "package-dependencies"
-
-- Utility functions
-- | Find and replace all occurrences of a value in a list
replaceEq :: Eq a => a -> a -> [a] -> [a]
diff --git a/src/Main.hs b/src/Main.hs
index cf45cc3..66f897f 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -2,7 +2,6 @@ module Main (main) where
import Development.Shake
-import qualified Base
import qualified CmdLineFlag
import qualified Environment
import qualified Rules
@@ -10,6 +9,7 @@ import qualified Rules.Clean
import qualified Rules.Oracles
import qualified Rules.Selftest
import qualified Rules.Test
+import qualified Settings.Paths
main :: IO ()
main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do
@@ -30,6 +30,6 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do
options :: ShakeOptions
options = shakeOptions
{ shakeChange = ChangeModtimeAndDigest
- , shakeFiles = Base.shakeFilesPath
+ , shakeFiles = Settings.Paths.shakeFilesPath
, shakeProgress = progressSimple
, shakeTimings = True }
diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs
index 6a5f7dd..a2a9234 100644
--- a/src/Oracles/PackageDeps.hs
+++ b/src/Oracles/PackageDeps.hs
@@ -1,9 +1,11 @@
{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
module Oracles.PackageDeps (packageDeps, packageDepsOracle) where
-import Base
import qualified Data.HashMap.Strict as Map
+
+import Base
import Package
+import Settings.Paths
newtype PackageDepsKey = PackageDepsKey PackageName
deriving (Show, Typeable, Eq, Hashable, Binary, NFData)
diff --git a/src/Rules/Clean.hs b/src/Rules/Clean.hs
index 0bff316..ca5c062 100644
--- a/src/Rules/Clean.hs
+++ b/src/Rules/Clean.hs
@@ -17,7 +17,7 @@ clean dir = do
cleanRules :: Rules ()
cleanRules = do
"clean" ~> do
- clean buildRootPath
+ forM_ [Stage0 ..] $ \stage -> clean (buildRootPath -/- stageString stage)
clean programInplacePath
clean "inplace/lib"
clean derivedConstantsPath
@@ -29,6 +29,6 @@ cleanRules = do
forM_ [Stage0 ..] $ \stage -> do
let dir = pkgPath pkg -/- contextDirectory (vanillaContext stage pkg)
removeDirectoryIfExists dir
- putBuild $ "| Remove the Shake database " ++ shakeFilesPath ++ "..."
- removeFilesAfter shakeFilesPath ["//*"]
+ putBuild $ "| Remove Hadrian files..."
+ removeFilesAfter buildRootPath ["//*"]
putSuccess $ "| Done. "
diff --git a/src/Settings/Paths.hs b/src/Settings/Paths.hs
index 678ed92..77fb5a5 100644
--- a/src/Settings/Paths.hs
+++ b/src/Settings/Paths.hs
@@ -1,7 +1,8 @@
module Settings.Paths (
contextDirectory, buildPath, pkgDataFile, pkgHaddockFile, pkgLibraryFile,
pkgLibraryFile0, pkgGhciLibraryFile, gmpBuildPath, gmpBuildInfoPath,
- packageDbDirectory, pkgConfFile
+ packageDbDirectory, pkgConfFile, shakeFilesPath, bootPackageConstraints,
+ packageDependencies
) where
import Base
@@ -16,6 +17,15 @@ import Settings.User
(~/~) :: FilePath -> FilePath -> FilePath
x ~/~ y = x ++ '/' : y
+shakeFilesPath :: FilePath
+shakeFilesPath = buildRootPath -/- "hadrian/shake-files"
+
+bootPackageConstraints :: FilePath
+bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints"
+
+packageDependencies :: FilePath
+packageDependencies = shakeFilesPath -/- "package-dependencies"
+
-- | Path to the directory containing build artefacts of a given 'Context'.
buildPath :: Context -> FilePath
buildPath context at Context {..} =
More information about the ghc-commits
mailing list