[commit: ghc] wip/nfs-locking: Compute cabalDeps in GhcCabal build (#320) (0589a9e)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:50:32 UTC 2017


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

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

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

commit 0589a9e4e68ee63a8e9d243e1604fbe9cda32f3c
Author: Zhen Zhang <izgzhen at gmail.com>
Date:   Tue Jun 6 23:46:11 2017 +0800

    Compute cabalDeps in GhcCabal build (#320)


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

0589a9e4e68ee63a8e9d243e1604fbe9cda32f3c
 src/Oracles/Dependencies.hs       | 9 ++++++++-
 src/Settings/Packages/GhcCabal.hs | 7 ++-----
 2 files changed, 10 insertions(+), 6 deletions(-)

diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs
index 2d6a404..167047d 100644
--- a/src/Oracles/Dependencies.hs
+++ b/src/Oracles/Dependencies.hs
@@ -1,6 +1,7 @@
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 module Oracles.Dependencies (
-    fileDependencies, contextDependencies, needContext, dependenciesOracles
+    fileDependencies, contextDependencies, needContext, dependenciesOracles,
+    pkgDependencies
     ) where
 
 import qualified Data.HashMap.Strict as Map
@@ -47,6 +48,12 @@ contextDependencies context at Context {..} = do
     pkgs <- sort <$> interpretInContext (pkgContext package) getPackages
     return . map pkgContext $ intersectOrd (compare . pkgNameString) pkgs deps
 
+-- | Given a `Package`, this `Action` looks up its package dependencies
+-- 'Settings.Paths.packageDependencies' using 'packageDependenciesOracle'
+-- The context will be the vanilla context with stage equal to 1
+pkgDependencies :: Package -> Action [Package]
+pkgDependencies = fmap (map Context.package) . contextDependencies . vanillaContext Stage1
+
 -- | Coarse-grain 'need': make sure given contexts are fully built.
 needContext :: [Context] -> Action ()
 needContext cs = do
diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs
index 3c830ae..57147e4 100644
--- a/src/Settings/Packages/GhcCabal.hs
+++ b/src/Settings/Packages/GhcCabal.hs
@@ -5,6 +5,7 @@ import Distribution.PackageDescription.Parse
 import Base
 import GHC
 import Oracles.Config.Setting
+import Oracles.Dependencies (pkgDependencies)
 import Predicate
 import Package (pkgCabalFile)
 import Distribution.Verbosity (silent)
@@ -15,12 +16,8 @@ import qualified Distribution.PackageDescription as DP
 
 ghcCabalPackageArgs :: Args
 ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do
-    -- Note: We could compute 'cabalDeps' instead of hard-coding it but this
-    -- seems unnecessary since we plan to drop @ghc-cabal@ altogether, #18.
     win <- lift windowsHost
-    let cabalDeps = [ array, base, bytestring, containers, deepseq, directory
-                    , pretty, process, time, if win then win32 else unix ]
-
+    cabalDeps <- lift $ pkgDependencies cabal
     lift $ need [pkgCabalFile cabal]
     pd <- liftIO . readGenericPackageDescription silent $ pkgCabalFile cabal
     let identifier   = DP.package . packageDescription $ pd



More information about the ghc-commits mailing list