[commit: ghc] wip/nfs-locking: Fix detection of libraries (86ed4e3)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:13:09 UTC 2017


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

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

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

commit 86ed4e32b39b0ab57e64fbd93cccfb8113d162b7
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Sun Dec 20 20:23:34 2015 +0100

    Fix detection of libraries
    
    Previously a very fragile heuristic was used. Now we explicitly declare
    this.
    
    Perhaps a better option in the future would be to instead emit this
    information from `ghc-cabal` and pick it up from `package-data.mk`.
    
    Fixes #9.


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

86ed4e32b39b0ab57e64fbd93cccfb8113d162b7
 src/GHC.hs                      |  2 +-
 src/Package.hs                  | 37 ++++++++++++++++++++++++++-----------
 src/Rules/Data.hs               |  3 ++-
 src/Settings.hs                 |  3 ++-
 src/Settings/TargetDirectory.hs |  2 +-
 5 files changed, 32 insertions(+), 15 deletions(-)

diff --git a/src/GHC.hs b/src/GHC.hs
index 0279197..c38af04 100644
--- a/src/GHC.hs
+++ b/src/GHC.hs
@@ -51,7 +51,7 @@ dllSplit        = utility  "dll-split"
 filepath        = library  "filepath"
 genapply        = utility  "genapply"
 genprimopcode   = utility  "genprimopcode"
-ghc             = topLevel "ghc-bin"        `setPath` "ghc"
+ghc             = topLevel "ghc-bin"        `setPath` "ghc" `setPkgType` Program
 ghcBoot         = library  "ghc-boot"
 ghcCabal        = utility  "ghc-cabal"
 ghci            = library  "ghci"
diff --git a/src/Package.hs b/src/Package.hs
index 8415bf1..6273a62 100644
--- a/src/Package.hs
+++ b/src/Package.hs
@@ -1,23 +1,31 @@
 {-# LANGUAGE DeriveGeneric #-}
 module Package (
-    Package (..), PackageName, pkgCabalFile, setPath, topLevel, library, utility,
-    matchPackageNames
+    Package (..), PackageName, PackageType (..),
+    -- * Queries
+    pkgCabalFile,
+    matchPackageNames,
+    -- * Helpers for constructing 'Package's
+    setPath, topLevel, library, utility, setPkgType
     ) where
 
 import Base
 import GHC.Generics (Generic)
 
--- It is helpful to distinguish package names from strings.
+-- | It is helpful to distinguish package names from strings.
 type PackageName = String
 
--- type PackageType = Program | Library
+-- | We regard packages as either being libraries or programs. This is
+-- bit of a convenient lie as Cabal packages can be both, but it works
+-- for now.
+data PackageType = Program | Library
+                 deriving Generic
 
--- pkgPath is the path to the source code relative to the root
 data Package = Package
      {
-         pkgName :: PackageName, -- Examples: "ghc", "Cabal"
-         pkgPath :: FilePath     -- "compiler", "libraries/Cabal/Cabal"
-         -- pkgType :: PackageType  -- TopLevel, Library
+         pkgName :: PackageName, -- ^ Examples: "ghc", "Cabal"
+         pkgPath :: FilePath,    -- ^ pkgPath is the path to the source code relative to the root.
+                                 -- e.g. "compiler", "libraries/Cabal/Cabal"
+         pkgType :: PackageType
      }
      deriving Generic
 
@@ -26,17 +34,20 @@ pkgCabalFile :: Package -> FilePath
 pkgCabalFile pkg = pkgPath pkg -/- pkgName pkg <.> "cabal"
 
 topLevel :: PackageName -> Package
-topLevel name = Package name name
+topLevel name = Package name name Library
 
 library :: PackageName -> Package
-library name = Package name ("libraries" -/- name)
+library name = Package name ("libraries" -/- name) Library
 
 utility :: PackageName -> Package
-utility name = Package name ("utils" -/- name)
+utility name = Package name ("utils" -/- name) Program
 
 setPath :: Package -> FilePath -> Package
 setPath pkg path = pkg { pkgPath = path }
 
+setPkgType :: Package -> PackageType -> Package
+setPkgType pkg ty = pkg { pkgType = ty }
+
 instance Show Package where
     show = pkgName
 
@@ -56,3 +67,7 @@ instance Binary Package
 instance Hashable Package where
     hashWithSalt salt = hashWithSalt salt . show
 instance NFData Package
+
+instance Binary PackageType
+instance Hashable PackageType
+instance NFData PackageType
diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs
index b68a1f6..fdbe21d 100644
--- a/src/Rules/Data.hs
+++ b/src/Rules/Data.hs
@@ -38,7 +38,8 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do
             buildWithResources [(ghcCabal rs, 1)] $
                 fullTarget target GhcCabal [cabalFile] outs
 
-            -- TODO: find out of ghc-cabal can be concurrent with ghc-pkg
+            -- ghc-pkg produces inplace-pkg-config when run on packages with
+            -- library components only
             when (isLibrary pkg) .
                 whenM (interpretPartial target registerPackage) .
                 buildWithResources [(ghcPkg rs, 1)] $
diff --git a/src/Settings.hs b/src/Settings.hs
index d16c5cd..7a1ab72 100644
--- a/src/Settings.hs
+++ b/src/Settings.hs
@@ -33,7 +33,8 @@ programPath :: Stage -> Package -> Maybe FilePath
 programPath = userProgramPath
 
 isLibrary :: Package -> Bool
-isLibrary pkg = programPath Stage0 pkg == Nothing
+isLibrary (Package {pkgType=Library}) = True
+isLibrary _ = False
 
 -- Find all Haskell source files for the current target. TODO: simplify.
 getPackageSources :: Expr [FilePath]
diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs
index 286670b..a4301f4 100644
--- a/src/Settings/TargetDirectory.hs
+++ b/src/Settings/TargetDirectory.hs
@@ -22,7 +22,7 @@ pkgDataFile stage pkg = targetPath stage pkg -/- "package-data.mk"
 -- Relative path to a package haddock file, e.g.:
 -- "libraries/array/dist-install/doc/html/array/array.haddock"
 pkgHaddockFile :: Package -> FilePath
-pkgHaddockFile pkg @ (Package name _) =
+pkgHaddockFile pkg @ (Package name _ _) =
     targetPath Stage1 pkg -/- "doc/html" -/- name -/- name <.> "haddock"
 
 -- Relative path to a package library file, e.g.:



More information about the ghc-commits mailing list