diff options
Diffstat (limited to 'compiler/main')
-rw-r--r-- | compiler/main/DriverPhases.hs | 9 | ||||
-rw-r--r-- | compiler/main/DriverPipeline.hs | 164 | ||||
-rw-r--r-- | compiler/main/DynFlags.hs | 22 | ||||
-rw-r--r-- | compiler/main/HscMain.hs | 2 | ||||
-rw-r--r-- | compiler/main/SysTools.hs | 16 | ||||
-rw-r--r-- | compiler/main/SysTools/BaseDir.hs | 2 | ||||
-rw-r--r-- | compiler/main/SysTools/Tasks.hs | 5 |
7 files changed, 25 insertions, 195 deletions
diff --git a/compiler/main/DriverPhases.hs b/compiler/main/DriverPhases.hs index d923262987..12e12ca321 100644 --- a/compiler/main/DriverPhases.hs +++ b/compiler/main/DriverPhases.hs @@ -138,8 +138,6 @@ data Phase | Cobjc -- Compile Objective-C | Cobjcxx -- Compile Objective-C++ | HCc -- Haskellised C (as opposed to vanilla C) compilation - | Splitter -- Assembly file splitter (part of '-split-objs') - | SplitAs -- Assembler for split assembly files (part of '-split-objs') | As Bool -- Assembler for regular assembly files (Bool: with-cpp) | LlvmOpt -- Run LLVM opt tool over llvm assembly | LlvmLlc -- LLVM bitcode to native assembly @@ -173,8 +171,6 @@ eqPhase (Hsc _) (Hsc _) = True eqPhase Cc Cc = True eqPhase Cobjc Cobjc = True eqPhase HCc HCc = True -eqPhase Splitter Splitter = True -eqPhase SplitAs SplitAs = True eqPhase (As x) (As y) = x == y eqPhase LlvmOpt LlvmOpt = True eqPhase LlvmLlc LlvmLlc = True @@ -218,11 +214,9 @@ nextPhase dflags p Cpp sf -> HsPp sf HsPp sf -> Hsc sf Hsc _ -> maybeHCc - Splitter -> SplitAs LlvmOpt -> LlvmLlc LlvmLlc -> LlvmMangle LlvmMangle -> As False - SplitAs -> MergeForeign As _ -> MergeForeign Ccxx -> As False Cc -> As False @@ -257,7 +251,6 @@ startPhase "M" = Cobjcxx startPhase "mm" = Cobjcxx startPhase "cc" = Ccxx startPhase "cxx" = Ccxx -startPhase "split_s" = Splitter startPhase "s" = As False startPhase "S" = As True startPhase "ll" = LlvmOpt @@ -286,13 +279,11 @@ phaseInputExt Ccxx = "cpp" phaseInputExt Cobjc = "m" phaseInputExt Cobjcxx = "mm" phaseInputExt Cc = "c" -phaseInputExt Splitter = "split_s" phaseInputExt (As True) = "S" phaseInputExt (As False) = "s" phaseInputExt LlvmOpt = "ll" phaseInputExt LlvmLlc = "bc" phaseInputExt LlvmMangle = "lm_s" -phaseInputExt SplitAs = "split_s" phaseInputExt CmmCpp = "cmmcpp" phaseInputExt Cmm = "cmm" phaseInputExt MergeForeign = "o" diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index a9e486c94a..6810de2e6b 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, NamedFieldPuns, NondecreasingIndentation, BangPatterns #-} +{-# LANGUAGE CPP, NamedFieldPuns, NondecreasingIndentation, BangPatterns, MultiWayIf #-} {-# OPTIONS_GHC -fno-cse #-} -- -fno-cse is needed for GLOBAL_VAR's to behave properly @@ -245,7 +245,7 @@ compileOne' m_tc_result mHscMessage src_flavour = ms_hsc_src summary mod_name = ms_mod_name summary - next_phase = hscPostBackendPhase dflags src_flavour hsc_lang + next_phase = hscPostBackendPhase src_flavour hsc_lang object_filename = ml_obj_file location -- #8180 - when using TemplateHaskell, switch on -dynamic-too so @@ -502,7 +502,6 @@ compileFile hsc_env stop_phase (src, mb_phase) = do let dflags = hsc_dflags hsc_env - split = gopt Opt_SplitObjs dflags mb_o_file = outputFile dflags ghc_link = ghcLink dflags -- Set by -c or -no-link @@ -519,11 +518,7 @@ compileFile hsc_env stop_phase (src, mb_phase) = do -- -o foo applies to the file we are compiling now | otherwise = Persistent - stop_phase' = case stop_phase of - As _ | split -> SplitAs - _ -> stop_phase - - ( _, out_file) <- runPipeline stop_phase' hsc_env + ( _, out_file) <- runPipeline stop_phase hsc_env (src, fmap RealPhase mb_phase) Nothing output Nothing{-no ModLocation-} [] return out_file @@ -1079,7 +1074,7 @@ runPhase (HscOut src_flavour mod_name result) _ dflags = do let o_file = ml_obj_file location -- The real object file hsc_lang = hscTarget dflags - next_phase = hscPostBackendPhase dflags src_flavour hsc_lang + next_phase = hscPostBackendPhase src_flavour hsc_lang case result of HscNotGeneratingCode -> @@ -1132,7 +1127,7 @@ runPhase (RealPhase Cmm) input_fn dflags = do let hsc_lang = hscTarget dflags - let next_phase = hscPostBackendPhase dflags HsSrcFile hsc_lang + let next_phase = hscPostBackendPhase HsSrcFile hsc_lang output_fn <- phaseOutputFilename next_phase @@ -1275,40 +1270,9 @@ runPhase (RealPhase cc_phase) input_fn dflags return (RealPhase next_phase, output_fn) ----------------------------------------------------------------------------- --- Splitting phase - -runPhase (RealPhase Splitter) input_fn dflags - = do -- tmp_pfx is the prefix used for the split .s files - - split_s_prefix <- - liftIO $ newTempName dflags TFL_CurrentModule "split" - let n_files_fn = split_s_prefix - - liftIO $ SysTools.runSplit dflags - [ SysTools.FileOption "" input_fn - , SysTools.FileOption "" split_s_prefix - , SysTools.FileOption "" n_files_fn - ] - - -- Save the number of split files for future references - s <- liftIO $ readFile n_files_fn - let n_files = read s :: Int - dflags' = dflags { splitInfo = Just (split_s_prefix, n_files) } - - setDynFlags dflags' - - -- Remember to delete all these files - liftIO $ addFilesToClean dflags' TFL_CurrentModule $ - [ split_s_prefix ++ "__" ++ show n ++ ".s" - | n <- [1..n_files]] - - return (RealPhase SplitAs, - "**splitter**") -- we don't use the filename in SplitAs - ------------------------------------------------------------------------------ -- As, SpitAs phase : Assembler --- This is for calling the assembler on a regular assembly file (not split). +-- This is for calling the assembler on a regular assembly file runPhase (RealPhase (As with_cpp)) input_fn dflags = do -- LLVM from version 3.0 onwards doesn't support the OS X system @@ -1368,96 +1332,6 @@ runPhase (RealPhase (As with_cpp)) input_fn dflags return (RealPhase next_phase, output_fn) --- This is for calling the assembler on a split assembly file (so a collection --- of assembly files) -runPhase (RealPhase SplitAs) _input_fn dflags - = do - -- we'll handle the stub_o file in this phase, so don't MergeForeign, - -- just jump straight to StopLn afterwards. - let next_phase = StopLn - output_fn <- phaseOutputFilename next_phase - - let base_o = dropExtension output_fn - osuf = objectSuf dflags - split_odir = base_o ++ "_" ++ osuf ++ "_split" - - let pic_c_flags = picCCOpts dflags - - -- this also creates the hierarchy - liftIO $ createDirectoryIfMissing True split_odir - - -- remove M_split/ *.o, because we're going to archive M_split/ *.o - -- later and we don't want to pick up any old objects. - fs <- liftIO $ getDirectoryContents split_odir - liftIO $ mapM_ removeFile $ - map (split_odir </>) $ filter (osuf `isSuffixOf`) fs - - let (split_s_prefix, n) = case splitInfo dflags of - Nothing -> panic "No split info" - Just x -> x - - let split_s n = split_s_prefix ++ "__" ++ show n <.> "s" - - split_obj :: Int -> FilePath - split_obj n = split_odir </> - takeFileName base_o ++ "__" ++ show n <.> osuf - - let assemble_file n - = SysTools.runAs dflags ( - - -- We only support SparcV9 and better because V8 lacks an atomic CAS - -- instruction so we have to make sure that the assembler accepts the - -- instruction set. Note that the user can still override this - -- (e.g., -mcpu=ultrasparc). GCC picks the "best" -mcpu flag - -- regardless of the ordering. - -- - -- This is a temporary hack. - (if platformArch (targetPlatform dflags) == ArchSPARC - then [SysTools.Option "-mcpu=v9"] - else []) ++ - - -- See Note [-fPIC for assembler] - map SysTools.Option pic_c_flags ++ - - [ SysTools.Option "-c" - , SysTools.Option "-o" - , SysTools.FileOption "" (split_obj n) - , SysTools.FileOption "" (split_s n) - ]) - - liftIO $ mapM_ assemble_file [1..n] - - -- Note [pipeline-split-init] - -- If we have a stub file -- which will be part of foreign_os -- - -- it may contain constructor - -- functions for initialisation of this module. We can't - -- simply leave the stub as a separate object file, because it - -- will never be linked in: nothing refers to it. We need to - -- ensure that if we ever refer to the data in this module - -- that needs initialisation, then we also pull in the - -- initialisation routine. - -- - -- To that end, we make a DANGEROUS ASSUMPTION here: the data - -- that needs to be initialised is all in the FIRST split - -- object. See Note [codegen-split-init]. - -- - -- We also merge in all the foreign objects since we're at it. - - PipeState{foreign_os} <- getPipeState - if null foreign_os - then return () - else liftIO $ do - tmp_split_1 <- newTempName dflags TFL_CurrentModule osuf - let split_1 = split_obj 1 - copyFile split_1 tmp_split_1 - removeFile split_1 - joinObjectFiles dflags (tmp_split_1 : foreign_os) split_1 - - -- join them into a single .o file - liftIO $ joinObjectFiles dflags (map split_obj [1..n]) output_fn - - return (RealPhase next_phase, output_fn) - ----------------------------------------------------------------------------- -- LlvmOpt phase runPhase (RealPhase LlvmOpt) input_fn dflags @@ -1499,13 +1373,10 @@ runPhase (RealPhase LlvmOpt) input_fn dflags runPhase (RealPhase LlvmLlc) input_fn dflags = do - next_phase <- if fastLlvmPipeline dflags - then maybeMergeForeign - -- hidden debugging flag '-dno-llvm-mangler' to skip mangling - else case gopt Opt_NoLlvmMangler dflags of - False -> return LlvmMangle - True | gopt Opt_SplitObjs dflags -> return Splitter - True -> return (As False) + next_phase <- if | fastLlvmPipeline dflags -> maybeMergeForeign + -- hidden debugging flag '-dno-llvm-mangler' to skip mangling + | gopt Opt_NoLlvmMangler dflags -> return (As False) + | otherwise -> return LlvmMangle output_fn <- phaseOutputFilename next_phase @@ -1577,7 +1448,7 @@ runPhase (RealPhase LlvmLlc) input_fn dflags runPhase (RealPhase LlvmMangle) input_fn dflags = do - let next_phase = if gopt Opt_SplitObjs dflags then Splitter else As False + let next_phase = As False output_fn <- phaseOutputFilename next_phase liftIO $ llvmFixupAsm dflags input_fn output_fn return (RealPhase next_phase, output_fn) @@ -2216,14 +2087,13 @@ writeInterfaceOnlyMode dflags = HscNothing == hscTarget dflags -- | What phase to run after one of the backend code generators has run -hscPostBackendPhase :: DynFlags -> HscSource -> HscTarget -> Phase -hscPostBackendPhase _ HsBootFile _ = StopLn -hscPostBackendPhase _ HsigFile _ = StopLn -hscPostBackendPhase dflags _ hsc_lang = +hscPostBackendPhase :: HscSource -> HscTarget -> Phase +hscPostBackendPhase HsBootFile _ = StopLn +hscPostBackendPhase HsigFile _ = StopLn +hscPostBackendPhase _ hsc_lang = case hsc_lang of - HscC -> HCc - HscAsm | gopt Opt_SplitObjs dflags -> Splitter - | otherwise -> As False + HscC -> HCc + HscAsm -> As False HscLlvm -> LlvmOpt HscNothing -> StopLn HscInterpreted -> StopLn diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index b574ba9080..1702bce392 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -88,7 +88,7 @@ module DynFlags ( ghcUsagePath, ghciUsagePath, topDir, tmpDir, rawSettings, versionedAppDir, extraGccViaCFlags, systemPackageConfig, - pgm_L, pgm_P, pgm_F, pgm_c, pgm_s, pgm_a, pgm_l, pgm_dll, pgm_T, + pgm_L, pgm_P, pgm_F, pgm_c, pgm_a, pgm_l, pgm_dll, pgm_T, pgm_windres, pgm_libtool, pgm_ar, pgm_ranlib, pgm_lo, pgm_lc, pgm_lcc, pgm_i, opt_L, opt_P, opt_F, opt_c, opt_a, opt_l, opt_i, opt_P_signature, @@ -523,7 +523,6 @@ data GeneralFlag | Opt_ExcessPrecision | Opt_EagerBlackHoling | Opt_NoHsMain - | Opt_SplitObjs | Opt_SplitSections | Opt_StgStats | Opt_HideAllPackages @@ -1720,13 +1719,10 @@ wayUnsetGeneralFlags :: Platform -> Way -> [GeneralFlag] wayUnsetGeneralFlags _ (WayCustom {}) = [] wayUnsetGeneralFlags _ WayThreaded = [] wayUnsetGeneralFlags _ WayDebug = [] -wayUnsetGeneralFlags _ WayDyn = [-- There's no point splitting objects +wayUnsetGeneralFlags _ WayDyn = [-- There's no point splitting -- when we're going to be dynamically -- linking. Plus it breaks compilation -- on OSX x86. - Opt_SplitObjs, - -- If splitobjs wasn't useful for this, - -- assume sections aren't either. Opt_SplitSections] wayUnsetGeneralFlags _ WayProf = [] wayUnsetGeneralFlags _ WayEventLog = [] @@ -2954,7 +2950,7 @@ dynamic_flags_deps = [ -- (see Trac #15319) sGccSupportsNoPie = False}))) , make_ord_flag defFlag "pgms" - (hasArg (\f -> alterSettings (\s -> s { sPgm_s = (f,[])}))) + (HasArg (\f -> addWarn "Object splitting was removed in GHC 8.8")) , make_ord_flag defFlag "pgma" (hasArg (\f -> alterSettings (\s -> s { sPgm_a = (f,[])}))) , make_ord_flag defFlag "pgml" @@ -2995,9 +2991,7 @@ dynamic_flags_deps = [ alterSettings (\s -> s { sOpt_windres = f : sOpt_windres s}))) , make_ord_flag defGhcFlag "split-objs" - (NoArg (if can_split - then setGeneralFlag Opt_SplitObjs - else addWarn "ignoring -split-objs")) + (NoArg $ addWarn "ignoring -split-objs") , make_ord_flag defGhcFlag "split-sections" (noArgM (\dflags -> do @@ -5499,12 +5493,6 @@ picPOpts dflags | otherwise = [] -- ----------------------------------------------------------------------------- --- Splitting - -can_split :: Bool -can_split = cSupportsSplitObjs == "YES" - --- ----------------------------------------------------------------------------- -- Compiler Info compilerInfo :: DynFlags -> [(String, String)] @@ -5526,7 +5514,7 @@ compilerInfo dflags ("Host platform", cHostPlatformString), ("Target platform", cTargetPlatformString), ("Have interpreter", cGhcWithInterpreter), - ("Object splitting supported", cSupportsSplitObjs), + ("Object splitting supported", showBool False), ("Have native code generator", cGhcWithNativeCodeGen), ("Support SMP", cGhcWithSMP), ("Tables next to code", cGhcEnableTablesNextToCode), diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index d7cebd00fc..49016e3799 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -1451,7 +1451,7 @@ doCodeGen hsc_env this_mod data_tycons -- we generate one SRT for the whole module. let pipeline_stream - | gopt Opt_SplitObjs dflags || gopt Opt_SplitSections dflags || + | gopt Opt_SplitSections dflags || osSubsectionsViaSymbols (platformOS (targetPlatform dflags)) = {-# SCC "cmmPipeline" #-} let run_pipeline us cmmgroup = do diff --git a/compiler/main/SysTools.hs b/compiler/main/SysTools.hs index 9bbce19602..543dd9ce3b 100644 --- a/compiler/main/SysTools.hs +++ b/compiler/main/SysTools.hs @@ -139,7 +139,7 @@ initSysTools top_dir -- NB: top_dir is assumed to be in standard Unix -- format, '/' separated mtool_dir <- findToolDir top_dir - -- see Note [tooldir: How GHC finds mingw and perl on Windows] + -- see Note [tooldir: How GHC finds mingw on Windows] let installed :: FilePath -> FilePath installed file = top_dir </> file @@ -212,7 +212,6 @@ initSysTools top_dir ldSupportsBuildId <- getBooleanSetting "ld supports build-id" ldSupportsFilelist <- getBooleanSetting "ld supports filelist" ldIsGnuLd <- getBooleanSetting "ld is GNU ld" - perl_path <- getToolSetting "perl command" let pkgconfig_path = installed "package.conf.d" ghc_usage_msg_path = installed "ghc-usage.txt" @@ -222,9 +221,6 @@ initSysTools top_dir -- architecture-specific stuff is done when building Config.hs unlit_path = libexec cGHC_UNLIT_PGM - -- split is a Perl script - split_script = libexec cGHC_SPLIT_PGM - windres_path <- getToolSetting "windres command" libtool_path <- getToolSetting "libtool command" ar_path <- getToolSetting "ar command" @@ -234,15 +230,6 @@ initSysTools top_dir touch_path <- getToolSetting "touch command" - let -- On Win32 we don't want to rely on #!/bin/perl, so we prepend - -- a call to Perl to get the invocation of split. - -- On Unix, scripts are invoked using the '#!' method. Binary - -- installations of GHC on Unix place the correct line on the - -- front of the script at installation time, so we don't want - -- to wire-in our knowledge of $(PERL) on the host system here. - (split_prog, split_args) - | isWindowsHost = (perl_path, [Option split_script]) - | otherwise = (split_script, []) mkdll_prog <- getToolSetting "dllwrap command" let mkdll_args = [] @@ -297,7 +284,6 @@ initSysTools top_dir sPgm_P = (cpp_prog, cpp_args), sPgm_F = "", sPgm_c = (gcc_prog, gcc_args), - sPgm_s = (split_prog,split_args), sPgm_a = (as_prog, as_args), sPgm_l = (ld_prog, ld_args), sPgm_dll = (mkdll_prog,mkdll_args), diff --git a/compiler/main/SysTools/BaseDir.hs b/compiler/main/SysTools/BaseDir.hs index 786b0e4ee9..d01d5214b4 100644 --- a/compiler/main/SysTools/BaseDir.hs +++ b/compiler/main/SysTools/BaseDir.hs @@ -68,7 +68,7 @@ On Windows: from topdir we can find package.conf, ghc-asm, etc. -Note [tooldir: How GHC finds mingw and perl on Windows] +Note [tooldir: How GHC finds mingw on Windows] GHC has some custom logic on Windows for finding the mingw toolchain and perl. Depending on whether GHC is built diff --git a/compiler/main/SysTools/Tasks.hs b/compiler/main/SysTools/Tasks.hs index a986db2fc0..9e3df26877 100644 --- a/compiler/main/SysTools/Tasks.hs +++ b/compiler/main/SysTools/Tasks.hs @@ -131,11 +131,6 @@ askLd dflags args = do runSomethingWith dflags "gcc" p args2 $ \real_args -> readCreateProcessWithExitCode' (proc p real_args){ env = mb_env } -runSplit :: DynFlags -> [Option] -> IO () -runSplit dflags args = do - let (p,args0) = pgm_s dflags - runSomething dflags "Splitter" p (args0++args) - runAs :: DynFlags -> [Option] -> IO () runAs dflags args = do let (p,args0) = pgm_a dflags |