X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fmain%2FDriverPipeline.hs;h=690328d8070021310feafa4cd573fae9b31c7d65;hb=2a8cdc3aee5997374273e27365f92c161aca8453;hp=a39ca38a994878b1ac0f38434ffef284e8cbaacf;hpb=dda45b7ae83033cf99630435c13054f3f6ac67d2;p=ghc-hetmet.git diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index a39ca38..690328d 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -29,13 +29,14 @@ module DriverPipeline ( import Packages import HeaderInfo import DriverPhases -import SysTools ( newTempName, addFilesToClean, getSysMan, copy ) +import SysTools ( newTempName, addFilesToClean, copy ) import qualified SysTools import HscMain import Finder import HscTypes import Outputable import Module +import UniqFM ( eltsUFM ) import ErrUtils import DynFlags import StaticFlags ( v_Ld_inputs, opt_Static, WayName(..) ) @@ -135,16 +136,16 @@ compile hsc_env mod_summary maybe_old_linkable old_iface mod_index nmods = do -- ... and what the next phase should be let next_phase = hscNextPhase dflags src_flavour hsc_lang -- ... and what file to generate the output into - output_fn <- getOutputFilename dflags next_phase - Temporary basename next_phase (Just location) + output_fn <- getOutputFilename next_phase + Temporary basename dflags next_phase (Just location) let dflags' = dflags { hscTarget = hsc_lang, hscOutName = output_fn, extCoreName = basename ++ ".hcr" } -- -no-recomp should also work with --make - let do_recomp = dopt Opt_RecompChecking dflags - source_unchanged = isJust maybe_old_linkable && do_recomp + let force_recomp = dopt Opt_ForceRecomp dflags + source_unchanged = isJust maybe_old_linkable && not force_recomp hsc_env' = hsc_env { hsc_dflags = dflags' } object_filename = ml_obj_file location @@ -235,7 +236,7 @@ compileStub dflags mod location = do stub_o = o_base ++ "_stub" `joinFileExt` o_ext -- compile the _stub.c file w/ gcc - let (stub_c,_) = mkStubPaths dflags mod location + let (stub_c,_) = mkStubPaths dflags (moduleName mod) location runPipeline StopLn dflags (stub_c,Nothing) (SpecificFile stub_o) Nothing{-no ModLocation-} @@ -271,7 +272,7 @@ link BatchCompile dflags batch_attempt_linking hpt | batch_attempt_linking = do let - home_mod_infos = moduleEnvElts hpt + home_mod_infos = eltsUFM hpt -- the packages we depend on pkg_deps = concatMap (dep_pkgs . mi_deps . hm_iface) home_mod_infos @@ -301,7 +302,7 @@ link BatchCompile dflags batch_attempt_linking hpt | Right t <- e_exe_time = any (t <) (map linkableTime linkables) - if dopt Opt_RecompChecking dflags && not linking_needed + if not (dopt Opt_ForceRecomp dflags) && not linking_needed then do debugTraceMsg dflags 2 (text exe_file <+> ptext SLIT("is up to date, linking not required.")) return Succeeded else do @@ -376,9 +377,7 @@ doLink dflags stop_phase o_files where -- Always link in the haskell98 package for static linking. Other -- packages have to be specified via the -package flag. - link_pkgs - | ExtPackage h98_id <- haskell98PackageId (pkgState dflags) = [h98_id] - | otherwise = [] + link_pkgs = [haskell98PackageId] -- --------------------------------------------------------------------------- @@ -434,7 +433,7 @@ runPipeline stop_phase dflags (input_fn, mb_phase) output maybe_loc -- this is a function which will be used to calculate output file names -- as we go along (we partially apply it to some of its inputs here) - let get_output_fn = getOutputFilename dflags stop_phase output basename + let get_output_fn = getOutputFilename stop_phase output basename -- Execute the pipeline... (dflags', output_fn, maybe_loc) <- @@ -449,7 +448,7 @@ runPipeline stop_phase dflags (input_fn, mb_phase) output maybe_loc Temporary -> return (dflags', output_fn) _other -> - do final_fn <- get_output_fn stop_phase maybe_loc + do final_fn <- get_output_fn dflags' stop_phase maybe_loc when (final_fn /= output_fn) $ copy dflags ("Copying `" ++ output_fn ++ "' to `" ++ final_fn ++ "'") output_fn final_fn @@ -459,7 +458,7 @@ runPipeline stop_phase dflags (input_fn, mb_phase) output maybe_loc pipeLoop :: DynFlags -> Phase -> Phase -> FilePath -> String -> Suffix - -> (Phase -> Maybe ModLocation -> IO FilePath) + -> (DynFlags -> Phase -> Maybe ModLocation -> IO FilePath) -> Maybe ModLocation -> IO (DynFlags, FilePath, Maybe ModLocation) @@ -486,28 +485,28 @@ pipeLoop dflags phase stop_phase orig_basename orig_suff orig_get_output_fn maybe_loc } getOutputFilename - :: DynFlags -> Phase -> PipelineOutput -> String - -> Phase{-next phase-} -> Maybe ModLocation -> IO FilePath -getOutputFilename dflags stop_phase output basename + :: Phase -> PipelineOutput -> String + -> DynFlags -> Phase{-next phase-} -> Maybe ModLocation -> IO FilePath +getOutputFilename stop_phase output basename = func where - hcsuf = hcSuf dflags - odir = objectDir dflags - osuf = objectSuf dflags - keep_hc = dopt Opt_KeepHcFiles dflags - keep_raw_s = dopt Opt_KeepRawSFiles dflags - keep_s = dopt Opt_KeepSFiles dflags - - myPhaseInputExt HCc = hcsuf - myPhaseInputExt StopLn = osuf - myPhaseInputExt other = phaseInputExt other - - func next_phase maybe_location + func dflags next_phase maybe_location | is_last_phase, Persistent <- output = persistent_fn | is_last_phase, SpecificFile f <- output = return f | keep_this_output = persistent_fn | otherwise = newTempName dflags suffix where + hcsuf = hcSuf dflags + odir = objectDir dflags + osuf = objectSuf dflags + keep_hc = dopt Opt_KeepHcFiles dflags + keep_raw_s = dopt Opt_KeepRawSFiles dflags + keep_s = dopt Opt_KeepSFiles dflags + + myPhaseInputExt HCc = hcsuf + myPhaseInputExt StopLn = osuf + myPhaseInputExt other = phaseInputExt other + is_last_phase = next_phase `eqPhase` stop_phase -- sometimes, we keep output from intermediate stages @@ -550,7 +549,7 @@ runPhase :: Phase -- Do this phase first -> String -- basename of original input source -> String -- its extension -> FilePath -- name of file which contains the input to this phase. - -> (Phase -> Maybe ModLocation -> IO FilePath) + -> (DynFlags -> Phase -> Maybe ModLocation -> IO FilePath) -- how to calculate the output filename -> Maybe ModLocation -- the ModLocation, if we have one -> IO (Phase, -- next phase @@ -568,7 +567,7 @@ runPhase :: Phase -- Do this phase first runPhase (Unlit sf) _stop dflags _basename _suff input_fn get_output_fn maybe_loc = do let unlit_flags = getOpts dflags opt_L -- The -h option passes the file name for unlit to put in a #line directive - output_fn <- get_output_fn (Cpp sf) maybe_loc + output_fn <- get_output_fn dflags (Cpp sf) maybe_loc SysTools.runUnlit dflags (map SysTools.Option unlit_flags ++ @@ -594,7 +593,7 @@ runPhase (Cpp sf) _stop dflags0 basename suff input_fn get_output_fn maybe_loc -- to the next phase of the pipeline. return (HsPp sf, dflags, maybe_loc, input_fn) else do - output_fn <- get_output_fn (HsPp sf) maybe_loc + output_fn <- get_output_fn dflags (HsPp sf) maybe_loc doCpp dflags True{-raw-} False{-no CC opts-} input_fn output_fn return (HsPp sf, dflags, maybe_loc, output_fn) @@ -609,7 +608,7 @@ runPhase (HsPp sf) _stop dflags basename suff input_fn get_output_fn maybe_loc else do let hspp_opts = getOpts dflags opt_F let orig_fn = basename `joinFileExt` suff - output_fn <- get_output_fn (Hsc sf) maybe_loc + output_fn <- get_output_fn dflags (Hsc sf) maybe_loc SysTools.runPp dflags ( [ SysTools.Option orig_fn , SysTools.Option input_fn @@ -640,7 +639,7 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma case src_flavour of ExtCoreFile -> do { -- no explicit imports in ExtCore input. ; m <- getCoreModuleName input_fn - ; return (Nothing, mkModule m) } + ; return (Nothing, mkModuleName m) } other -> do { buf <- hGetStringBuffer input_fn ; (_,_,L _ mod_name) <- getImports dflags buf input_fn @@ -677,22 +676,6 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma = location3 { ml_obj_file = ofile } | otherwise = location3 - -- Make the ModSummary to hand to hscMain - src_timestamp <- getModificationTime (basename `joinFileExt` suff) - let - unused_field = panic "runPhase:ModSummary field" - -- Some fields are not looked at by hscMain - mod_summary = ModSummary { ms_mod = mod_name, - ms_hsc_src = src_flavour, - ms_hspp_file = input_fn, - ms_hspp_opts = dflags, - ms_hspp_buf = hspp_buf, - ms_location = location4, - ms_hs_date = src_timestamp, - ms_obj_date = Nothing, - ms_imps = unused_field, - ms_srcimps = unused_field } - o_file = ml_obj_file location4 -- The real object file @@ -703,9 +686,11 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma -- changed (which the compiler itself figures out). -- Setting source_unchanged to False tells the compiler that M.o is out of -- date wrt M.hs (or M.o doesn't exist) so we must recompile regardless. - let do_recomp = dopt Opt_RecompChecking dflags + src_timestamp <- getModificationTime (basename `joinFileExt` suff) + + let force_recomp = dopt Opt_ForceRecomp dflags source_unchanged <- - if not do_recomp || not (isStopLn stop) + if force_recomp || not (isStopLn stop) -- Set source_unchanged to False unconditionally if -- (a) recompilation checker is off, or -- (b) we aren't going all the way to .o file (e.g. ghc -S) @@ -722,7 +707,7 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma -- get the DynFlags let hsc_lang = hscMaybeAdjustTarget dflags stop src_flavour (hscTarget dflags) let next_phase = hscNextPhase dflags src_flavour hsc_lang - output_fn <- get_output_fn next_phase (Just location4) + output_fn <- get_output_fn dflags next_phase (Just location4) let dflags' = dflags { hscTarget = hsc_lang, hscOutName = output_fn, @@ -731,7 +716,22 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma hsc_env <- newHscEnv dflags' -- Tell the finder cache about this module - addHomeModuleToFinder hsc_env mod_name location4 + mod <- addHomeModuleToFinder hsc_env mod_name location4 + + -- Make the ModSummary to hand to hscMain + let + unused_field = panic "runPhase:ModSummary field" + -- Some fields are not looked at by hscMain + mod_summary = ModSummary { ms_mod = mod, + ms_hsc_src = src_flavour, + ms_hspp_file = input_fn, + ms_hspp_opts = dflags, + ms_hspp_buf = hspp_buf, + ms_location = location4, + ms_hs_date = src_timestamp, + ms_obj_date = Nothing, + ms_imps = unused_field, + ms_srcimps = unused_field } -- run the compiler! mbResult <- hscCompileOneShot hsc_env @@ -749,7 +749,7 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma return (StopLn, dflags', Just location4, o_file) Just (HscRecomp hasStub) -> do when hasStub $ - do stub_o <- compileStub dflags' mod_name location4 + do stub_o <- compileStub dflags' mod location4 consIORef v_Ld_inputs stub_o -- In the case of hs-boot files, generate a dummy .o-boot -- stamp file for the benefit of Make @@ -762,7 +762,7 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma runPhase CmmCpp stop dflags basename suff input_fn get_output_fn maybe_loc = do - output_fn <- get_output_fn Cmm maybe_loc + output_fn <- get_output_fn dflags Cmm maybe_loc doCpp dflags False{-not raw-} True{-include CC opts-} input_fn output_fn return (Cmm, dflags, maybe_loc, output_fn) @@ -770,7 +770,7 @@ runPhase Cmm stop dflags basename suff input_fn get_output_fn maybe_loc = do let hsc_lang = hscMaybeAdjustTarget dflags stop HsSrcFile (hscTarget dflags) let next_phase = hscNextPhase dflags HsSrcFile hsc_lang - output_fn <- get_output_fn next_phase maybe_loc + output_fn <- get_output_fn dflags next_phase maybe_loc let dflags' = dflags { hscTarget = hsc_lang, hscOutName = output_fn, @@ -789,7 +789,7 @@ runPhase Cmm stop dflags basename suff input_fn get_output_fn maybe_loc -- way too many hacks, and I can't say I've ever used it anyway. runPhase cc_phase stop dflags basename suff input_fn get_output_fn maybe_loc - | cc_phase `eqPhase` Cc || cc_phase `eqPhase` HCc + | cc_phase `eqPhase` Cc || cc_phase `eqPhase` Ccpp || cc_phase `eqPhase` HCc = do let cc_opts = getOpts dflags opt_c hcc = cc_phase `eqPhase` HCc @@ -827,7 +827,7 @@ runPhase cc_phase stop dflags basename suff input_fn get_output_fn maybe_loc next_phase | hcc && mangle = Mangle | otherwise = As - output_fn <- get_output_fn next_phase maybe_loc + output_fn <- get_output_fn dflags next_phase maybe_loc let more_hcc_opts = @@ -851,7 +851,8 @@ runPhase cc_phase stop dflags basename suff input_fn get_output_fn maybe_loc -- compiling .hc files, by adding the -x c option. -- Also useful for plain .c files, just in case GHC saw a -- -x c option. - [ SysTools.Option "-x", SysTools.Option "c"] ++ + [ SysTools.Option "-x", if cc_phase `eqPhase` Ccpp + then SysTools.Option "c++" else SysTools.Option "c"] ++ [ SysTools.FileOption "" input_fn , SysTools.Option "-o" , SysTools.FileOption "" output_fn @@ -859,6 +860,15 @@ runPhase cc_phase stop dflags basename suff input_fn get_output_fn maybe_loc ++ map SysTools.Option ( md_c_flags ++ pic_c_flags +#ifdef sparc_TARGET_ARCH + -- We only support SparcV9 and better because V8 lacks an atomic CAS + -- instruction. Note that the user can still override this + -- (e.g., -mcpu=ultrasparc) as GCC picks the "best" -mcpu flag + -- regardless of the ordering. + -- + -- This is a temporary hack. + ++ ["-mcpu=v9"] +#endif ++ (if hcc && mangle then md_regd_c_flags else []) @@ -893,7 +903,7 @@ runPhase Mangle stop dflags _basename _suff input_fn get_output_fn maybe_loc next_phase | split = SplitMangle | otherwise = As - output_fn <- get_output_fn next_phase maybe_loc + output_fn <- get_output_fn dflags next_phase maybe_loc SysTools.runMangle dflags (map SysTools.Option mangler_opts ++ [ SysTools.FileOption "" input_fn @@ -937,7 +947,7 @@ runPhase As stop dflags _basename _suff input_fn get_output_fn maybe_loc = do let as_opts = getOpts dflags opt_a let cmdline_include_paths = includePaths dflags - output_fn <- get_output_fn StopLn maybe_loc + output_fn <- get_output_fn dflags StopLn maybe_loc -- we create directories for the object file, because it -- might be a hierarchical module. @@ -946,6 +956,16 @@ runPhase As stop dflags _basename _suff input_fn get_output_fn maybe_loc SysTools.runAs dflags (map SysTools.Option as_opts ++ [ SysTools.Option ("-I" ++ p) | p <- cmdline_include_paths ] +#ifdef sparc_TARGET_ARCH + -- 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. + ++ [ SysTools.Option "-mcpu=v9" ] +#endif ++ [ SysTools.Option "-c" , SysTools.FileOption "" input_fn , SysTools.Option "-o" @@ -957,7 +977,7 @@ runPhase As stop dflags _basename _suff input_fn get_output_fn maybe_loc runPhase SplitAs stop dflags basename _suff _input_fn get_output_fn maybe_loc = do - output_fn <- get_output_fn StopLn maybe_loc + output_fn <- get_output_fn dflags StopLn maybe_loc let (base_o, _) = splitFilename output_fn split_odir = base_o ++ "_split" @@ -1025,9 +1045,9 @@ runPhase SplitAs stop dflags basename _suff _input_fn get_output_fn maybe_loc -- we don't need the generality of a phase (MoveBinary is always -- done after linking and makes only sense in a parallel setup) -- HWL -runPhase_MoveBinary input_fn +runPhase_MoveBinary dflags input_fn = do - sysMan <- getSysMan + let sysMan = pgm_sysman dflags pvm_root <- getEnv "PVM_ROOT" pvm_arch <- getEnv "PVM_ARCH" let @@ -1224,7 +1244,7 @@ staticLink dflags o_files dep_packages = do -- parallel only: move binary to another dir -- HWL when (WayPar `elem` ways) - (do success <- runPhase_MoveBinary output_fn + (do success <- runPhase_MoveBinary dflags output_fn if success then return () else throwDyn (InstallationError ("cannot move binary to PVM dir"))) @@ -1272,12 +1292,8 @@ doMkDLL dflags o_files dep_packages = do let extra_ld_opts = getOpts dflags opt_dll let pstate = pkgState dflags - rts_id | ExtPackage id <- rtsPackageId pstate = id - | otherwise = panic "staticLink: rts package missing" - base_id | ExtPackage id <- basePackageId pstate = id - | otherwise = panic "staticLink: base package missing" - rts_pkg = getPackageDetails pstate rts_id - base_pkg = getPackageDetails pstate base_id + rts_pkg = getPackageDetails pstate rtsPackageId + base_pkg = getPackageDetails pstate basePackageId let extra_os = if static || no_hs_main then []