[commit: ghc] wip/nfs-locking: Move needBuilder to src/Builder.hs. (7baa070)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:05:14 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/7baa070bd5bb2b40235bdb362d1f0ec6063f260d/ghc
>---------------------------------------------------------------
commit 7baa070bd5bb2b40235bdb362d1f0ec6063f260d
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Fri Aug 21 16:07:01 2015 +0100
Move needBuilder to src/Builder.hs.
>---------------------------------------------------------------
7baa070bd5bb2b40235bdb362d1f0ec6063f260d
src/Builder.hs | 25 +++++++++++++++++--------
1 file changed, 17 insertions(+), 8 deletions(-)
diff --git a/src/Builder.hs b/src/Builder.hs
index ac184d3..bd0ef49 100644
--- a/src/Builder.hs
+++ b/src/Builder.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE DeriveGeneric #-}
module Builder (
- Builder (..), builderKey, builderPath, specified
+ Builder (..), builderKey, builderPath, specified, needBuilder
) where
import Base
@@ -61,7 +61,7 @@ builderKey builder = case builder of
-- GhcCabalHsColour is a synonym for GhcCabal (called in hscolour mode)
GhcCabalHsColour -> builderKey $ GhcCabal
-builderPath :: Builder -> Action String
+builderPath :: Builder -> Action FilePath
builderPath builder = do
path <- askConfigWithDefault (builderKey builder) $
putError $ "\nCannot find path to '" ++ (builderKey builder)
@@ -71,6 +71,21 @@ builderPath builder = do
specified :: Builder -> Action Bool
specified = fmap (not . null) . builderPath
+-- Make sure a builder exists on the given path and rebuild it if out of date.
+-- If laxDependencies is True then we do not rebuild GHC even if it is out of
+-- date (can save a lot of build time when changing GHC).
+needBuilder :: Bool -> Builder -> Action ()
+needBuilder laxDependencies builder = do
+ path <- builderPath builder
+ if laxDependencies && allowOrderOnlyDependency builder
+ then orderOnly [path]
+ else need [path]
+ where
+ allowOrderOnlyDependency :: Builder -> Bool
+ allowOrderOnlyDependency (Ghc _) = True
+ allowOrderOnlyDependency (GhcM _) = True
+ allowOrderOnlyDependency _ = False
+
-- On Windows: if the path starts with "/", prepend it with the correct path to
-- the root, e.g: "/usr/local/bin/ghc.exe" => "C:/msys/usr/local/bin/ghc.exe".
fixAbsolutePathOnWindows :: FilePath -> Action FilePath
@@ -84,12 +99,6 @@ fixAbsolutePathOnWindows path = do
else
return path
--- When LaxDeps flag is set ('lax-dependencies = YES' in user.config),
--- dependencies on the GHC executable are turned into order-only dependencies
--- to avoid needless recompilation when making changes to GHC's sources. In
--- certain situations this can lead to build failures, in which case you
--- should reset the flag (at least temporarily).
-
-- Instances for storing in the Shake database
instance Binary Builder
instance Hashable Builder
More information about the ghc-commits
mailing list