[commit: ghc] wip/nfs-locking: Factor out buildPackageGhciLibrary from buildPackageLibrary and make it more robust. (c0b1a37)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:03:44 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/c0b1a37c9681fb98ed85bbccb4004fad993c58f2/ghc
>---------------------------------------------------------------
commit c0b1a37c9681fb98ed85bbccb4004fad993c58f2
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Tue Feb 16 19:15:47 2016 +0000
Factor out buildPackageGhciLibrary from buildPackageLibrary and make it more robust.
See #207.
>---------------------------------------------------------------
c0b1a37c9681fb98ed85bbccb4004fad993c58f2
src/Rules.hs | 2 ++
src/Rules/Library.hs | 19 +++++++++++--------
2 files changed, 13 insertions(+), 8 deletions(-)
diff --git a/src/Rules.hs b/src/Rules.hs
index 74ffe30..444a2cb 100644
--- a/src/Rules.hs
+++ b/src/Rules.hs
@@ -61,6 +61,7 @@ packageRules = do
let readPackageDb = [(packageDb, 1)]
writePackageDb = [(packageDb, maxConcurrentReaders)]
+ -- TODO: not all build rules make sense for all stage/package combinations
let contexts = liftM3 Context allStages knownPackages allWays
vanillaContexts = liftM2 vanillaContext allStages knownPackages
@@ -72,6 +73,7 @@ packageRules = do
[ buildPackageData
, buildPackageDependencies readPackageDb
, buildPackageDocumentation
+ , buildPackageGhciLibrary
, generatePackageCode
, buildProgram
, registerPackage writePackageDb ]
diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs
index e53355f..c6d92a5 100644
--- a/src/Rules/Library.hs
+++ b/src/Rules/Library.hs
@@ -1,5 +1,7 @@
{-# LANGUAGE RecordWildCards #-}
-module Rules.Library (buildPackageLibrary, cSources, hSources) where
+module Rules.Library (
+ buildPackageLibrary, buildPackageGhciLibrary, cSources, hSources
+ ) where
import Data.Char
import qualified System.Directory as IO
@@ -17,10 +19,10 @@ import Target
buildPackageLibrary :: Context -> Rules ()
buildPackageLibrary context @ (Context {..}) = do
let buildPath = targetPath stage package -/- "build"
- libHs = buildPath -/- "libHS" ++ pkgNameString package
+ libPrefix = buildPath -/- "libHS" ++ pkgNameString package
-- TODO: handle dynamic libraries
- matchVersionedFilePath libHs (waySuffix way <.> "a") ?> \a -> do
+ matchVersionedFilePath libPrefix (waySuffix way <.> "a") ?> \a -> do
removeFileIfExists a
cSrcs <- cSources context
hSrcs <- hSources context
@@ -58,12 +60,13 @@ buildPackageLibrary context @ (Context {..}) = do
a
(dropWhileEnd isPunctuation synopsis)
+buildPackageGhciLibrary :: Context -> Rules ()
+buildPackageGhciLibrary context @ (Context {..}) = priority 2 $ do
+ let buildPath = targetPath stage package -/- "build"
+ libPrefix = buildPath -/- "HS" ++ pkgNameString package
+
-- TODO: simplify handling of AutoApply.cmm
- -- TODO: this looks fragile as haskell objects can match this rule if their
- -- names start with "HS" and they are on top of the module hierarchy.
- -- This happens with hsc2hs, which has top-level file HSCParser.hs.
- priority 2 $ when (package /= hsc2hs && way == vanilla) $
- (buildPath -/- "HS*.o") %> \obj -> do
+ matchVersionedFilePath libPrefix (waySuffix way <.> "o") ?> \obj -> do
cSrcs <- cSources context
hSrcs <- hSources context
let cObjs = [ buildPath -/- src -<.> "o" | src <- cSrcs
More information about the ghc-commits
mailing list