[commit: ghc] wip/nfs-locking: Drop experimental code for #174. (64ae7fe)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:08:41 UTC 2017


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

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

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

commit 64ae7fe8fd907dffd6b6221b95111d24f1bf6372
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Tue Apr 26 00:25:12 2016 +0100

    Drop experimental code for #174.


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

64ae7fe8fd907dffd6b6221b95111d24f1bf6372
 src/Rules/Compile.hs         | 24 ++++--------------------
 src/Settings/Builders/Ghc.hs | 12 ++++--------
 src/Settings/User.hs         | 13 ++++---------
 3 files changed, 12 insertions(+), 37 deletions(-)

diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs
index a3c970d..93503bd 100644
--- a/src/Rules/Compile.hs
+++ b/src/Rules/Compile.hs
@@ -12,21 +12,9 @@ compilePackage :: [(Resource, Int)] -> Context -> Rules ()
 compilePackage rs context at Context {..} = do
     let path = buildPath context
 
-    path <//> "*" <.> hisuf way %> \hi ->
-        if compileInterfaceFilesSeparately
-        then do
-            (src, deps) <- dependencies path $ hi -<.> osuf way
-            need $ src : deps
-            buildWithResources rs $ Target context (Ghc Compile stage) [src] [hi]
-        else need [ hi -<.> osuf way ]
+    path <//> "*" <.> hisuf way %> \hi -> need [ hi -<.> osuf way ]
 
-    path <//> "*" <.> hibootsuf way %> \hiboot ->
-        if compileInterfaceFilesSeparately
-        then do
-            (src, deps) <- dependencies path $ hiboot -<.> obootsuf way
-            need $ src : deps
-            buildWithResources rs $ Target context (Ghc Compile stage) [src] [hiboot]
-        else need [ hiboot -<.> obootsuf way ]
+    path <//> "*" <.> hibootsuf way %> \hiboot -> need [ hiboot -<.> obootsuf way ]
 
     -- TODO: add dependencies for #include of .h and .hs-incl files (gcc -MM?)
     path <//> "*" <.> osuf way %> \obj -> do
@@ -36,15 +24,11 @@ compilePackage rs context at Context {..} = do
             need $ src : deps
             build $ Target context (Cc Compile stage) [src] [obj]
         else do
-            if compileInterfaceFilesSeparately && "//*.hs" ?== src
-            then need $ (obj -<.> hisuf way) : src : deps
-            else need $ src : deps
+            need $ src : deps
             buildWithResources rs $ Target context (Ghc Compile stage) [src] [obj]
 
     -- TODO: get rid of these special cases
     path <//> "*" <.> obootsuf way %> \obj -> do
         (src, deps) <- dependencies path obj
-        if compileInterfaceFilesSeparately
-        then need $ (obj -<.> hibootsuf way) : src : deps
-        else need $ src : deps
+        need $ src : deps
         buildWithResources rs $ Target context (Ghc Compile stage) [src] [obj]
diff --git a/src/Settings/Builders/Ghc.hs b/src/Settings/Builders/Ghc.hs
index 7152526..8dabda6 100644
--- a/src/Settings/Builders/Ghc.hs
+++ b/src/Settings/Builders/Ghc.hs
@@ -18,16 +18,13 @@ import Settings.Builders.Common (cIncludeArgs)
 --     $$(call cmd,$1_$2_HC) $$($1_$2_$3_ALL_HC_OPTS) -c $$< -o $$@
 --     $$(if $$(findstring YES,$$($1_$2_DYNAMIC_TOO)),-dyno
 --     $$(addsuffix .$$(dyn_osuf)-boot,$$(basename $$@)))
--- TODO: Simplify
 ghcBuilderArgs :: Args
 ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do
     output <- getOutput
     stage  <- getStage
     way    <- getWay
     when (stage > Stage0) . lift $ needTouchy
-    let buildObj  = any (\s -> ("//*." ++ s way) ?== output) [ osuf,  obootsuf]
-        buildHi   = any (\s -> ("//*." ++ s way) ?== output) [hisuf, hibootsuf]
-        buildProg = not (buildObj || buildHi)
+    let buildObj = any (\s -> ("//*." ++ s way) ?== output) [ osuf,  obootsuf]
     mconcat [ commonGhcArgs
             , arg "-H32m"
             , stage0    ? arg "-O"
@@ -35,11 +32,10 @@ ghcBuilderArgs = (stagedBuilder (Ghc Compile) ||^ stagedBuilder (Ghc Link)) ? do
             , arg "-Wall"
             , arg "-fwarn-tabs"
             , splitObjectsArgs
-            , buildProg ? ghcLinkArgs
-            , not buildProg ? arg "-c"
+            , not buildObj ? ghcLinkArgs
+            , buildObj ? arg "-c"
             , append =<< getInputs
-            , buildHi ? append ["-fno-code", "-fwrite-interface"]
-            , not buildHi ? mconcat [ arg "-o", arg =<< getOutput ] ]
+            , arg "-o", arg =<< getOutput ]
 
 ghcLinkArgs :: Args
 ghcLinkArgs = stagedBuilder (Ghc Link) ? do
diff --git a/src/Settings/User.hs b/src/Settings/User.hs
index 6fc5536..9f2302b 100644
--- a/src/Settings/User.hs
+++ b/src/Settings/User.hs
@@ -1,9 +1,8 @@
 module Settings.User (
-    buildRootPath, trackBuildSystem, compileInterfaceFilesSeparately,
-    userArgs, userPackages, userLibraryWays, userRtsWays, userKnownPackages,
-    integerLibrary, buildHaddock, validating, ghciWithDebugger, ghcProfiled,
-    ghcDebugged, dynamicGhcPrograms, laxDependencies, verboseCommands,
-    turnWarningsIntoErrors, splitObjects
+    buildRootPath, trackBuildSystem, userArgs, userPackages, userLibraryWays,
+    userRtsWays, userKnownPackages, integerLibrary, buildHaddock, validating,
+    ghciWithDebugger, ghcProfiled, ghcDebugged, dynamicGhcPrograms,
+    laxDependencies, verboseCommands, turnWarningsIntoErrors, splitObjects
     ) where
 
 import Base
@@ -94,7 +93,3 @@ verboseCommands = return False
 -- | To enable -Werror in Stage2 set turnWarningsIntoErrors = stage2.
 turnWarningsIntoErrors :: Predicate
 turnWarningsIntoErrors = return False
-
--- | Decouple the compilation of @*.hi@ and @*.o@ files by setting to True.
-compileInterfaceFilesSeparately :: Bool
-compileInterfaceFilesSeparately = False



More information about the ghc-commits mailing list