[commit: ghc] wip/nfs-locking: Adds Rules for IntegerGmp (94f5e79)

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


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

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

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

commit 94f5e79a5947dca7fa4719f79f8892fa18d88f33
Author: Moritz Angermann <moritz.angermann at gmail.com>
Date:   Sun Jan 3 18:48:04 2016 +0800

    Adds Rules for IntegerGmp
    
    This should fix #71. We build the integer-gmp library similary to libffi now.


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

94f5e79a5947dca7fa4719f79f8892fa18d88f33
 shaking-up-ghc.cabal    |   1 +
 src/Main.hs             |   2 +
 src/Rules/IntegerGmp.hs | 112 ++++++++++++++++++++++++++++++++++++++++++++++++
 3 files changed, 115 insertions(+)

diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal
index 3f91f30..334cd59 100644
--- a/shaking-up-ghc.cabal
+++ b/shaking-up-ghc.cabal
@@ -49,6 +49,7 @@ executable ghc-shake
                        , Rules.Generators.GhcPlatformH
                        , Rules.Generators.GhcVersionH
                        , Rules.Generators.VersionHs
+                       , Rules.IntegerGmp
                        , Rules.Libffi
                        , Rules.Library
                        , Rules.Oracles
diff --git a/src/Main.hs b/src/Main.hs
index 82f0072..043e173 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -5,6 +5,7 @@ import Rules.Config
 import Rules.Generate
 import Rules.Copy
 import Rules.Libffi
+import Rules.IntegerGmp
 import Rules.Oracles
 
 main :: IO ()
@@ -15,6 +16,7 @@ main = shakeArgs options $ do
     generateTargets -- see Rules
     generateRules   -- see Rules.Generate
     libffiRules     -- see Rules.Libffi
+    integerGmpRules -- see Rules.IntegerGmp
     oracleRules     -- see Rules.Oracles
     packageRules    -- see Rules
   where
diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs
new file mode 100644
index 0000000..443b912
--- /dev/null
+++ b/src/Rules/IntegerGmp.hs
@@ -0,0 +1,112 @@
+module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary) where
+
+import System.Directory
+
+import Base
+import Expression
+import GHC
+import Oracles.Config.Setting
+import Rules.Actions
+
+integerGmpBase :: FilePath
+integerGmpBase = "libraries" -/- "integer-gmp" -/- "gmp"
+
+integerGmpBuild :: FilePath
+integerGmpBuild = integerGmpBase -/- "gmpbuild"
+
+integerGmpLibrary :: FilePath
+integerGmpLibrary = integerGmpBase -/- "libgmp.a"
+
+-- relative to integerGmpBuild
+integerGmpPatch :: FilePath
+integerGmpPatch = ".." -/- "tarball" -/- "gmp-5.0.4.patch"
+
+target :: PartialTarget
+target = PartialTarget Stage0 integerGmp
+
+-- TODO: See Libffi.hs about removing code duplication.
+configureEnvironment :: Action [CmdOption]
+configureEnvironment = do
+    sequence [ builderEnv "CC" $ Gcc Stage1
+             , builderEnv "CXX" $ Gcc Stage1
+             , builderEnv "AR" Ar
+             , builderEnv "NM" Nm]
+  where
+    builderEnv var builder = do
+        needBuilder False builder
+        path <- builderPath builder
+        return $ AddEnv var path
+
+configureArguments :: Action [String]
+configureArguments = do
+    hostPlatform  <- setting HostPlatform
+    buildPlatform <- setting BuildPlatform
+    return [ "--enable-shared=no"
+           , "--host=" ++ hostPlatform
+           , "--build=" ++ buildPlatform]
+
+-- TODO: we rebuild integer-gmp every time.
+integerGmpRules :: Rules ()
+integerGmpRules = do
+    integerGmpLibrary %> \_ -> do
+        need [sourcePath -/- "Rules" -/- "integerGmp.hs"]
+
+        -- remove the old build folder, if it exists.
+        liftIO $ removeFiles integerGmpBuild ["//*"]
+
+        -- unpack the gmp tarball.
+        -- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is
+        -- gmp-4.2.4.tar.bz2 repacked without the doc/ directory contents.
+        -- That's because the doc/ directory contents are under the GFDL,
+        -- which causes problems for Debian.
+        tarballs <- getDirectoryFiles "" [integerGmpBase -/- "tarball/gmp*.tar.bz2"]
+        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
+
+        -- 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
+
+        -- 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
+
+        -- make
+        putBuild "| Running make..."
+        unit $ cmd Shell "make" ["-C", integerGmpBuild, "MAKEFLAGS="]
+
+        -- 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'
+
+        -- TODO: do we need these as well?
+        -- mkdir integerGmpBase -/- objs
+        -- unit $ cmd Shell [Cwd integerGmpBase -/- "objs"] "$AR_STAGE1 x ../libgmp.a"
+        -- $RANLIB_CMD integerGmpBase -/- "libgmp.a"
+
+        putSuccess "| Successfully build custom library 'integer-gmp'"
+
+    "libraries/integer-gmp/gmp/gmp.h" %> \_ -> need [integerGmpLibrary]



More information about the ghc-commits mailing list