[commit: ghc] wip/nfs-locking: Pass way to buildPackageLibrary via Context, minor revision. (98b1f8c)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:21:00 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/98b1f8c2e233d4b9504dfe359b0f538f7af9095e/ghc
>---------------------------------------------------------------
commit 98b1f8c2e233d4b9504dfe359b0f538f7af9095e
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Tue Feb 16 03:01:56 2016 +0000
Pass way to buildPackageLibrary via Context, minor revision.
See #207.
>---------------------------------------------------------------
98b1f8c2e233d4b9504dfe359b0f538f7af9095e
src/Rules.hs | 15 +++++++++------
src/Rules/Documentation.hs | 1 +
src/Rules/Library.hs | 13 +++++--------
src/Way.hs | 4 ++--
4 files changed, 17 insertions(+), 16 deletions(-)
diff --git a/src/Rules.hs b/src/Rules.hs
index a3d67cb..4592b4a 100644
--- a/src/Rules.hs
+++ b/src/Rules.hs
@@ -64,16 +64,19 @@ packageRules = do
let contexts = liftM3 Context allStages knownPackages allWays
vanillaContexts = liftM2 vanillaContext allStages knownPackages
- traverse_ (compilePackage readPackageDb) contexts
- traverse_ (buildPackageDependencies readPackageDb) vanillaContexts
+ for_ contexts $ mconcat
+ [ compilePackage readPackageDb
+ , buildPackageLibrary ]
+
+ for_ vanillaContexts $ mconcat
+ [ buildPackageData
+ , buildPackageDependencies readPackageDb
+ , buildPackageDocumentation
+ , generatePackageCode ]
for_ allStages $ \stage ->
for_ knownPackages $ \package -> do
let context = vanillaContext stage package
- buildPackageData context
- buildPackageDocumentation context
- generatePackageCode context
- buildPackageLibrary context
buildProgram context
registerPackage writePackageDb context
diff --git a/src/Rules/Documentation.hs b/src/Rules/Documentation.hs
index 848a3fa..e3b0e7d 100644
--- a/src/Rules/Documentation.hs
+++ b/src/Rules/Documentation.hs
@@ -37,6 +37,7 @@ buildPackageDocumentation context @ (Context {..}) =
build $ Target context GhcCabalHsColour [cabalFile] []
-- Build Haddock documentation
+ -- TODO: pass the correct way from Rules via Context
let haddockWay = if dynamicGhcPrograms then dynamic else vanilla
build $ Target (context {way = haddockWay}) Haddock srcs [file]
diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs
index 79b4952..d77d58e 100644
--- a/src/Rules/Library.hs
+++ b/src/Rules/Library.hs
@@ -14,24 +14,21 @@ import Rules.Gmp
import Settings
import Target
--- TODO: Use way from Context, #207
buildPackageLibrary :: Context -> Rules ()
buildPackageLibrary context @ (Context {..}) = do
let buildPath = targetPath stage package -/- "build"
-- TODO: handle dynamic libraries
- matchBuildResult buildPath "a" ?> \a -> do
-
+ buildPath <//> "*" ++ waySuffix way ++ ".a" %> \a -> do
removeFileIfExists a
cSrcs <- cSources context
hSrcs <- hSources context
- -- TODO: simplify handling of AutoApply.cmm
- let w = detectWay a -- TODO: eliminate differences below
- cObjs = [ buildPath -/- src -<.> osuf w | src <- cSrcs
+ -- TODO: simplify handling of AutoApply.cmm, eliminate differences below
+ let cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs
, not ("//AutoApply.cmm" ?== src) ]
- ++ [ src -<.> osuf w | src <- cSrcs, "//AutoApply.cmm" ?== src ]
- hObjs = [ buildPath -/- src <.> osuf w | src <- hSrcs ]
+ ++ [ src -<.> osuf way | src <- cSrcs, "//AutoApply.cmm" ?== src ]
+ hObjs = [ buildPath -/- src <.> osuf way | src <- hSrcs ]
-- This will create split objects if required (we don't track them
-- explicitly as this would needlessly bloat the Shake database).
diff --git a/src/Way.hs b/src/Way.hs
index 668ed63..c393437 100644
--- a/src/Way.hs
+++ b/src/Way.hs
@@ -6,8 +6,8 @@ module Way (
threadedDebugProfiling, threadedDebugDynamic, threadedProfilingDynamic,
threadedLoggingDynamic, debugProfiling, debugDynamic, loggingDynamic,
- allWays, wayPrefix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf, libsuf,
- safeDetectWay, detectWay, matchBuildResult
+ allWays, wayPrefix, waySuffix, hisuf, osuf, hcsuf, obootsuf, hibootsuf, ssuf,
+ libsuf, safeDetectWay, detectWay, matchBuildResult
) where
import Base hiding (unit)
More information about the ghc-commits
mailing list