[commit: ghc] wip/nfs-locking: Add buildPackageLibrary build rule. (3f3134c)
git at git.haskell.org
git at git.haskell.org
Thu Oct 26 23:16:28 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/3f3134cc10b412afc71b7beb80a77ee779ecc3c1/ghc
>---------------------------------------------------------------
commit 3f3134cc10b412afc71b7beb80a77ee779ecc3c1
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Thu Aug 6 01:41:25 2015 +0100
Add buildPackageLibrary build rule.
>---------------------------------------------------------------
3f3134cc10b412afc71b7beb80a77ee779ecc3c1
src/Rules/Compile.hs | 4 ----
src/Rules/Library.hs | 63 ++++++++++++++++++++++++++++++++++++++++++++++++++++
src/Rules/Package.hs | 7 +++++-
3 files changed, 69 insertions(+), 5 deletions(-)
diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs
index 89b60c2..6f57a81 100644
--- a/src/Rules/Compile.hs
+++ b/src/Rules/Compile.hs
@@ -12,10 +12,6 @@ import Rules.Actions
import Rules.Resources
import Data.Maybe
-matchBuildResult :: FilePath -> String -> FilePath -> Bool
-matchBuildResult buildPath extension file =
- (buildPath <//> "*" ++ extension) ?== file && (isJust . detectWay $ file)
-
compilePackage :: Resources -> StagePackageTarget -> Rules ()
compilePackage _ target = do
let stage = Target.stage target
diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs
new file mode 100644
index 0000000..5bd6551
--- /dev/null
+++ b/src/Rules/Library.hs
@@ -0,0 +1,63 @@
+module Rules.Library (buildPackageLibrary) where
+
+import Way
+import Base
+import Util
+import Builder
+import Switches
+import Expression
+import qualified Target
+import Oracles.PackageData
+import Settings.Util
+import Settings.TargetDirectory
+import Rules.Actions
+import Rules.Resources
+import Data.Maybe
+
+buildPackageLibrary :: Resources -> StagePackageTarget -> Rules ()
+buildPackageLibrary _ target = do
+ let stage = Target.stage target
+ pkg = Target.package target
+ path = targetPath stage pkg
+ buildPath = path -/- "build"
+
+ matchBuildResult buildPath "a" ?> \a -> do
+ liftIO $ removeFiles "." [a]
+ cSrcs <- interpret target $ getPkgDataList CSrcs
+ modules <- interpret target $ getPkgDataList Modules
+
+ let way = fromJust . detectWay $ a -- fromJust is safe
+ hsSrcs = map (replaceEq '.' '/') modules
+ cObjs = [ buildPath -/- src -<.> osuf way | src <- cSrcs ]
+ hsObjs = [ buildPath -/- src <.> osuf way | src <- hsSrcs ]
+
+ need $ cObjs ++ hsObjs -- this will create split objects if required
+
+ splitObjs <- fmap concat $ forM hsSrcs $ \src -> do
+ let files = buildPath -/- src ++ "_" ++ osuf way ++ "_split/*"
+ getDirectoryFiles "" [files]
+
+ split <- interpret target splitObjects
+ let allObjs = if split
+ then cObjs ++ hsObjs ++ splitObjs
+ else cObjs ++ hsObjs
+
+ build $ fullTarget target allObjs Ar [a]
+
+-- ldRule :: Resources -> StagePackageTarget -> Rules ()
+-- ldRule pkg @ (Package name path _ _) todo @ (stage, dist, _) =
+-- let pathDist = path </> dist
+-- buildDir = pathDist </> "build"
+-- in
+-- priority 2 $ (buildDir </> "*.o") %> \out -> do
+-- cObjs <- pkgCObjects path dist vanilla
+-- hObjs <- pkgDepHsObjects path dist vanilla
+-- need $ cObjs ++ hObjs
+-- run Ld $ ldArgs stage (cObjs ++ hObjs) $ unifyPath out
+-- synopsis <- dropWhileEnd isPunctuation <$> showArg (Synopsis pathDist)
+-- putColoured Green $ "/--------\n| Successfully built package '"
+-- ++ name ++ "' (stage " ++ show stage ++ ")."
+-- putColoured Green $ "| Package synopsis: " ++ synopsis ++ "."
+-- ++ "\n\\--------"
+-- -- Finally, record the argument list
+-- need [argListPath argListDir pkg stage]
diff --git a/src/Rules/Package.hs b/src/Rules/Package.hs
index 572fff6..dbbe5cc 100644
--- a/src/Rules/Package.hs
+++ b/src/Rules/Package.hs
@@ -4,8 +4,13 @@ import Base
import Expression
import Rules.Data
import Rules.Compile
+import Rules.Library
import Rules.Resources
import Rules.Dependencies
buildPackage :: Resources -> StagePackageTarget -> Rules ()
-buildPackage = buildPackageData <> buildPackageDependencies <> compilePackage
+buildPackage = mconcat
+ [ buildPackageData
+ , buildPackageDependencies
+ , compilePackage
+ , buildPackageLibrary ]
More information about the ghc-commits
mailing list