[commit: ghc] wip/nfs-locking: Clean up build rules for custom packages. (1c3c9f3)

git at git.haskell.org git at git.haskell.org
Thu Oct 26 23:52:38 UTC 2017


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

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

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

commit 1c3c9f3438f0fbd80ff476f63e253ecf0355920a
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Mon Jan 4 01:34:17 2016 +0000

    Clean up build rules for custom packages.


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

1c3c9f3438f0fbd80ff476f63e253ecf0355920a
 src/Rules/IntegerGmp.hs | 64 +++++++++++++++++++++----------------------------
 src/Rules/Libffi.hs     | 31 ++++++++----------------
 2 files changed, 37 insertions(+), 58 deletions(-)

diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs
index 1f50dc0..4e19b9d 100644
--- a/src/Rules/IntegerGmp.hs
+++ b/src/Rules/IntegerGmp.hs
@@ -1,12 +1,11 @@
 module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary) where
 
-import System.Directory
-
 import Base
 import Expression
 import GHC
 import Oracles.Config.Setting
 import Rules.Actions
+import Settings.User
 
 integerGmpBase :: FilePath
 integerGmpBase = "libraries" -/- "integer-gmp" -/- "gmp"
@@ -28,9 +27,8 @@ target = PartialTarget Stage0 integerGmp
 configureEnvironment :: Action [CmdOption]
 configureEnvironment = do
     sequence [ builderEnv "CC" $ Gcc Stage1
-             , builderEnv "CXX" $ Gcc Stage1
              , builderEnv "AR" Ar
-             , builderEnv "NM" Nm]
+             , builderEnv "NM" Nm ]
   where
     builderEnv var builder = do
         needBuilder False builder
@@ -49,7 +47,7 @@ configureArguments = do
 integerGmpRules :: Rules ()
 integerGmpRules = do
     integerGmpLibrary %> \_ -> do
-        need [sourcePath -/- "Rules" -/- "integerGmp.hs"]
+        when trackBuildSystem $ need [sourcePath -/- "Rules" -/- "integerGmp.hs"]
 
         -- remove the old build folder, if it exists.
         liftIO $ removeFiles integerGmpBuild ["//*"]
@@ -64,53 +62,45 @@ integerGmpRules = do
         when (length tarballs /= 1) $
             putError $ "integerGmpRules: exactly one tarball expected"
                      ++ "(found: " ++ show tarballs ++ ")."
-        let filename = dropExtension . dropExtension . takeFileName $ head tarballs
-        let suffix = "-nodoc-patched"
-        unless (suffix `isSuffixOf` filename) $
-            putError $ "integerGmpRules: expected suffix " ++ suffix
-                     ++ " (found: " ++ filename ++ ")."
-        let libname = take (length filename - length suffix) filename
 
         need tarballs
         build $ fullTarget target Tar tarballs [integerGmpBase]
 
         -- move gmp-<version> to gmpbuild
-        let integerGmpExtracted = integerGmpBase -/- libname
-        liftIO $ renameDirectory integerGmpExtracted integerGmpBuild
-        putBuild $ "| Move " ++ integerGmpExtracted ++ " -> " ++ integerGmpBuild
+        let filename = dropExtension . dropExtension . takeFileName $ head tarballs
+            suffix   = "-nodoc-patched"
+        unless (suffix `isSuffixOf` filename) $
+            putError $ "integerGmpRules: expected suffix " ++ suffix
+                     ++ " (found: " ++ filename ++ ")."
+        let libname = take (length filename - length suffix) filename
+        moveDirectory (integerGmpBase -/- libname) integerGmpBuild
 
         -- apply patches
         -- TODO: replace "patch" with PATCH_CMD
-        unit $ cmd Shell [Cwd integerGmpBase] "patch -p0 < gmpsrc.patch"
-        unit $ cmd Shell [Cwd integerGmpBuild] "patch -p1 < " [integerGmpPatch]
-        putBuild $ "| Applied gmpsrc.patch and " ++ takeFileName integerGmpPatch
+        unit . quietly $ cmd Shell (EchoStdout False) [Cwd integerGmpBase] "patch -p0 < gmpsrc.patch"
+        putBuild $ "| Apply " ++ (integerGmpBase -/- "gmpsrc.patch")
+        unit . quietly $ cmd Shell (EchoStdout False) [Cwd integerGmpBuild] "patch -p1 < " [integerGmpPatch]
+        putBuild $ "| Apply " ++ (integerGmpBase -/- integerGmpPatch)
 
         -- TODO: What's `chmod +x libraries/integer-gmp/gmp/ln` for?
 
-        -- ./configure
-        putBuild "| Running libffi configure..."
         envs <- configureEnvironment
         args <- configureArguments
-        unit $ cmd Shell [Cwd integerGmpBuild] "bash configure" envs args
+        runConfigure integerGmpBuild envs args
 
-        -- make
-        putBuild "| Running make..."
-        unit $ cmd Shell "make" ["-C", integerGmpBuild, "MAKEFLAGS="]
+        runMake integerGmpBuild []
 
         -- copy library and header
-        forM_ ["gmp.h", ".libs" -/- "libgmp.a"] $ \file -> do
-            let file' = integerGmpBase -/- takeFileName file
-            copyFileChanged (integerGmpBuild -/- file) file'
-            putBuild $ "| Copy " ++ file ++ " -> " ++ file'
-
-        ar  <- builderPath Ar
-        ran <- builderPath Ranlib
-        -- unpack libgmp.a
-        putBuild "| Unpacking libgmp.a..."
-        unit $ cmd Shell [Cwd integerGmpBase] "mkdir -p objs"
-        unit $ cmd Shell [Cwd (integerGmpBase -/- "objs")] [ar] " x ../libgmp.a"
-        unit $ cmd Shell [Cwd integerGmpBase] [ran] " libgmp.a"
-
-        putSuccess "| Successfully build custom library 'integer-gmp'"
+        -- TODO: why copy library, can we move it instead?
+        forM_ ["gmp.h", ".libs" -/- "libgmp.a"] $ \file ->
+            copyFile (integerGmpBuild -/- file) (integerGmpBase -/- takeFileName file)
+
+        let objsDir = integerGmpBase -/- "objs"
+        createDirectory objsDir
+        build $ fullTarget target Ar [integerGmpLibrary] [objsDir]
+
+        runBuilder Ranlib [integerGmpLibrary]
+
+        putSuccess "| Successfully built custom library 'integer-gmp'"
 
     "libraries/integer-gmp/gmp/gmp.h" %> \_ -> need [integerGmpLibrary]
diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs
index f5f2668..93a20ab 100644
--- a/src/Rules/Libffi.hs
+++ b/src/Rules/Libffi.hs
@@ -1,13 +1,12 @@
 module Rules.Libffi (libffiRules, libffiLibrary) where
 
-import System.Directory
-
 import Base
 import Expression
 import GHC
 import Oracles.Config.Setting
 import Rules.Actions
 import Settings.Builders.Common
+import Settings.User
 
 -- We use this file to track the whole libffi library
 libffiLibrary :: FilePath
@@ -63,40 +62,30 @@ configureArguments = do
 libffiRules :: Rules ()
 libffiRules = do
     libffiLibrary %> \_ -> do
-        need [sourcePath -/- "Rules/Libffi.hs"]
+        when trackBuildSystem $ need [sourcePath -/- "Rules/Libffi.hs"]
         liftIO $ removeFiles libffiBuild ["//*"]
         tarballs <- getDirectoryFiles "" ["libffi-tarballs/libffi*.tar.gz"]
         when (length tarballs /= 1) $
             putError $ "libffiRules: exactly one libffi tarball expected"
                      ++ "(found: " ++ show tarballs ++ ")."
-        let libname = dropExtension . dropExtension . takeFileName $ head tarballs
 
         need tarballs
         build $ fullTarget target Tar tarballs ["libffi-tarballs"]
 
-        let libffiExtracted = "libffi-tarballs" -/- libname
-        liftIO $ renameDirectory libffiExtracted libffiBuild
-        putBuild $ "| Move " ++ libffiExtracted ++ " -> " ++ libffiBuild
+        let libname = dropExtension . dropExtension . takeFileName $ head tarballs
+        moveDirectory ("libffi-tarballs" -/- libname) libffiBuild
 
-        old <- liftIO $ readFile libffiMakefile
-        let new = fixLibffiMakefile old
-        length new `seq` liftIO $ writeFile libffiMakefile new
-        putBuild $ "| Fix " ++ libffiMakefile
+        fixFile libffiMakefile fixLibffiMakefile
 
-        forM_ ["config.guess", "config.sub"] $ \file -> do
-            copyFileChanged file $ libffiBuild -/- file
-            putBuild $ "| Copy " ++ file ++ " -> " ++ (libffiBuild -/- file)
+        forM_ ["config.guess", "config.sub"] $ \file ->
+            copyFile file (libffiBuild -/- file)
 
-        putBuild $ "| Running libffi configure..."
         envs <- configureEnvironment
         args <- configureArguments
-        unit $ cmd Shell [Cwd libffiBuild] "bash configure" envs args
-
-        putBuild $ "| Running make..."
-        unit $ cmd Shell "make" ["-C", libffiBuild, "MAKEFLAGS="]
+        runConfigure libffiBuild envs args
 
-        putBuild $ "| Running make install..."
-        unit $ cmd Shell "make" ["-C", libffiBuild, "MAKEFLAGS= install"]
+        runMake libffiBuild []
+        runMake libffiBuild ["install"]
 
         putSuccess $ "| Successfully built custom library 'libffi'"
 



More information about the ghc-commits mailing list