[commit: ghc] wip/nfs-locking: Refactor Gmp and Libffi rules. (f0781a7)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:58:54 UTC 2017


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

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

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

commit f0781a7c0c1124d7e0150298ca39b08a849ac338
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Thu May 5 05:30:22 2016 +0100

    Refactor Gmp and Libffi rules.


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

f0781a7c0c1124d7e0150298ca39b08a849ac338
 src/Builder.hs      |  9 ++++++++-
 src/Rules/Gmp.hs    | 22 +++++++---------------
 src/Rules/Libffi.hs | 18 +++++++-----------
 3 files changed, 22 insertions(+), 27 deletions(-)

diff --git a/src/Builder.hs b/src/Builder.hs
index fa76097..a205067 100644
--- a/src/Builder.hs
+++ b/src/Builder.hs
@@ -1,7 +1,7 @@
 {-# LANGUAGE DeriveGeneric, LambdaCase #-}
 module Builder (
     CompilerMode (..), Builder (..),
-    builderPath, getBuilderPath, specified, needBuilder
+    builderPath, getBuilderPath, builderEnvironment, specified, needBuilder
     ) where
 
 import Control.Monad.Trans.Reader
@@ -134,6 +134,13 @@ builderPath builder = case builderProvenance builder of
 getBuilderPath :: Builder -> ReaderT a Action FilePath
 getBuilderPath = lift . builderPath
 
+-- | Write a Builder's path into a given environment variable.
+builderEnvironment :: String -> Builder -> Action CmdOption
+builderEnvironment variable builder = do
+    needBuilder builder
+    path <- builderPath builder
+    return $ AddEnv variable path
+
 specified :: Builder -> Action Bool
 specified = fmap (not . null) . builderPath
 
diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs
index 2de1878..1121d5d 100644
--- a/src/Rules/Gmp.hs
+++ b/src/Rules/Gmp.hs
@@ -1,6 +1,7 @@
 module Rules.Gmp (gmpRules) where
 
 import Base
+import Builder
 import Expression
 import GHC
 import Oracles.Config.Setting
@@ -11,31 +12,22 @@ import Settings.Paths
 import Target
 
 gmpBase :: FilePath
-gmpBase = "libraries/integer-gmp/gmp"
+gmpBase = pkgPath integerGmp -/- "gmp"
 
 gmpContext :: Context
 gmpContext = vanillaContext Stage1 integerGmp
 
+-- TODO: Noone needs this file, but we build it. Why?
 gmpLibraryInTreeH :: FilePath
 gmpLibraryInTreeH = gmpBuildPath -/- "include/gmp.h"
 
-gmpLibraryFakeH :: FilePath
-gmpLibraryFakeH = gmpBase -/- "ghc-gmp.h"
-
 gmpPatches :: [FilePath]
 gmpPatches = (gmpBase -/-) <$> ["gmpsrc.patch", "tarball/gmp-5.0.4.patch"]
 
--- TODO: See Libffi.hs about removing code duplication.
 configureEnvironment :: Action [CmdOption]
-configureEnvironment = do
-    sequence [ builderEnv "CC" $ Cc Compile Stage1
-             , builderEnv "AR" Ar
-             , builderEnv "NM" Nm ]
-  where
-    builderEnv var bld = do
-        needBuilder bld
-        path <- builderPath bld
-        return $ AddEnv var path
+configureEnvironment = sequence [ builderEnvironment "CC" $ Cc Compile Stage1
+                                , builderEnvironment "AR" Ar
+                                , builderEnvironment "NM" Nm ]
 
 -- TODO: we rebuild gmp every time.
 gmpRules :: Rules ()
@@ -53,7 +45,7 @@ gmpRules = do
         then do
             putBuild "| GMP library/framework detected and will be used"
             createDirectory $ takeDirectory gmpLibraryH
-            copyFile gmpLibraryFakeH gmpLibraryH
+            copyFile (gmpBase -/- "ghc-gmp.h") gmpLibraryH
         else do
             putBuild "| No GMP library/framework detected; in tree GMP will be built"
 
diff --git a/src/Rules/Libffi.hs b/src/Rules/Libffi.hs
index 424b552..0a000aa 100644
--- a/src/Rules/Libffi.hs
+++ b/src/Rules/Libffi.hs
@@ -1,6 +1,7 @@
 module Rules.Libffi (rtsBuildPath, libffiRules, libffiDependencies) where
 
 import Base
+import Builder
 import Expression
 import GHC
 import Oracles.Config.Flag
@@ -43,19 +44,14 @@ configureEnvironment = do
                [ cArgs
                , argStagedSettingList ConfCcArgs ]
     ldFlags <- interpretInContext libffiContext $ fromDiffExpr ldArgs
-    sequence [ builderEnv "CC" $ Cc Compile Stage1
-             , builderEnv "CXX" $ Cc Compile Stage1
-             , builderEnv "LD" Ld
-             , builderEnv "AR" Ar
-             , builderEnv "NM" Nm
-             , builderEnv "RANLIB" Ranlib
+    sequence [ builderEnvironment "CC" $ Cc Compile Stage1
+             , builderEnvironment "CXX" $ Cc Compile Stage1
+             , builderEnvironment "LD" Ld
+             , builderEnvironment "AR" Ar
+             , builderEnvironment "NM" Nm
+             , builderEnvironment "RANLIB" Ranlib
              , return . AddEnv  "CFLAGS" $ unwords  cFlags ++ " -w"
              , return . AddEnv "LDFLAGS" $ unwords ldFlags ++ " -w" ]
-  where
-    builderEnv var b = do
-        needBuilder b
-        path <- builderPath b
-        return $ AddEnv var path
 
 -- TODO: remove code duplication (need sourcePath)
 -- TODO: split into multiple rules



More information about the ghc-commits mailing list