[commit: ghc] wip/nfs-locking: Add matchPackageNames to match packages and package names. (341f711)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:12:35 UTC 2017


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

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

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

commit 341f711761e2ec9680613e81ad65335e61713f08
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Sun Dec 20 04:11:35 2015 +0000

    Add matchPackageNames to match packages and package names.


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

341f711761e2ec9680613e81ad65335e61713f08
 src/Package.hs           | 8 +++++++-
 src/Rules/Data.hs        | 3 +--
 src/Settings/Packages.hs | 7 ++++---
 3 files changed, 12 insertions(+), 6 deletions(-)

diff --git a/src/Package.hs b/src/Package.hs
index f64daee..8415bf1 100644
--- a/src/Package.hs
+++ b/src/Package.hs
@@ -1,6 +1,7 @@
 {-# LANGUAGE DeriveGeneric #-}
 module Package (
-    Package (..), PackageName, pkgCabalFile, setPath, topLevel, library, utility
+    Package (..), PackageName, pkgCabalFile, setPath, topLevel, library, utility,
+    matchPackageNames
     ) where
 
 import Base
@@ -45,6 +46,11 @@ instance Eq Package where
 instance Ord Package where
     compare = compare `on` pkgName
 
+-- Given a sorted list of packages and a sorted list of package names, returns
+-- packages whose names appear in the list of names
+matchPackageNames :: [Package] -> [PackageName] -> [Package]
+matchPackageNames = intersectOrd (\pkg name -> compare (pkgName pkg) name)
+
 -- Instances for storing in the Shake database
 instance Binary Package
 instance Hashable Package where
diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs
index 95ac426..b6925d0 100644
--- a/src/Rules/Data.hs
+++ b/src/Rules/Data.hs
@@ -31,8 +31,7 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do
             -- We configure packages in the order of their dependencies
             deps <- packageDeps pkg
             pkgs <- interpretPartial target getPackages
-            let cmp p name = compare (pkgName p) name
-                depPkgs    = intersectOrd cmp (sort pkgs) deps
+            let depPkgs = matchPackageNames (sort pkgs) deps
             need [ targetPath stage p -/- "package-data.mk" | p <- depPkgs ]
 
             need [cabalFile]
diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs
index 718b8de..df52715 100644
--- a/src/Settings/Packages.hs
+++ b/src/Settings/Packages.hs
@@ -18,7 +18,7 @@ defaultPackages = mconcat
 
 packagesStage0 :: Packages
 packagesStage0 = mconcat
-    [ append [ ghcBoot, binary, cabal, compiler, ghc, ghcCabal, ghcPkg
+    [ append [ binary, cabal, compiler, ghc, ghcBoot, ghcCabal, ghcPkg
              , hsc2hs, hoopl, hpc, templateHaskell, transformers ]
     , stage0 ? append [deriveConstants, genapply, genprimopcode, hp2ps]
     , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ]
@@ -41,9 +41,10 @@ packagesStage2 = mconcat
     [ append [ghcTags]
     , buildHaddock ? append [haddock] ]
 
+-- TODO: switch to Set Package as the order of packages should not matter?
 knownPackages :: [Package]
-knownPackages = defaultKnownPackages ++ userKnownPackages
+knownPackages = sort $ defaultKnownPackages ++ userKnownPackages
 
--- Note: this is slow but we keep it simple as there not too many packages (30)
+-- Note: this is slow but we keep it simple as there are just ~50 packages
 findKnownPackage :: PackageName -> Maybe Package
 findKnownPackage name = find (\pkg -> pkgName pkg == name) knownPackages



More information about the ghc-commits mailing list