[commit: ghc] wip/nfs-locking: Add support for non-library packages. (c488f65)

git at git.haskell.org git at git.haskell.org
Thu Oct 26 23:22:50 UTC 2017


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

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

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

commit c488f65dd9a894af75e633c5bd78220d7b60cc84
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Fri Sep 25 02:53:37 2015 +0100

    Add support for non-library packages.


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

c488f65dd9a894af75e633c5bd78220d7b60cc84
 src/GHC.hs                      | 21 +++++++++++++++------
 src/Rules.hs                    |  7 ++++++-
 src/Rules/Data.hs               |  4 ++--
 src/Settings.hs                 |  8 +++++++-
 src/Settings/Packages.hs        |  8 ++++----
 src/Settings/TargetDirectory.hs |  2 ++
 src/Settings/User.hs            | 10 +++++++---
 7 files changed, 43 insertions(+), 17 deletions(-)

diff --git a/src/GHC.hs b/src/GHC.hs
index c277c6a..668cf48 100644
--- a/src/GHC.hs
+++ b/src/GHC.hs
@@ -4,9 +4,10 @@ module GHC (
     integerGmp, integerSimple, parallel, pretty, primitive, process, stm,
     templateHaskell, terminfo, time, transformers, unix, win32, xhtml,
 
-    defaultKnownPackages, defaultTargetDirectory
+    defaultKnownPackages, defaultTargetDirectory, defaultProgramPath
     ) where
 
+import Base
 import Package
 import Stage
 
@@ -66,8 +67,16 @@ xhtml           = library  "xhtml"
 -- * package-data.mk : contains output of ghc-cabal applied to pkgCabal
 -- TODO: simplify to just 'show stage'?
 defaultTargetDirectory :: Stage -> Package -> FilePath
-defaultTargetDirectory stage package
-    | package == compiler = "stage" ++ show (fromEnum stage + 1)
-    | package == ghc      = "stage" ++ show (fromEnum stage + 1)
-    | stage   == Stage0   = "dist-boot"
-    | otherwise           = "dist-install"
+defaultTargetDirectory stage pkg
+    | pkg   == compiler = "stage" ++ show (fromEnum stage + 1)
+    | pkg   == ghc      = "stage" ++ show (fromEnum stage + 1)
+    | stage == Stage0   = "dist-boot"
+    | otherwise         = "dist-install"
+
+defaultProgramPath :: Stage -> Package -> Maybe FilePath
+defaultProgramPath stage pkg
+    | pkg == ghc = program $ "ghc-stage" ++ show (fromEnum stage + 1)
+    | otherwise  = Nothing
+  where
+    program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg
+                                      -/- "build/tmp" -/- name <.> exe
diff --git a/src/Rules.hs b/src/Rules.hs
index 26e57bd..e615c64 100644
--- a/src/Rules.hs
+++ b/src/Rules.hs
@@ -11,7 +11,8 @@ generateTargets :: Rules ()
 generateTargets = action $ do
     targets <- fmap concat . forM [Stage0 ..] $ \stage -> do
         pkgs <- interpretWithStage stage getPackages
-        fmap concat . forM pkgs $ \pkg -> do
+        let (libPkgs, programPkgs) = partition isLibrary pkgs
+        libTargets <- fmap concat . forM libPkgs $ \pkg -> do
             let target    = PartialTarget stage pkg
                 buildPath = targetPath stage pkg -/- "build"
             libName     <- interpretPartial target $ getPkgData LibName
@@ -28,6 +29,10 @@ generateTargets = action $ do
                    ++ [ haddock | needHaddock          && stage == Stage1 ]
                    ++ libs
 
+        let programTargets = map (fromJust . programPath stage) programPkgs
+
+        return $ libTargets ++ programTargets
+
     need $ reverse targets
 
 -- TODO: add Stage2 (compiler only?)
diff --git a/src/Rules/Data.hs b/src/Rules/Data.hs
index 3622918..1085f8f 100644
--- a/src/Rules/Data.hs
+++ b/src/Rules/Data.hs
@@ -17,7 +17,6 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do
     fmap (path -/-)
         [ "package-data.mk"
         , "haddock-prologue.txt"
-        , "inplace-pkg-config"
         , "setup-config"
         , "build" -/- "autogen" -/- "cabal_macros.h"
         -- TODO: Is this needed? Also check out Paths_cpsa.hs.
@@ -39,7 +38,8 @@ buildPackageData rs target @ (PartialTarget stage pkg) = do
                 fullTarget target GhcCabal [cabalFile] outs
 
             -- TODO: find out of ghc-cabal can be concurrent with ghc-pkg
-            whenM (interpretPartial target registerPackage) .
+            when (isLibrary pkg) .
+                whenM (interpretPartial target registerPackage) .
                 buildWithResources [(ghcPkg rs, 1)] $
                 fullTarget target (GhcPkg stage) [cabalFile] outs
 
diff --git a/src/Settings.hs b/src/Settings.hs
index dab73ed..d16c5cd 100644
--- a/src/Settings.hs
+++ b/src/Settings.hs
@@ -3,7 +3,7 @@ module Settings (
     module Settings.TargetDirectory,
     module Settings.User,
     module Settings.Ways,
-    getPkgData, getPkgDataList,
+    getPkgData, getPkgDataList, programPath, isLibrary,
     getPackagePath, getTargetDirectory, getTargetPath, getPackageSources,
     ) where
 
@@ -29,6 +29,12 @@ getPkgData key = lift . pkgData . key =<< getTargetPath
 getPkgDataList :: (FilePath -> PackageDataList) -> Expr [String]
 getPkgDataList key = lift . pkgDataList . key =<< getTargetPath
 
+programPath :: Stage -> Package -> Maybe FilePath
+programPath = userProgramPath
+
+isLibrary :: Package -> Bool
+isLibrary pkg = programPath Stage0 pkg == Nothing
+
 -- Find all Haskell source files for the current target. TODO: simplify.
 getPackageSources :: Expr [FilePath]
 getPackageSources = do
diff --git a/src/Settings/Packages.hs b/src/Settings/Packages.hs
index 8b913f5..1fe70dc 100644
--- a/src/Settings/Packages.hs
+++ b/src/Settings/Packages.hs
@@ -16,16 +16,16 @@ defaultPackages = mconcat
 
 packagesStage0 :: Packages
 packagesStage0 = mconcat
-    [ append [ binPackageDb, binary, cabal, compiler, ghc, hoopl, hpc, transformers ]
+    [ append [ binPackageDb, binary, cabal, compiler, ghc, hoopl, hpc
+             , templateHaskell, transformers ]
     , notM windowsHost ? notM (anyHostOs ["ios"]) ? append [terminfo] ]
 
 -- TODO: what do we do with parallel, stm, random, primitive, vector and dph?
 packagesStage1 :: Packages
 packagesStage1 = mconcat
     [ packagesStage0
-    , append [ array, base, bytestring, containers, deepseq, directory
-             , filepath, ghc, ghcPrim, haskeline, integerLibrary, pretty
-             , process, templateHaskell, time ]
+    , append [ array, base, bytestring, containers, deepseq, directory, filepath
+             , ghcPrim, haskeline, integerLibrary, pretty, process, time ]
     , windowsHost      ? append [win32]
     , notM windowsHost ? append [unix]
     , buildHaddock     ? append [xhtml] ]
diff --git a/src/Settings/TargetDirectory.hs b/src/Settings/TargetDirectory.hs
index 58f2d51..b84d03d 100644
--- a/src/Settings/TargetDirectory.hs
+++ b/src/Settings/TargetDirectory.hs
@@ -5,6 +5,8 @@ module Settings.TargetDirectory (
 import Expression
 import Settings.User
 
+-- TODO: move to Settings.hs?
+
 -- User can override the default target directory settings given below
 targetDirectory :: Stage -> Package -> FilePath
 targetDirectory = userTargetDirectory
diff --git a/src/Settings/User.hs b/src/Settings/User.hs
index 9a71ac2..d841028 100644
--- a/src/Settings/User.hs
+++ b/src/Settings/User.hs
@@ -1,6 +1,6 @@
 module Settings.User (
     userArgs, userPackages, userLibWays, userRtsWays, userTargetDirectory,
-    userKnownPackages, integerLibrary,
+    userProgramPath, userKnownPackages, integerLibrary,
     trackBuildSystem, buildHaddock, validating, ghciWithDebugger, ghcProfiled,
     ghcDebugged, dynamicGhcPrograms, laxDependencies
     ) where
@@ -15,7 +15,7 @@ userArgs = mempty
 
 -- Control which packages get to be built
 userPackages :: Packages
-userPackages = remove [ghc]
+userPackages = mempty
 
 -- Add new user-defined packages
 userKnownPackages :: [Package]
@@ -28,10 +28,14 @@ userLibWays = mempty
 userRtsWays :: Ways
 userRtsWays = mempty
 
--- Control where build results go (see Settings.Default for an example)
+-- Control where build results go (see GHC.hs for defaults)
 userTargetDirectory :: Stage -> Package -> FilePath
 userTargetDirectory = defaultTargetDirectory
 
+-- Control how built programs are called (see GHC.hs for defaults)
+userProgramPath :: Stage -> Package -> Maybe FilePath
+userProgramPath = defaultProgramPath
+
 -- Choose integer library: integerGmp, integerGmp2 or integerSimple
 integerLibrary :: Package
 integerLibrary = integerGmp



More information about the ghc-commits mailing list