[commit: ghc] wip/nfs-locking: Drop orderOnly dependency on GMP objects (19293d9)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 01:02:55 UTC 2017


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

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

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

commit 19293d92469d2c80e125f62d527407ea0ac5fe4e
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Sun May 22 01:19:16 2016 +0100

    Drop orderOnly dependency on GMP objects


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

19293d92469d2c80e125f62d527407ea0ac5fe4e
 src/Rules/Gmp.hs     |  2 +-
 src/Rules/Library.hs | 12 ++++++------
 2 files changed, 7 insertions(+), 7 deletions(-)

diff --git a/src/Rules/Gmp.hs b/src/Rules/Gmp.hs
index 845ba6e..f761639 100644
--- a/src/Rules/Gmp.hs
+++ b/src/Rules/Gmp.hs
@@ -1,4 +1,4 @@
-module Rules.Gmp (gmpRules) where
+module Rules.Gmp (gmpRules, gmpContext) where
 
 import Base
 import Builder
diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs
index 2e59755..edbdb52 100644
--- a/src/Rules/Library.hs
+++ b/src/Rules/Library.hs
@@ -8,9 +8,9 @@ import qualified System.Directory as IO
 import Base
 import Context
 import Expression
-import GHC
 import Oracles.PackageData
 import Rules.Actions
+import Rules.Gmp
 import Settings
 import Target
 
@@ -75,7 +75,7 @@ buildPackageGhciLibrary context at Context {..} = priority 2 $ do
             build $ Target context Ld objs [obj]
 
 -- TODO: Get rid of code duplication and simplify. See also src2dep.
--- Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath'
+-- | Given a 'Context' and a 'FilePath' to a source file, compute the 'FilePath'
 -- to its object file. For example, in Context Stage1 rts threaded:
 -- * "Task.c"                          -> "_build/stage1/rts/Task.thr_o"
 -- * "_build/stage1/rts/sm/Evac_thr.c" -> "_build/stage1/rts/sm/Evac_thr.thr_o"
@@ -90,12 +90,12 @@ cSources context = interpretInContext context $ getPkgDataList CSrcs
 hSources :: Context -> Action [FilePath]
 hSources context = do
     modules <- interpretInContext context $ getPkgDataList Modules
-    -- GHC.Prim is special: we do not build it
+    -- GHC.Prim is special: we do not build it.
     return . map (replaceEq '.' '/') . filter (/= "GHC.Prim") $ modules
 
 extraObjects :: Context -> Action [FilePath]
-extraObjects (Context _ package _)
-    | package == integerGmp = do
-        orderOnly [gmpLibraryH] -- TODO: move this dependency elsewhere, #113?
+extraObjects context
+    | context == gmpContext = do
+        need [gmpLibraryH] -- TODO: Move this dependency elsewhere, #113?
         map unifyPath <$> getDirectoryFiles "" [gmpObjects -/- "*.o"]
     | otherwise         = return []



More information about the ghc-commits mailing list