diff options
author | Ben Gamari <ben@smart-cactus.org> | 2018-11-26 17:21:12 -0500 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2019-03-05 22:22:40 -0500 |
commit | 37f257afcd6a52cf4d76c60d766b1aeb520b9f05 (patch) | |
tree | ac800e46fbf94c16ce39170f4a720637b07dde06 /hadrian | |
parent | 646b6dfbe125aa756a935e840979ba11b4a882c0 (diff) | |
download | haskell-37f257afcd6a52cf4d76c60d766b1aeb520b9f05.tar.gz |
Rip out object splitting
The splitter is an evil Perl script that processes assembler code.
Its job can be done better by the linker's --gc-sections flag. GHC
passes this flag to the linker whenever -split-sections is passed on
the command line.
This is based on @DemiMarie's D2768.
Fixes Trac #11315
Fixes Trac #9832
Fixes Trac #8964
Fixes Trac #8685
Fixes Trac #8629
Diffstat (limited to 'hadrian')
-rw-r--r-- | hadrian/README.md | 5 | ||||
-rw-r--r-- | hadrian/cfg/system.config.in | 1 | ||||
-rw-r--r-- | hadrian/doc/user-settings.md | 9 | ||||
-rw-r--r-- | hadrian/src/Base.hs | 7 | ||||
-rw-r--r-- | hadrian/src/Builder.hs | 3 | ||||
-rw-r--r-- | hadrian/src/CommandLine.hs | 12 | ||||
-rw-r--r-- | hadrian/src/Flavour.hs | 2 | ||||
-rw-r--r-- | hadrian/src/Oracles/Flag.hs | 13 | ||||
-rw-r--r-- | hadrian/src/Packages.hs | 3 | ||||
-rw-r--r-- | hadrian/src/Rules/BinaryDist.hs | 2 | ||||
-rw-r--r-- | hadrian/src/Rules/Generate.hs | 30 | ||||
-rw-r--r-- | hadrian/src/Rules/Library.hs | 12 | ||||
-rw-r--r-- | hadrian/src/Settings/Builders/Ghc.hs | 1 | ||||
-rw-r--r-- | hadrian/src/Settings/Default.hs | 13 | ||||
-rw-r--r-- | hadrian/src/Settings/Default.hs-boot | 3 |
15 files changed, 8 insertions, 108 deletions
diff --git a/hadrian/README.md b/hadrian/README.md index 7b6646d655..179d9d07ce 100644 --- a/hadrian/README.md +++ b/hadrian/README.md @@ -114,10 +114,6 @@ four settings: `none`, `brief` (one line per build command; this is the default setting), `normal` (typically a box per build command), and `unicorn` (when `normal` just won't do). -* `--split-objects`: generate split objects, which are switched off by default. -Due to a GHC [bug][ghc-split-objs-bug], you need a full clean rebuild when using -this flag. - * `--verbose`: run Hadrian in verbose mode. In particular this prints diagnostic messages by Shake oracles. @@ -263,7 +259,6 @@ projects), as well as Well-Typed. [ghc-preparation]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation [ghc-windows-quick-build]: https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Windows#AQuickBuild [windows-build]: https://gitlab.haskell.org/ghc/ghc/blob/master/hadrian/doc/windows.md -[ghc-split-objs-bug]: https://ghc.haskell.org/trac/ghc/ticket/11315 [test-issue]: https://github.com/snowleopard/hadrian/issues/197 [validation-issue]: https://github.com/snowleopard/hadrian/issues/187 [dynamic-windows-issue]: https://github.com/snowleopard/hadrian/issues/343 diff --git a/hadrian/cfg/system.config.in b/hadrian/cfg/system.config.in index 4cae2b6783..affeeaa5d5 100644 --- a/hadrian/cfg/system.config.in +++ b/hadrian/cfg/system.config.in @@ -43,7 +43,6 @@ hs-cpp-args = @HaskellCPPArgs@ #=============== solaris-broken-shld = @SOLARIS_BROKEN_SHLD@ -split-objects-broken = @SplitObjsBroken@ ghc-unregisterised = @Unregisterised@ ghc-source-path = @hardtop@ leading-underscore = @LeadingUnderscore@ diff --git a/hadrian/doc/user-settings.md b/hadrian/doc/user-settings.md index 68929d325a..d0531a3f3d 100644 --- a/hadrian/doc/user-settings.md +++ b/hadrian/doc/user-settings.md @@ -23,8 +23,6 @@ data Flavour = Flavour { libraryWays :: Ways, -- | Build RTS these ways. rtsWays :: Ways, - -- | Build split objects. - splitObjects :: Predicate, -- | Build dynamic GHC programs. dynamicGhcPrograms :: Action Bool, -- | Enable GHCi debugger. @@ -275,13 +273,6 @@ their effects. ## Miscellaneous -To change the default behaviour of Hadrian with respect to building split -objects, override the `splitObjects` setting of the `Flavour` record: -```haskell -userFlavour :: Flavour -userFlavour = defaultFlavour { name = "user", splitObjects = return False } -``` - Hadrian prints various progress info during the build. You can change the colours used by default by overriding `buildProgressColour` and `successColour`: ```haskell diff --git a/hadrian/src/Base.hs b/hadrian/src/Base.hs index 47d9107669..19573de8fd 100644 --- a/hadrian/src/Base.hs +++ b/hadrian/src/Base.hs @@ -26,7 +26,6 @@ module Base ( generatedDir, generatedPath, stageBinPath, stageLibPath, templateHscPath, ghcDeps, includesDependencies, haddockDeps, relativePackageDbPath, packageDbPath, packageDbStamp, mingwStamp, - ghcSplitPath ) where import Control.Applicative @@ -138,12 +137,6 @@ haddockDeps stage = do templateHscPath :: Stage -> Action FilePath templateHscPath stage = stageLibPath stage <&> (-/- "template-hsc.h") --- | @ghc-split@ is a Perl script used by GHC when run with @-split-objs@ flag. --- It is generated in "Rules.Generate". This function returns the path relative --- to the build root under which we will copy @ghc-split@. -ghcSplitPath :: Stage -> FilePath -ghcSplitPath stage = stageString stage -/- "bin" -/- "ghc-split" - -- | We use this stamp file to track whether we've moved the mingw toolchain -- under the build root (to make it accessible to the GHCs we build on -- Windows). See "Rules.Program". diff --git a/hadrian/src/Builder.hs b/hadrian/src/Builder.hs index b56f9c1071..6c14eb4517 100644 --- a/hadrian/src/Builder.hs +++ b/hadrian/src/Builder.hs @@ -181,8 +181,7 @@ instance H.Builder Builder where unlitPath <- builderPath Unlit ghcdeps <- ghcDeps stage ghcgens <- generatedGhcDependencies stage - return $ [ root -/- ghcSplitPath stage -- TODO: Make conditional on --split-objects - , unlitPath ] + return $ [ unlitPath ] ++ ghcdeps ++ ghcgens ++ [ touchyPath | win ] diff --git a/hadrian/src/CommandLine.hs b/hadrian/src/CommandLine.hs index 842fb037cc..75e981222a 100644 --- a/hadrian/src/CommandLine.hs +++ b/hadrian/src/CommandLine.hs @@ -1,6 +1,6 @@ module CommandLine ( optDescrs, cmdLineArgsMap, cmdFlavour, lookupFreeze1, cmdIntegerSimple, - cmdProgressColour, cmdProgressInfo, cmdConfigure, cmdSplitObjects, + cmdProgressColour, cmdProgressInfo, cmdConfigure, cmdDocsArgs, lookupBuildRoot, TestArgs(..), TestSpeed(..), defaultTestArgs ) where @@ -25,7 +25,6 @@ data CommandLineArgs = CommandLineArgs , integerSimple :: Bool , progressColour :: UseColour , progressInfo :: ProgressInfo - , splitObjects :: Bool , buildRoot :: BuildRoot , testArgs :: TestArgs , docTargets :: DocTargets } @@ -40,7 +39,6 @@ defaultCommandLineArgs = CommandLineArgs , integerSimple = False , progressColour = Auto , progressInfo = Brief - , splitObjects = False , buildRoot = BuildRoot "_build" , testArgs = defaultTestArgs , docTargets = Set.fromList [minBound..maxBound] } @@ -121,9 +119,6 @@ readProgressInfo ms = set :: ProgressInfo -> CommandLineArgs -> CommandLineArgs set flag flags = flags { progressInfo = flag } -readSplitObjects :: Either String (CommandLineArgs -> CommandLineArgs) -readSplitObjects = Right $ \flags -> flags { splitObjects = True } - readTestCompiler :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs) readTestCompiler compiler = maybe (Left "Cannot parse compiler") (Right . set) compiler where @@ -220,8 +215,6 @@ optDescrs = "Use colours in progress info (Never, Auto or Always)." , Option [] ["progress-info"] (OptArg readProgressInfo "STYLE") "Progress info style (None, Brief, Normal or Unicorn)." - , Option [] ["split-objects"] (NoArg readSplitObjects) - "Generate split objects (requires a full clean rebuild)." , Option [] ["docs"] (OptArg readDocsArg "TARGET") "Strip down docs targets (none, no-haddocks, no-sphinx[-{html, pdfs, man}]." , Option [] ["test-compiler"] (OptArg readTestCompiler "TEST_COMPILER") @@ -283,8 +276,5 @@ cmdProgressColour = progressColour <$> cmdLineArgs cmdProgressInfo :: Action ProgressInfo cmdProgressInfo = progressInfo <$> cmdLineArgs -cmdSplitObjects :: Action Bool -cmdSplitObjects = splitObjects <$> cmdLineArgs - cmdDocsArgs :: Action DocTargets cmdDocsArgs = docTargets <$> cmdLineArgs diff --git a/hadrian/src/Flavour.hs b/hadrian/src/Flavour.hs index 4a71e80c45..06407e7022 100644 --- a/hadrian/src/Flavour.hs +++ b/hadrian/src/Flavour.hs @@ -26,8 +26,6 @@ data Flavour = Flavour { libraryWays :: Ways, -- | Build RTS these ways. rtsWays :: Ways, - -- | Build split objects. - splitObjects :: Predicate, -- | Build dynamic GHC programs. dynamicGhcPrograms :: Action Bool, -- | Enable GHCi debugger. diff --git a/hadrian/src/Oracles/Flag.hs b/hadrian/src/Oracles/Flag.hs index b294cebc93..4f5116bf41 100644 --- a/hadrian/src/Oracles/Flag.hs +++ b/hadrian/src/Oracles/Flag.hs @@ -1,6 +1,6 @@ module Oracles.Flag ( Flag (..), flag, getFlag, platformSupportsSharedLibs, ghcWithSMP, - ghcWithNativeCodeGen, supportsSplitObjects + ghcWithNativeCodeGen ) where import Hadrian.Oracles.TextFile @@ -17,7 +17,6 @@ data Flag = ArSupportsAtFile | GmpFrameworkPref | LeadingUnderscore | SolarisBrokenShld - | SplitObjectsBroken | WithLibdw | HaveLibMingwEx | UseSystemFfi @@ -35,7 +34,6 @@ flag f = do GmpFrameworkPref -> "gmp-framework-preferred" LeadingUnderscore -> "leading-underscore" SolarisBrokenShld -> "solaris-broken-shld" - SplitObjectsBroken -> "split-objects-broken" WithLibdw -> "with-libdw" HaveLibMingwEx -> "have-lib-mingw-ex" UseSystemFfi -> "use-system-ffi" @@ -69,12 +67,3 @@ ghcWithNativeCodeGen = do badOs <- anyTargetOs ["ios", "aix"] ghcUnreg <- flag GhcUnregisterised return $ goodArch && not badOs && not ghcUnreg - -supportsSplitObjects :: Action Bool -supportsSplitObjects = do - broken <- flag SplitObjectsBroken - ghcUnreg <- flag GhcUnregisterised - goodArch <- anyTargetArch [ "i386", "x86_64", "powerpc", "sparc" ] - goodOs <- anyTargetOs [ "mingw32", "cygwin32", "linux", "darwin", "solaris2" - , "freebsd", "dragonfly", "netbsd", "openbsd" ] - return $ not broken && not ghcUnreg && goodArch && goodOs diff --git a/hadrian/src/Packages.hs b/hadrian/src/Packages.hs index 75a74b2ae6..2738c6952d 100644 --- a/hadrian/src/Packages.hs +++ b/hadrian/src/Packages.hs @@ -4,7 +4,7 @@ module Packages ( array, base, binary, bytestring, cabal, checkApiAnnotations, checkPpr, compareSizes, compiler, containers, deepseq, deriveConstants, directory, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCompact, - ghcHeap, ghci, ghcPkg, ghcPrim, ghcSplit, haddock, haskeline, + ghcHeap, ghci, ghcPkg, ghcPrim, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, libffi, libiserv, mtl, parsec, pretty, primitive, process, rts, runGhc, stm, templateHaskell, terminfo, text, time, timeout, touchy, transformers, @@ -69,7 +69,6 @@ ghcHeap = lib "ghc-heap" ghci = lib "ghci" ghcPkg = util "ghc-pkg" ghcPrim = lib "ghc-prim" -ghcSplit = util "ghc-split" haddock = util "haddock" haskeline = lib "haskeline" hsc2hs = util "hsc2hs" diff --git a/hadrian/src/Rules/BinaryDist.hs b/hadrian/src/Rules/BinaryDist.hs index d54ac3d140..609766d5ca 100644 --- a/hadrian/src/Rules/BinaryDist.hs +++ b/hadrian/src/Rules/BinaryDist.hs @@ -134,7 +134,7 @@ bindistRules = do need $ map (bindistFilesDir -/-) (["configure", "Makefile"] ++ bindistInstallFiles) need $ map ((bindistFilesDir -/- "wrappers") -/-) ["check-api-annotations" - , "check-ppr", "ghc", "ghc-iserv", "ghc-pkg", "ghc-split" + , "check-ppr", "ghc", "ghc-iserv", "ghc-pkg" , "ghci-script", "ghci", "haddock", "hpc", "hp2ps", "hsc2hs" , "runghc"] diff --git a/hadrian/src/Rules/Generate.hs b/hadrian/src/Rules/Generate.hs index 13544f2a7d..032f6a68c1 100644 --- a/hadrian/src/Rules/Generate.hs +++ b/hadrian/src/Rules/Generate.hs @@ -174,11 +174,6 @@ generateRules = do priority 2.0 $ (root -/- generatedDir -/- "ghcplatform.h") <~ generateGhcPlatformH priority 2.0 $ (root -/- generatedDir -/- "ghcversion.h") <~ generateGhcVersionH - forM_ [Stage0 ..] $ \stage -> - root -/- ghcSplitPath stage %> \path -> do - generate path emptyTarget generateGhcSplit - makeExecutable path - -- TODO: simplify, get rid of fake rts context root -/- generatedDir ++ "//*" %> \file -> do withTempDir $ \dir -> build $ @@ -200,26 +195,6 @@ emptyTarget = vanillaContext (error "Rules.Generate.emptyTarget: unknown stage") cppify :: String -> String cppify = replaceEq '-' '_' . replaceEq '.' '_' -ghcSplitSource :: FilePath -ghcSplitSource = "driver/split/ghc-split.pl" - --- ref: rules/build-perl.mk --- | Generate the @ghc-split@ Perl script. -generateGhcSplit :: Expr String -generateGhcSplit = do - trackGenerateHs - targetPlatform <- getSetting TargetPlatform - ghcEnableTNC <- expr $ yesNo <$> ghcEnableTablesNextToCode - perlPath <- getBuilderPath Perl - contents <- expr $ readFileLines ghcSplitSource - return . unlines $ - [ "#!" ++ perlPath - , "my $TARGETPLATFORM = " ++ show targetPlatform ++ ";" - -- I don't see where the ghc-split tool uses TNC, but - -- it's in the build-perl macro. - , "my $TABLES_NEXT_TO_CODE = " ++ show ghcEnableTNC ++ ";" - ] ++ contents - -- | Generate @ghcplatform.h@ header. generateGhcPlatformH :: Expr String generateGhcPlatformH = do @@ -289,7 +264,6 @@ generateConfigHs = do | intLib == integerGmp = "IntegerGMP" | intLib == integerSimple = "IntegerSimple" | otherwise = error $ "Unknown integer library: " ++ pkgName intLib - cSupportsSplitObjs <- expr $ yesNo <$> supportsSplitObjects cGhcWithInterpreter <- expr $ yesNo <$> ghcWithInterpreter cGhcWithNativeCodeGen <- expr $ yesNo <$> ghcWithNativeCodeGen cGhcWithSMP <- expr $ yesNo <$> ghcWithSMP @@ -341,8 +315,6 @@ generateConfigHs = do , "cIntegerLibrary = " ++ show (pkgName intLib) , "cIntegerLibraryType :: IntegerLibrary" , "cIntegerLibraryType = " ++ cIntegerLibraryType - , "cSupportsSplitObjs :: String" - , "cSupportsSplitObjs = " ++ show cSupportsSplitObjs , "cGhcWithInterpreter :: String" , "cGhcWithInterpreter = " ++ show cGhcWithInterpreter , "cGhcWithNativeCodeGen :: String" @@ -357,8 +329,6 @@ generateConfigHs = do , "cLeadingUnderscore = " ++ show cLeadingUnderscore , "cGHC_UNLIT_PGM :: String" , "cGHC_UNLIT_PGM = " ++ show cGHC_UNLIT_PGM - , "cGHC_SPLIT_PGM :: String" - , "cGHC_SPLIT_PGM = " ++ show "ghc-split" , "cLibFFI :: Bool" , "cLibFFI = " ++ show cLibFFI , "cGhcThreaded :: Bool" diff --git a/hadrian/src/Rules/Library.hs b/hadrian/src/Rules/Library.hs index d19907bfa9..edec160cc2 100644 --- a/hadrian/src/Rules/Library.hs +++ b/hadrian/src/Rules/Library.hs @@ -121,18 +121,8 @@ libraryObjects :: Context -> Action [FilePath] libraryObjects context@Context{..} = do hsObjs <- hsObjects context noHsObjs <- nonHsObjects context - - -- This will create split objects if required (we don't track them - -- explicitly as this would needlessly bloat the Shake database). need $ noHsObjs ++ hsObjs - - split <- interpretInContext context =<< splitObjects <$> flavour - let getSplitObjs = concatForM hsObjs $ \obj -> do - let dir = dropExtension obj ++ "_" ++ osuf way ++ "_split" - contents <- liftIO $ IO.getDirectoryContents dir - return . map (dir -/-) $ filter (not . all (== '.')) contents - - (noHsObjs ++) <$> if split then getSplitObjs else return hsObjs + return (noHsObjs ++ hsObjs) -- * Library paths types and parsers diff --git a/hadrian/src/Settings/Builders/Ghc.hs b/hadrian/src/Settings/Builders/Ghc.hs index 4bc10e5edd..b952a017bc 100644 --- a/hadrian/src/Settings/Builders/Ghc.hs +++ b/hadrian/src/Settings/Builders/Ghc.hs @@ -17,7 +17,6 @@ compileAndLinkHs :: Args compileAndLinkHs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do mconcat [ arg "-Wall" , commonGhcArgs - , splitObjects <$> flavour ? arg "-split-objs" , ghcLinkArgs , defaultGhcWarningsArgs , builder (Ghc CompileHs) ? arg "-c" diff --git a/hadrian/src/Settings/Default.hs b/hadrian/src/Settings/Default.hs index 084dcf3d42..b74ee09499 100644 --- a/hadrian/src/Settings/Default.hs +++ b/hadrian/src/Settings/Default.hs @@ -10,7 +10,7 @@ module Settings.Default ( defaultArgs, -- * Default build flavour - defaultFlavour, defaultSplitObjects + defaultFlavour ) where import qualified Hadrian.Builder.Ar @@ -210,7 +210,6 @@ defaultFlavour = Flavour , integerLibrary = (\x -> if x then integerSimple else integerGmp) <$> cmdIntegerSimple , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays - , splitObjects = defaultSplitObjects , dynamicGhcPrograms = defaultDynamicGhcPrograms , ghciWithDebugger = False , ghcProfiled = False @@ -228,16 +227,6 @@ defaultDynamicGhcPrograms = do supportsShared <- platformSupportsSharedLibs return (not win && supportsShared) --- | Default condition for building split objects. -defaultSplitObjects :: Predicate -defaultSplitObjects = do - goodStage <- notStage0 -- We don't split bootstrap (stage 0) packages - pkg <- getPackage - supported <- expr supportsSplitObjects - split <- expr cmdSplitObjects - let goodPackage = isLibrary pkg && pkg /= compiler && pkg /= rts - return $ split && goodStage && goodPackage && supported - -- | All 'Builder'-dependent command line arguments. defaultBuilderArgs :: Args defaultBuilderArgs = mconcat diff --git a/hadrian/src/Settings/Default.hs-boot b/hadrian/src/Settings/Default.hs-boot index 30a28497e9..e2996d9c71 100644 --- a/hadrian/src/Settings/Default.hs-boot +++ b/hadrian/src/Settings/Default.hs-boot @@ -1,7 +1,7 @@ module Settings.Default ( SourceArgs (..), sourceArgs, defaultBuilderArgs, defaultPackageArgs, defaultArgs, defaultLibraryWays, defaultRtsWays, - defaultFlavour, defaultSplitObjects + defaultFlavour ) where import Flavour @@ -18,4 +18,3 @@ sourceArgs :: SourceArgs -> Args defaultBuilderArgs, defaultPackageArgs, defaultArgs :: Args defaultLibraryWays, defaultRtsWays :: Ways defaultFlavour :: Flavour -defaultSplitObjects :: Predicate |