[commit: ghc] master: Drop custom logic for Scav_thr and Evac_thr (#497) (1232d26)

git at git.haskell.org git at git.haskell.org
Tue Oct 23 20:13:05 UTC 2018


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/1232d26576eb156301aedab77f17d509c6887c48/ghc

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

commit 1232d26576eb156301aedab77f17d509c6887c48
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Sun Feb 4 02:31:10 2018 +0000

    Drop custom logic for Scav_thr and Evac_thr (#497)
    
    See https://phabricator.haskell.org/D3237


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

1232d26576eb156301aedab77f17d509c6887c48
 doc/user-settings.md             |  2 +-
 src/Rules/Compile.hs             |  2 +-
 src/Rules/Generate.hs            |  9 ++-------
 src/Rules/Library.hs             |  5 +----
 src/Rules/PackageData.hs         |  4 +---
 src/Settings/Builders/RunTest.hs |  2 --
 src/Settings/Packages/Rts.hs     | 14 ++++++--------
 7 files changed, 12 insertions(+), 26 deletions(-)

diff --git a/doc/user-settings.md b/doc/user-settings.md
index e800d51..1a89dd4 100644
--- a/doc/user-settings.md
+++ b/doc/user-settings.md
@@ -87,7 +87,7 @@ You can combine several custom command line settings using `mconcat`:
 userArgs :: Args
 userArgs = mconcat
     [ builder Ghc ? package cabal ? arg "-O0"
-    , package rts ? input "//Evac_thr.c" ? pure [ "-DPARALLEL_GC", "-Irts/sm" ] ]
+    , package rts ? input "//PrimOps.c" ? pure ["-fno-PIC", "-static"] ]
 ```
 You can match any combination of the `builder`, `stage`, `package`, `way`, `input`
 and `output` predicates when specifying custom command line arguments. File
diff --git a/src/Rules/Compile.hs b/src/Rules/Compile.hs
index b7f3bc8..8bca888 100644
--- a/src/Rules/Compile.hs
+++ b/src/Rules/Compile.hs
@@ -25,7 +25,7 @@ compilePackage rs context at Context {..} = do
             buildWithResources rs $ target context (Ghc CompileHs stage) [src] [obj]
 
     priority 2.0 $ do
-        nonHs "c"   %> compile (Ghc CompileCWithGhc) (obj2src "c"   isGeneratedCFile  )
+        nonHs "c"   %> compile (Ghc CompileCWithGhc) (obj2src "c"   $ const False     )
         nonHs "cmm" %> compile (Ghc CompileHs)       (obj2src "cmm" isGeneratedCmmFile)
         nonHs "s"   %> compile (Ghc CompileHs)       (obj2src "S"   $ const False     )
 
diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs
index 8616da0..a8f3956 100644
--- a/src/Rules/Generate.hs
+++ b/src/Rules/Generate.hs
@@ -1,6 +1,6 @@
 module Rules.Generate (
-    isGeneratedCFile, isGeneratedCmmFile, generatePackageCode, generateRules,
-    copyRules, includesDependencies, generatedDependencies
+    isGeneratedCmmFile, generatePackageCode, generateRules, copyRules,
+    includesDependencies, generatedDependencies
     ) where
 
 import Base
@@ -29,9 +29,6 @@ primopsTxt stage = contextDir (vanillaContext stage compiler) -/- "primops.txt"
 platformH :: Stage -> FilePath
 platformH stage = contextDir (vanillaContext stage compiler) -/- "ghc_boot_platform.h"
 
-isGeneratedCFile :: FilePath -> Bool
-isGeneratedCFile file = takeBaseName file `elem` ["Evac_thr", "Scav_thr"]
-
 isGeneratedCmmFile :: FilePath -> Bool
 isGeneratedCmmFile file = takeBaseName file == "AutoApply"
 
@@ -155,8 +152,6 @@ copyRules = do
     (inplaceLibPath -/- "platformConstants") <~ (buildRoot <&> (-/- generatedDir))
     (inplaceLibPath -/- "settings")          <~ return "."
     (inplaceLibPath -/- "template-hsc.h")    <~ return (pkgPath hsc2hs)
-    "//c/sm/Evac_thr.c" %> copyFile (pkgPath rts -/- "sm/Evac.c")
-    "//c/sm/Scav_thr.c" %> copyFile (pkgPath rts -/- "sm/Scav.c")
   where
     pattern <~ mdir = pattern %> \file -> do
         dir <- mdir
diff --git a/src/Rules/Library.hs b/src/Rules/Library.hs
index e6e5b16..7b7a179 100644
--- a/src/Rules/Library.hs
+++ b/src/Rules/Library.hs
@@ -89,10 +89,7 @@ cObjects :: Context -> Action [FilePath]
 cObjects context = do
     path <- buildPath context
     srcs <- pkgDataList (CSrcs path)
-    objs <- mapM (objectPath context) srcs
-    return $ if way context == threaded
-        then objs
-        else filter ((`notElem` ["Evac_thr", "Scav_thr"]) . takeBaseName) objs
+    mapM (objectPath context) srcs
 
 extraObjects :: Context -> Action [FilePath]
 extraObjects context
diff --git a/src/Rules/PackageData.hs b/src/Rules/PackageData.hs
index 2442b03..32a9117 100644
--- a/src/Rules/PackageData.hs
+++ b/src/Rules/PackageData.hs
@@ -75,12 +75,10 @@ packageCSources pkg
     | pkg /= rts = getDirectoryFiles (pkgPath pkg) ["*.c"]
     | otherwise  = do
         windows <- windowsHost
-        rtsPath <- rtsBuildPath
         sources <- fmap (map unifyPath) . getDirectoryFiles (pkgPath pkg) .
             map (-/- "*.c") $ [ ".", "hooks", "sm", "eventlog", "linker" ] ++
                               [ if windows then "win32" else "posix"     ]
-        return $ sources ++ [ rtsPath -/- "c/sm/Evac_thr.c" ]
-                         ++ [ rtsPath -/- "c/sm/Scav_thr.c" ]
+        return sources
 
 packageAsmSources :: Package -> Action [FilePath]
 packageAsmSources pkg
diff --git a/src/Settings/Builders/RunTest.hs b/src/Settings/Builders/RunTest.hs
index 1f70a03..3094e8d 100644
--- a/src/Settings/Builders/RunTest.hs
+++ b/src/Settings/Builders/RunTest.hs
@@ -1,12 +1,10 @@
 module Settings.Builders.RunTest (runTestBuilderArgs) where
 
 import Hadrian.Utilities
-import Hadrian.Haskell.Cabal
 
 import Flavour
 import Rules.Test
 import Settings.Builders.Common
-import Settings.Builders.Ghc
 import CommandLine ( TestArgs(..), defaultTestArgs )
 
 -- Arguments to send to the runtest.py script.
diff --git a/src/Settings/Packages/Rts.hs b/src/Settings/Packages/Rts.hs
index 7b3bb2d..fcbd795 100644
--- a/src/Settings/Packages/Rts.hs
+++ b/src/Settings/Packages/Rts.hs
@@ -59,11 +59,13 @@ rtsLibffiLibrary way = do
 -- This apparently doesn't work on OS X (Darwin) nor on Solaris.
 -- On Darwin we get errors of the form
 --
---  ld: absolute addressing (perhaps -mdynamic-no-pic) used in _stg_ap_0_fast from rts/dist/build/Apply.dyn_o not allowed in slidable image
+--  ld: absolute addressing (perhaps -mdynamic-no-pic) used in _stg_ap_0_fast
+--      from rts/dist/build/Apply.dyn_o not allowed in slidable image
 --
 -- and lots of these warnings:
 --
---  ld: warning codegen in _stg_ap_pppv_fast (offset 0x0000005E) prevents image from loading in dyld shared cache
+--  ld: warning codegen in _stg_ap_pppv_fast (offset 0x0000005E) prevents image
+--      from loading in dyld shared cache
 --
 -- On Solaris we get errors like:
 --
@@ -75,7 +77,7 @@ rtsLibffiLibrary way = do
 -- collect2: ld returned 1 exit status
 speedHack :: Action Bool
 speedHack = do
-    i386 <- anyTargetArch ["i386"]
+    i386   <- anyTargetArch ["i386"]
     goodOS <- not <$> anyTargetOs ["darwin", "solaris2"]
     return $ i386 && goodOS
 
@@ -171,9 +173,6 @@ rtsPackageArgs = package rts ? do
             , (not <$> flag GccIsClang) ?
               inputs ["//Compact.c"] ? arg "-finline-limit=2500"
 
-            , inputs ["//Evac_thr.c", "//Scav_thr.c"] ?
-              pure ["-DPARALLEL_GC", "-Irts/sm"]
-
             , input "//StgCRun.c" ? windowsHost ? arg "-Wno-return-local-addr"
             , input "//RetainerProfile.c" ? flag GccIsClang ?
               arg "-Wno-incompatible-pointer-types"
@@ -183,8 +182,7 @@ rtsPackageArgs = package rts ? do
             , inputs [ "//Interpreter.c", "//Storage.c", "//Adjustor.c" ] ?
               arg "-Wno-strict-prototypes"
             , inputs ["//Interpreter.c", "//Adjustor.c", "//sm/Storage.c"] ?
-              anyTargetArch ["powerpc"] ? arg "-Wno-undef"
-            ]
+              anyTargetArch ["powerpc"] ? arg "-Wno-undef" ]
 
     mconcat
         [ builder (Cc FindCDependencies) ? cArgs



More information about the ghc-commits mailing list