[commit: ghc] wip/nfs-locking: Attempt to fix integer-gmp problem on Travis, see #103. (ae6f58d)
git at git.haskell.org
git at git.haskell.org
Thu Oct 26 23:55:22 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/ae6f58daa17dd6ba6bc81cbd19cc1a4f3e082ae8/ghc
>---------------------------------------------------------------
commit ae6f58daa17dd6ba6bc81cbd19cc1a4f3e082ae8
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Tue Jan 5 17:02:55 2016 +0000
Attempt to fix integer-gmp problem on Travis, see #103.
>---------------------------------------------------------------
ae6f58daa17dd6ba6bc81cbd19cc1a4f3e082ae8
src/Rules/Generate.hs | 16 ++++++----------
src/Rules/IntegerGmp.hs | 48 ++++++++++++++++++++++++++++++++----------------
src/Rules/Library.hs | 8 ++++++--
3 files changed, 44 insertions(+), 28 deletions(-)
diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs
index 921c672..2b33a53 100644
--- a/src/Rules/Generate.hs
+++ b/src/Rules/Generate.hs
@@ -14,6 +14,8 @@ import Rules.Generators.GhcVersionH
import Rules.Generators.VersionHs
import Oracles.ModuleFiles
import Rules.Actions
+import Rules.IntegerGmp
+import Rules.Libffi
import Rules.Resources (Resources)
import Settings
import Settings.Builders.DeriveConstants
@@ -33,13 +35,12 @@ includesDependencies = ("includes" -/-) <$>
, "ghcplatform.h"
, "ghcversion.h" ]
-libffiDependencies :: [FilePath]
-libffiDependencies = (targetPath Stage1 rts -/-) <$>
- [ "build/ffi.h"
- , "build/ffitarget.h" ]
+integerGmpDependencies :: [FilePath]
+integerGmpDependencies = [integerGmpLibraryH]
defaultDependencies :: [FilePath]
-defaultDependencies = includesDependencies ++ libffiDependencies
+defaultDependencies =
+ includesDependencies ++ libffiDependencies ++ integerGmpDependencies
derivedConstantsDependencies :: [FilePath]
derivedConstantsDependencies = (derivedConstantsPath -/-) <$>
@@ -69,15 +70,10 @@ compilerDependencies stage =
, "primop-vector-tycons.hs-incl"
, "primop-vector-tys.hs-incl" ]
-integerGmpDependencies :: [FilePath]
-integerGmpDependencies = ((pkgPath integerGmp -/- "gmp") -/-) <$>
- [ "gmp.h" ] -- identical to integerGmpLibraryH, but doesn't require the import.
-
generatedDependencies :: Stage -> Package -> [FilePath]
generatedDependencies stage pkg
| pkg == compiler = compilerDependencies stage
| pkg == rts = derivedConstantsDependencies
- | pkg == integerGmp = integerGmpDependencies
| stage == Stage0 = defaultDependencies
| otherwise = []
diff --git a/src/Rules/IntegerGmp.hs b/src/Rules/IntegerGmp.hs
index 9bbf482..91ca074 100644
--- a/src/Rules/IntegerGmp.hs
+++ b/src/Rules/IntegerGmp.hs
@@ -1,4 +1,4 @@
-module Rules.IntegerGmp (integerGmpRules, integerGmpLibrary, integerGmpLibraryH) where
+module Rules.IntegerGmp (integerGmpRules, integerGmpObjects, integerGmpLibraryH) where
import Base
import Expression
@@ -8,16 +8,25 @@ import Rules.Actions
import Settings.User
integerGmpBase :: FilePath
-integerGmpBase = "libraries" -/- "integer-gmp" -/- "gmp"
+integerGmpBase = "libraries/integer-gmp/gmp"
integerGmpBuild :: FilePath
integerGmpBuild = integerGmpBase -/- "gmpbuild"
+integerGmpObjects :: FilePath
+integerGmpObjects = integerGmpBase -/- "objs"
+
integerGmpLibrary :: FilePath
integerGmpLibrary = integerGmpBase -/- "libgmp.a"
+integerGmpLibraryInTreeH :: FilePath
+integerGmpLibraryInTreeH = integerGmpBase -/- "gmp.h"
+
integerGmpLibraryH :: FilePath
-integerGmpLibraryH = integerGmpBase -/- "gmp.h"
+integerGmpLibraryH = pkgPath integerGmp -/- "include/ghc-gmp.h"
+
+integerGmpLibraryFakeH :: FilePath
+integerGmpLibraryFakeH = integerGmpBase -/- "ghc-gmp.h"
-- relative to integerGmpBuild
integerGmpPatch :: FilePath
@@ -49,12 +58,14 @@ configureArguments = do
-- TODO: we rebuild integer-gmp every time.
integerGmpRules :: Rules ()
integerGmpRules = do
- integerGmpLibrary %> \_ -> do
+
+ -- TODO: split into multiple rules
+ integerGmpLibraryH %> \_ -> do
when trackBuildSystem $ need [sourcePath -/- "Rules/IntegerGmp.hs"]
-- remove the old build folder, if it exists.
liftIO $ removeFiles integerGmpBuild ["//*"]
- liftIO $ removeFiles (integerGmpBase -/- "objs") ["//*"]
+ liftIO $ removeFiles (integerGmpObjects) ["//*"]
-- unpack the gmp tarball.
-- Note: We use a tarball like gmp-4.2.4-nodoc.tar.bz2, which is
@@ -91,19 +102,24 @@ integerGmpRules = do
args <- configureArguments
runConfigure integerGmpBuild envs args
- runMake integerGmpBuild []
+ -- check whether we need to build in tree gmp
+ -- this is indicated by line "HaveFrameworkGMP = YES" in `config.mk`
+ configMk <- liftIO . readFile $ integerGmpBase -/- "config.mk"
+ if "HaveFrameworkGMP = YES" `isInfixOf` configMk
+ then do
+ putBuild "\n| GMP framework detected and will be used"
+ copyFile integerGmpLibraryFakeH integerGmpLibraryH
+ else do
+ putBuild "\n| No GMP framework detected"
+ runMake integerGmpBuild []
- -- copy library and header
- -- TODO: why copy library, can we move it instead?
- forM_ ["gmp.h", ".libs" -/- "libgmp.a"] $ \file ->
- copyFile (integerGmpBuild -/- file) (integerGmpBase -/- takeFileName file)
+ copyFile integerGmpLibraryInTreeH integerGmpLibraryH
+ -- TODO: why copy library, can we move it instead?
+ copyFile (integerGmpBuild -/- ".libs/libgmp.a") integerGmpLibrary
- let objsDir = integerGmpBase -/- "objs"
- createDirectory objsDir
- build $ fullTarget target Ar [integerGmpLibrary] [objsDir]
+ createDirectory integerGmpObjects
+ build $ fullTarget target Ar [integerGmpLibrary] [integerGmpObjects]
- runBuilder Ranlib [integerGmpLibrary]
+ runBuilder Ranlib [integerGmpLibrary]
putSuccess "| Successfully built custom library 'integer-gmp'"
-
- integerGmpLibraryH %> \_ -> need [integerGmpLibrary]
diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs
index d9a1a48..41e7b3d 100644
--- a/src/Rules/Library.hs
+++ b/src/Rules/Library.hs
@@ -79,6 +79,10 @@ hSources target = do
extraObjects :: PartialTarget -> Action [FilePath]
extraObjects (PartialTarget _ pkg)
| pkg == integerGmp = do
- need [integerGmpLibrary]
- getDirectoryFiles "" [pkgPath pkg -/- "gmp/objs/*.o"]
+ need [integerGmpLibraryH]
+ objsExist <- doesDirectoryExist integerGmpObjects
+ putBuild $ "objsExist = " ++ show objsExist
+ if objsExist
+ then getDirectoryFiles "" [integerGmpObjects -/- "*.o"]
+ else return []
| otherwise = return []
More information about the ghc-commits
mailing list