[commit: ghc] master: Fix dependencies (#477) (9dd7ad2)

git at git.haskell.org git at git.haskell.org
Tue Oct 23 20:12:19 UTC 2018


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/9dd7ad2accc79efbbfb7847c89e881fa02f7c911/ghc

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

commit 9dd7ad2accc79efbbfb7847c89e881fa02f7c911
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Mon Nov 20 03:26:15 2017 +0000

    Fix dependencies (#477)
    
    See #464
    
    * Drop non-source dependencies during compilation
    
    * Drop duplicated dependencies on package configuration
    
    * Compute transitive closure of context dependencies
    
    * Don't depend on a temporary file


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

9dd7ad2accc79efbbfb7847c89e881fa02f7c911
 src/Rules/Compile.hs              |  2 --
 src/Rules/Dependencies.hs         |  4 ++--
 src/Settings/Builders/Ghc.hs      |  8 ++++----
 src/Settings/Packages/GhcCabal.hs |  5 +++--
 src/Utilities.hs                  | 30 +++++++++++++++++++-----------
 5 files changed, 28 insertions(+), 21 deletions(-)

diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs
index a4b1278..b7f3bc8 100644
--- a/src/Rules/Compile.hs
+++ b/src/Rules/Compile.hs
@@ -22,8 +22,6 @@ compilePackage rs context at Context {..} = do
             path <- buildPath context
             (src, deps) <- lookupDependencies (path -/- ".dependencies") obj
             need $ src : deps
-            when (isLibrary package) $ need =<< return <$> pkgConfFile context
-            needLibrary =<< contextDependencies context
             buildWithResources rs $ target context (Ghc CompileHs stage) [src] [obj]
 
     priority 2.0 $ do
diff --git a/src/Rules/Dependencies.hs b/src/Rules/Dependencies.hs
index f27ef0d..f9d17e9 100644
--- a/src/Rules/Dependencies.hs
+++ b/src/Rules/Dependencies.hs
@@ -19,11 +19,11 @@ buildPackageDependencies rs context at Context {..} =
         orderOnly =<< interpretInContext context generatedDependencies
         let mk = deps <.> "mk"
         if null srcs
-        then writeFileChanged mk ""
+        then writeFile' mk ""
         else buildWithResources rs $
             target context (Ghc FindHsDependencies stage) srcs [mk]
         removeFile $ mk <.> "bak"
-        mkDeps <- readFile' mk
+        mkDeps <- liftIO $ readFile mk
         writeFileChanged deps . unlines
                               . map (\(src, deps) -> unwords $ src : deps)
                               . map (bimap unifyPath (map unifyPath))
diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs
index a975e7e..af78b74 100644
--- a/src/Settings/Builders/Ghc.hs
+++ b/src/Settings/Builders/Ghc.hs
@@ -87,10 +87,10 @@ haddockGhcArgs = mconcat [ commonGhcArgs, getPkgDataList HsArgs ]
 -- Used in ghcBuilderArgs, ghcCBuilderArgs, ghcMBuilderArgs and haddockGhcArgs.
 commonGhcArgs :: Args
 commonGhcArgs = do
-    way     <- getWay
-    path    <- getBuildPath
-    pkg     <- getPackage
-    when (isLibrary pkg) $ do
+    way  <- getWay
+    path <- getBuildPath
+    pkg  <- getPackage
+    when (pkg == rts) $ do
         context <- getContext
         conf <- expr $ pkgConfFile context
         expr $ need [conf]
diff --git a/src/Settings/Packages/GhcCabal.hs b/src/Settings/Packages/GhcCabal.hs
index 0e915b3..c88617b 100644
--- a/src/Settings/Packages/GhcCabal.hs
+++ b/src/Settings/Packages/GhcCabal.hs
@@ -8,10 +8,11 @@ import Utilities
 
 ghcCabalPackageArgs :: Args
 ghcCabalPackageArgs = stage0 ? package ghcCabal ? builder Ghc ? do
-    cabalDeps    <- expr $ stage1Dependencies cabal
+    cabalDeps <- expr $ stage1Dependencies cabal
+    let bootDeps = cabalDeps \\ [integerGmp, integerSimple, mtl, parsec, text]
     cabalVersion <- expr $ pkgVersion (unsafePkgCabalFile cabal) -- TODO: improve
     mconcat
-        [ pure [ "-package " ++ pkgName pkg | pkg <- cabalDeps \\ [parsec, mtl] ]
+        [ pure [ "-package " ++ pkgName pkg | pkg <- bootDeps ]
         , arg "--make"
         , arg "-j"
         , pure ["-Wall", "-fno-warn-unused-imports", "-fno-warn-warnings-deprecations"]
diff --git a/src/Utilities.hs b/src/Utilities.hs
index 3c61dae..fc898c3 100644
--- a/src/Utilities.hs
+++ b/src/Utilities.hs
@@ -24,21 +24,29 @@ buildWithResources rs target = H.buildWithResources rs target getArgs
 buildWithCmdOptions :: [CmdOption] -> Target -> Action ()
 buildWithCmdOptions opts target = H.buildWithCmdOptions opts target getArgs
 
--- | Given a 'Context' this 'Action' look up the package dependencies and wrap
+-- TODO: Cache the computation.
+-- | Given a 'Context' this 'Action' looks up the package dependencies and wraps
 -- the results in appropriate contexts. The only subtlety here is that we never
 -- depend on packages built in 'Stage2' or later, therefore the stage of the
 -- resulting dependencies is bounded from above at 'Stage1'. To compute package
--- dependencies we scan package @.cabal@ files, see 'pkgDependencies' defined
--- in "Hadrian.Haskell.Cabal".
+-- dependencies we transitively scan @.cabal@ files using 'pkgDependencies'
+-- defined in "Hadrian.Haskell.Cabal".
 contextDependencies :: Context -> Action [Context]
-contextDependencies Context {..} = case pkgCabalFile package of
-    Nothing        -> return [] -- Non-Cabal packages have no dependencies.
-    Just cabalFile -> do
-        let depStage   = min stage Stage1
-            depContext = \pkg -> Context depStage pkg way
-        deps <- pkgDependencies cabalFile
-        pkgs <- sort <$> stagePackages depStage
-        return . map depContext $ intersectOrd (compare . pkgName) pkgs deps
+contextDependencies Context {..} = do
+    depPkgs <- go [package]
+    return [ Context depStage pkg way | pkg <- depPkgs, pkg /= package ]
+  where
+    depStage = min stage Stage1
+    go pkgs  = do
+        deps <- concatMapM step pkgs
+        let newPkgs = nubOrd $ sort (deps ++ pkgs)
+        if pkgs == newPkgs then return pkgs else go newPkgs
+    step pkg   = case pkgCabalFile pkg of
+        Nothing        -> return [] -- Non-Cabal packages have no dependencies.
+        Just cabalFile -> do
+            deps   <- pkgDependencies cabalFile
+            active <- sort <$> stagePackages depStage
+            return $ intersectOrd (compare . pkgName) active deps
 
 -- | Lookup dependencies of a 'Package' in the vanilla Stage1 context.
 stage1Dependencies :: Package -> Action [Package]



More information about the ghc-commits mailing list