X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fmain%2FDriverPipeline.hs;h=7620d074bd5af21deeae2276bb1c4080be02c739;hb=fc9bbbab3fe56cf0ff5723abbdb0f496d257f34e;hp=ef2c239177dd99ba96cca42e46c10e20d7cefd27;hpb=7eb5e29b4a7b6fef55512bc7bf3308e712ca3eba;p=ghc-hetmet.git diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index ef2c239..7620d07 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1,3 +1,6 @@ +{-# OPTIONS -fno-cse #-} +-- -fno-cse is needed for GLOBAL_VAR's to behave properly + ----------------------------------------------------------------------------- -- -- GHC Driver @@ -32,10 +35,10 @@ import Finder import HscTypes import Outputable import Module -import UniqFM ( eltsUFM ) +import LazyUniqFM ( eltsUFM ) import ErrUtils import DynFlags -import StaticFlags ( v_Ld_inputs, opt_Static, opt_HardwireLibPaths, WayName(..) ) +import StaticFlags ( v_Ld_inputs, opt_Static, WayName(..) ) import Config import Panic import Util @@ -43,22 +46,21 @@ import StringBuffer ( hGetStringBuffer ) import BasicTypes ( SuccessFlag(..) ) import Maybes ( expectJust ) import ParserCoreUtils ( getCoreModuleName ) -import SrcLoc ( unLoc ) -import SrcLoc ( Located(..) ) +import SrcLoc +import FastString -import Control.Exception as Exception +import Exception import Data.IORef ( readIORef, writeIORef, IORef ) import GHC.Exts ( Int(..) ) import System.Directory import System.FilePath import System.IO -import SYSTEM_IO_ERROR as IO +import System.IO.Error as IO import Control.Monad import Data.List ( isSuffixOf ) import Data.Maybe import System.Exit import System.Environment -import System.FilePath -- --------------------------------------------------------------------------- -- Pre-process @@ -69,10 +71,10 @@ import System.FilePath -- We return the augmented DynFlags, because they contain the result -- of slurping in the OPTIONS pragmas -preprocess :: DynFlags -> (FilePath, Maybe Phase) -> IO (DynFlags, FilePath) -preprocess dflags (filename, mb_phase) = +preprocess :: HscEnv -> (FilePath, Maybe Phase) -> IO (DynFlags, FilePath) +preprocess hsc_env (filename, mb_phase) = ASSERT2(isJust mb_phase || isHaskellSrcFilename filename, text filename) - runPipeline anyHsc dflags (filename, mb_phase) + runPipeline anyHsc hsc_env (filename, mb_phase) Nothing Temporary Nothing{-no ModLocation-} -- --------------------------------------------------------------------------- @@ -94,7 +96,7 @@ compile :: HscEnv -> Maybe Linkable -- old linkable, if we have one -> IO (Maybe HomeModInfo) -- the complete HomeModInfo, if successful -compile hsc_env summary mod_index nmods mb_old_iface maybe_old_linkable +compile hsc_env0 summary mod_index nmods mb_old_iface maybe_old_linkable = do let dflags0 = ms_hspp_opts summary this_mod = ms_mod summary @@ -115,6 +117,7 @@ compile hsc_env summary mod_index nmods mb_old_iface maybe_old_linkable d -> d old_paths = includePaths dflags0 dflags = dflags0 { includePaths = current_dir : old_paths } + hsc_env = hsc_env0 {hsc_dflags = dflags} -- Figure out what lang we're generating let hsc_lang = hscMaybeAdjustTarget dflags StopLn src_flavour (hscTarget dflags) @@ -127,16 +130,16 @@ compile hsc_env summary mod_index nmods mb_old_iface maybe_old_linkable let dflags' = dflags { hscTarget = hsc_lang, hscOutName = output_fn, extCoreName = basename ++ ".hcr" } + let hsc_env' = hsc_env { hsc_dflags = dflags' } - -- -no-recomp should also work with --make + -- -fforce-recomp should also work with --make 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 let getStubLinkable False = return [] getStubLinkable True - = do stub_o <- compileStub dflags' this_mod location + = do stub_o <- compileStub hsc_env' this_mod location return [ DotO stub_o ] handleBatch HscNoRecomp @@ -158,7 +161,7 @@ compile hsc_env summary mod_index nmods mb_old_iface maybe_old_linkable -> return ([], ms_hs_date summary) -- We're in --make mode: finish the compilation pipeline. _other - -> do runPipeline StopLn dflags (output_fn,Nothing) + -> do runPipeline StopLn hsc_env' (output_fn,Nothing) (Just basename) Persistent (Just location) @@ -229,14 +232,14 @@ compile hsc_env summary mod_index nmods mb_old_iface maybe_old_linkable -- -odir obj, we would get obj/src/A_stub.o, which is wrong; we want -- obj/A_stub.o. -compileStub :: DynFlags -> Module -> ModLocation -> IO FilePath -compileStub dflags mod location = do +compileStub :: HscEnv -> Module -> ModLocation -> IO FilePath +compileStub hsc_env mod location = do let (o_base, o_ext) = splitExtension (ml_obj_file location) stub_o = (o_base ++ "_stub") <.> o_ext -- compile the _stub.c file w/ gcc - let (stub_c,_,_) = mkStubPaths dflags (moduleName mod) location - runPipeline StopLn dflags (stub_c,Nothing) Nothing + let (stub_c,_,_) = mkStubPaths (hsc_dflags hsc_env) (moduleName mod) location + runPipeline StopLn hsc_env (stub_c,Nothing) Nothing (SpecificFile stub_o) Nothing{-no ModLocation-} return stub_o @@ -294,7 +297,7 @@ link LinkBinary dflags batch_attempt_linking hpt -- if the modification time on the executable is later than the -- modification times on all of the objects, then omit linking - -- (unless the -no-recomp flag was given). + -- (unless the -fforce-recomp flag was given). e_exe_time <- IO.try $ getModificationTime exe_file extra_ld_inputs <- readIORef v_Ld_inputs extra_times <- mapM (IO.try . getModificationTime) extra_ld_inputs @@ -305,11 +308,11 @@ link LinkBinary dflags batch_attempt_linking hpt Right t -> any (t <) other_times 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.")) + then do debugTraceMsg dflags 2 (text exe_file <+> ptext (sLit "is up to date, linking not required.")) return Succeeded else do - debugTraceMsg dflags 1 (ptext SLIT("Linking") <+> text exe_file + debugTraceMsg dflags 1 (ptext (sLit "Linking") <+> text exe_file <+> text "...") -- Don't showPass in Batch mode; doLink will do that for us. @@ -338,18 +341,19 @@ panicBadLink other = panic ("link: GHC not built to link this way: " ++ -- ----------------------------------------------------------------------------- -- Compile files in one-shot mode. -oneShot :: DynFlags -> Phase -> [(String, Maybe Phase)] -> IO () -oneShot dflags stop_phase srcs = do - o_files <- mapM (compileFile dflags stop_phase) srcs - doLink dflags stop_phase o_files +oneShot :: HscEnv -> Phase -> [(String, Maybe Phase)] -> IO () +oneShot hsc_env stop_phase srcs = do + o_files <- mapM (compileFile hsc_env stop_phase) srcs + doLink (hsc_dflags hsc_env) stop_phase o_files -compileFile :: DynFlags -> Phase -> (FilePath, Maybe Phase) -> IO FilePath -compileFile dflags stop_phase (src, mb_phase) = do +compileFile :: HscEnv -> Phase -> (FilePath, Maybe Phase) -> IO FilePath +compileFile hsc_env stop_phase (src, mb_phase) = do exists <- doesFileExist src when (not exists) $ - throwDyn (CmdLineError ("does not exist: " ++ src)) + ghcError (CmdLineError ("does not exist: " ++ src)) let + dflags = hsc_dflags hsc_env split = dopt Opt_SplitObjs dflags mb_o_file = outputFile dflags ghc_link = ghcLink dflags -- Set by -c or -no-link @@ -367,7 +371,7 @@ compileFile dflags stop_phase (src, mb_phase) = do As | split -> SplitAs _ -> stop_phase - (_, out_file) <- runPipeline stop_phase' dflags + (_, out_file) <- runPipeline stop_phase' hsc_env (src, mb_phase) Nothing output Nothing{-no ModLocation-} return out_file @@ -387,7 +391,9 @@ 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 = [haskell98PackageId] + link_pkgs + | dopt Opt_AutoLinkPackages dflags = [haskell98PackageId] + | otherwise = [] -- --------------------------------------------------------------------------- @@ -414,16 +420,16 @@ data PipelineOutput runPipeline :: Phase -- When to stop - -> DynFlags -- Dynamic flags + -> HscEnv -- Compilation environment -> (FilePath,Maybe Phase) -- Input filename (and maybe -x suffix) -> Maybe FilePath -- original basename (if different from ^^^) -> PipelineOutput -- Output filename -> Maybe ModLocation -- A ModLocation, if this is a Haskell module -> IO (DynFlags, FilePath) -- (final flags, output filename) -runPipeline stop_phase dflags0 (input_fn, mb_phase) mb_basename output maybe_loc +runPipeline stop_phase hsc_env0 (input_fn, mb_phase) mb_basename output maybe_loc = do - let + let dflags0 = hsc_dflags hsc_env0 (input_basename, suffix) = splitExtension input_fn suffix' = drop 1 suffix -- strip off the . basename | Just b <- mb_basename = b @@ -431,6 +437,7 @@ runPipeline stop_phase dflags0 (input_fn, mb_phase) mb_basename output maybe_loc -- Decide where dump files should go based on the pipeline output dflags = dflags0 { dumpPrefix = Just (basename ++ ".") } + hsc_env = hsc_env0 {hsc_dflags = dflags} -- If we were given a -x flag, then use that phase to start from start_phase = fromMaybe (startPhase suffix') mb_phase @@ -443,7 +450,7 @@ runPipeline stop_phase dflags0 (input_fn, mb_phase) mb_basename output maybe_loc -- before B in a normal compilation pipeline. when (not (start_phase `happensBefore` stop_phase)) $ - throwDyn (UsageError + ghcError (UsageError ("cannot compile this file to desired target: " ++ input_fn)) @@ -453,7 +460,7 @@ runPipeline stop_phase dflags0 (input_fn, mb_phase) mb_basename output maybe_loc -- Execute the pipeline... (dflags', output_fn, maybe_loc) <- - pipeLoop dflags start_phase stop_phase input_fn + pipeLoop hsc_env start_phase stop_phase input_fn basename suffix' get_output_fn maybe_loc -- Sometimes, a compilation phase doesn't actually generate any output @@ -474,18 +481,18 @@ runPipeline stop_phase dflags0 (input_fn, mb_phase) mb_basename output maybe_loc -pipeLoop :: DynFlags -> Phase -> Phase +pipeLoop :: HscEnv -> Phase -> Phase -> FilePath -> String -> Suffix -> (DynFlags -> Phase -> Maybe ModLocation -> IO FilePath) -> Maybe ModLocation -> IO (DynFlags, FilePath, Maybe ModLocation) -pipeLoop dflags phase stop_phase +pipeLoop hsc_env phase stop_phase input_fn orig_basename orig_suff orig_get_output_fn maybe_loc | phase `eqPhase` stop_phase -- All done - = return (dflags, input_fn, maybe_loc) + = return (hsc_dflags hsc_env, input_fn, maybe_loc) | not (phase `happensBefore` stop_phase) -- Something has gone wrong. We'll try to cover all the cases when @@ -496,11 +503,12 @@ pipeLoop dflags phase stop_phase " but I wanted to stop at phase " ++ show stop_phase) | otherwise - = do { (next_phase, dflags', maybe_loc, output_fn) - <- runPhase phase stop_phase dflags orig_basename - orig_suff input_fn orig_get_output_fn maybe_loc - ; pipeLoop dflags' next_phase stop_phase output_fn - orig_basename orig_suff orig_get_output_fn maybe_loc } + = do (next_phase, dflags', maybe_loc, output_fn) + <- runPhase phase stop_phase hsc_env orig_basename + orig_suff input_fn orig_get_output_fn maybe_loc + let hsc_env' = hsc_env {hsc_dflags = dflags'} + pipeLoop hsc_env' next_phase stop_phase output_fn + orig_basename orig_suff orig_get_output_fn maybe_loc getOutputFilename :: Phase -> PipelineOutput -> String @@ -563,7 +571,7 @@ getOutputFilename stop_phase output basename runPhase :: Phase -- Do this phase first -> Phase -- Stop just before this phase - -> DynFlags + -> HscEnv -> String -- basename of original input source -> String -- its extension -> FilePath -- name of file which contains the input to this phase. @@ -582,18 +590,24 @@ runPhase :: Phase -- Do this phase first ------------------------------------------------------------------------------- -- Unlit phase -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 +runPhase (Unlit sf) _stop hsc_env _basename _suff input_fn get_output_fn maybe_loc + = do + let dflags = hsc_dflags hsc_env output_fn <- get_output_fn dflags (Cpp sf) maybe_loc - SysTools.runUnlit dflags - (map SysTools.Option unlit_flags ++ - [ SysTools.Option "-h" - , SysTools.Option input_fn - , SysTools.FileOption "" input_fn - , SysTools.FileOption "" output_fn - ]) + let unlit_flags = getOpts dflags opt_L + flags = map SysTools.Option unlit_flags ++ + [ -- The -h option passes the file name for unlit to + -- put in a #line directive + SysTools.Option "-h" + -- cpp interprets \b etc as escape sequences, + -- so we use / for filenames in pragmas + , SysTools.Option $ reslash Forwards $ normalise input_fn + , SysTools.FileOption "" input_fn + , SysTools.FileOption "" output_fn + ] + + SysTools.runUnlit dflags flags return (Cpp sf, dflags, maybe_loc, output_fn) @@ -601,10 +615,12 @@ runPhase (Unlit sf) _stop dflags _basename _suff input_fn get_output_fn maybe_lo -- Cpp phase : (a) gets OPTIONS out of file -- (b) runs cpp if necessary -runPhase (Cpp sf) _stop dflags0 basename suff input_fn get_output_fn maybe_loc - = do src_opts <- getOptionsFromFile input_fn - (dflags,unhandled_flags) <- parseDynamicFlags dflags0 (map unLoc src_opts) - checkProcessArgsResult unhandled_flags (basename <.> suff) +runPhase (Cpp sf) _stop hsc_env _basename _suff input_fn get_output_fn maybe_loc + = do let dflags0 = hsc_dflags hsc_env + src_opts <- getOptionsFromFile dflags0 input_fn + (dflags, unhandled_flags, warns) <- parseDynamicFlags dflags0 src_opts + handleFlagWarnings dflags warns + checkProcessArgsResult unhandled_flags if not (dopt Opt_Cpp dflags) then -- no need to preprocess CPP, just pass input file along @@ -618,8 +634,9 @@ runPhase (Cpp sf) _stop dflags0 basename suff input_fn get_output_fn maybe_loc ------------------------------------------------------------------------------- -- HsPp phase -runPhase (HsPp sf) _stop dflags basename suff input_fn get_output_fn maybe_loc - = do if not (dopt Opt_Pp dflags) then +runPhase (HsPp sf) _stop hsc_env basename suff input_fn get_output_fn maybe_loc + = do let dflags = hsc_dflags hsc_env + if not (dopt Opt_Pp dflags) then -- no need to preprocess, just pass input file along -- to the next phase of the pipeline. return (Hsc sf, dflags, maybe_loc, input_fn) @@ -641,8 +658,9 @@ runPhase (HsPp sf) _stop dflags basename suff input_fn get_output_fn maybe_loc -- Compilation of a single module, in "legacy" mode (_not_ under -- the direction of the compilation manager). -runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _maybe_loc +runPhase (Hsc src_flavour) stop hsc_env basename suff input_fn get_output_fn _maybe_loc = do -- normal Hsc mode, not mkdependHS + let dflags0 = hsc_dflags hsc_env -- we add the current directory (i.e. the directory in which -- the .hs files resides) to the include path, since this is @@ -733,10 +751,10 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma hscOutName = output_fn, extCoreName = basename ++ ".hcr" } - hsc_env <- newHscEnv dflags' + let hsc_env' = hsc_env {hsc_dflags = dflags'} -- Tell the finder cache about this module - mod <- addHomeModuleToFinder hsc_env mod_name location4 + mod <- addHomeModuleToFinder hsc_env' mod_name location4 -- Make the ModSummary to hand to hscMain let @@ -752,13 +770,13 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma ms_srcimps = src_imps } -- run the compiler! - mbResult <- hscCompileOneShot hsc_env + mbResult <- hscCompileOneShot hsc_env' mod_summary source_unchanged Nothing -- No iface Nothing -- No "module i of n" progress info case mbResult of - Nothing -> throwDyn (PhaseFailed "hsc" (ExitFailure 1)) + Nothing -> ghcError (PhaseFailed "hsc" (ExitFailure 1)) Just HscNoRecomp -> do SysTools.touch dflags' "Touching object file" o_file -- The .o file must have a later modification date @@ -767,7 +785,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 location4 + do stub_o <- compileStub hsc_env' 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 @@ -778,14 +796,16 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma ----------------------------------------------------------------------------- -- Cmm phase -runPhase CmmCpp _stop dflags _basename _suff input_fn get_output_fn maybe_loc +runPhase CmmCpp _stop hsc_env _basename _suff input_fn get_output_fn maybe_loc = do + let dflags = hsc_dflags hsc_env 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) -runPhase Cmm stop dflags basename _ input_fn get_output_fn maybe_loc +runPhase Cmm stop hsc_env basename _ input_fn get_output_fn maybe_loc = do + let dflags = hsc_dflags hsc_env let hsc_lang = hscMaybeAdjustTarget dflags stop HsSrcFile (hscTarget dflags) let next_phase = hscNextPhase dflags HsSrcFile hsc_lang output_fn <- get_output_fn dflags next_phase maybe_loc @@ -793,10 +813,11 @@ runPhase Cmm stop dflags basename _ input_fn get_output_fn maybe_loc let dflags' = dflags { hscTarget = hsc_lang, hscOutName = output_fn, extCoreName = basename ++ ".hcr" } + let hsc_env' = hsc_env {hsc_dflags = dflags'} - ok <- hscCmmFile dflags' input_fn + ok <- hscCmmFile hsc_env' input_fn - when (not ok) $ throwDyn (PhaseFailed "cmm" (ExitFailure 1)) + when (not ok) $ ghcError (PhaseFailed "cmm" (ExitFailure 1)) return (next_phase, dflags, maybe_loc, output_fn) @@ -806,9 +827,10 @@ runPhase Cmm stop dflags basename _ input_fn get_output_fn maybe_loc -- we don't support preprocessing .c files (with -E) now. Doing so introduces -- 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 +runPhase cc_phase _stop hsc_env _basename _suff input_fn get_output_fn maybe_loc | cc_phase `eqPhase` Cc || cc_phase `eqPhase` Ccpp || cc_phase `eqPhase` HCc - = do let cc_opts = getOpts dflags opt_c + = do let dflags = hsc_dflags hsc_env + let cc_opts = getOpts dflags opt_c hcc = cc_phase `eqPhase` HCc let cmdline_include_paths = includePaths dflags @@ -829,7 +851,20 @@ runPhase cc_phase _stop dflags _basename _suff input_fn get_output_fn maybe_loc let verb = getVerbFlag dflags - pkg_extra_cc_opts <- getPackageExtraCcOpts dflags pkgs + -- cc-options are not passed when compiling .hc files. Our + -- hc code doesn't not #include any header files anyway, so these + -- options aren't necessary. + pkg_extra_cc_opts <- + if cc_phase `eqPhase` HCc + then return [] + else getPackageExtraCcOpts dflags pkgs + +#ifdef darwin_TARGET_OS + pkg_framework_paths <- getPackageFrameworkPath dflags pkgs + let cmdline_framework_paths = frameworkPaths dflags + let framework_paths = map ("-F"++) + (cmdline_framework_paths ++ pkg_framework_paths) +#endif let split_objs = dopt Opt_SplitObjs dflags split_opt | hcc && split_objs = [ "-DUSE_SPLIT_MARKERS" ] @@ -903,6 +938,9 @@ runPhase cc_phase _stop dflags _basename _suff input_fn get_output_fn maybe_loc else []) ++ [ verb, "-S", "-Wimplicit", cc_opt ] ++ [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ] +#ifdef darwin_TARGET_OS + ++ framework_paths +#endif ++ cc_opts ++ split_opt ++ include_paths @@ -916,8 +954,9 @@ runPhase cc_phase _stop dflags _basename _suff input_fn get_output_fn maybe_loc ----------------------------------------------------------------------------- -- Mangle phase -runPhase Mangle _stop dflags _basename _suff input_fn get_output_fn maybe_loc - = do let mangler_opts = getOpts dflags opt_m +runPhase Mangle _stop hsc_env _basename _suff input_fn get_output_fn maybe_loc + = do let dflags = hsc_dflags hsc_env + let mangler_opts = getOpts dflags opt_m #if i386_TARGET_ARCH machdep_opts <- return [ show (stolen_x86_regs dflags) ] @@ -942,9 +981,10 @@ runPhase Mangle _stop dflags _basename _suff input_fn get_output_fn maybe_loc ----------------------------------------------------------------------------- -- Splitting phase -runPhase SplitMangle _stop dflags _basename _suff input_fn _get_output_fn maybe_loc +runPhase SplitMangle _stop hsc_env _basename _suff input_fn _get_output_fn maybe_loc = do -- tmp_pfx is the prefix used for the split .s files -- We also use it as the file to contain the no. of split .s files (sigh) + let dflags = hsc_dflags hsc_env split_s_prefix <- SysTools.newTempName dflags "split" let n_files_fn = split_s_prefix @@ -969,8 +1009,9 @@ runPhase SplitMangle _stop dflags _basename _suff input_fn _get_output_fn maybe_ ----------------------------------------------------------------------------- -- As phase -runPhase As _stop dflags _basename _suff input_fn get_output_fn maybe_loc - = do let as_opts = getOpts dflags opt_a +runPhase As _stop hsc_env _basename _suff input_fn get_output_fn maybe_loc + = do let dflags = hsc_dflags hsc_env + let as_opts = getOpts dflags opt_a let cmdline_include_paths = includePaths dflags output_fn <- get_output_fn dflags StopLn maybe_loc @@ -1001,8 +1042,9 @@ runPhase As _stop dflags _basename _suff input_fn get_output_fn maybe_loc return (StopLn, dflags, maybe_loc, output_fn) -runPhase SplitAs _stop dflags _basename _suff _input_fn get_output_fn maybe_loc +runPhase SplitAs _stop hsc_env _basename _suff _input_fn get_output_fn maybe_loc = do + let dflags = hsc_dflags hsc_env output_fn <- get_output_fn dflags StopLn maybe_loc let base_o = dropExtension output_fn @@ -1071,22 +1113,58 @@ runPhase other _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 :: DynFlags -> FilePath -> IO Bool -runPhase_MoveBinary dflags input_fn - = do +runPhase_MoveBinary :: DynFlags -> FilePath -> [PackageId] -> IO Bool +runPhase_MoveBinary dflags input_fn dep_packages + | WayPar `elem` (wayNames dflags) && not opt_Static = + panic ("Don't know how to combine PVM wrapper and dynamic wrapper") + | WayPar `elem` (wayNames dflags) = do let sysMan = pgm_sysman dflags pvm_root <- getEnv "PVM_ROOT" pvm_arch <- getEnv "PVM_ARCH" - let + let pvm_executable_base = "=" ++ input_fn pvm_executable = pvm_root ++ "/bin/" ++ pvm_arch ++ "/" ++ pvm_executable_base -- nuke old binary; maybe use configur'ed names for cp and rm? - Panic.try (removeFile pvm_executable) + tryIO (removeFile pvm_executable) -- move the newly created binary into PVM land copy dflags "copying PVM executable" input_fn pvm_executable -- generate a wrapper script for running a parallel prg under PVM writeFile input_fn (mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan) return True + | not opt_Static = + case (dynLibLoader dflags) of + Wrapped wrapmode -> + do + let (o_base, o_ext) = splitExtension input_fn + let wrapped_executable | o_ext == "exe" = (o_base ++ "_real") <.> o_ext + | otherwise = input_fn ++ "_real" + behaviour <- wrapper_behaviour dflags wrapmode dep_packages + + -- THINKME isn't this possible to do a bit nicer? + let behaviour' = concatMap (\x -> if x=='\\' then "\\\\" else [x]) behaviour + renameFile input_fn wrapped_executable + let rtsDetails = (getPackageDetails (pkgState dflags) rtsPackageId); + SysTools.runCc dflags + ([ SysTools.FileOption "" ((head (libraryDirs rtsDetails)) ++ "/dyn-wrapper.c") + , SysTools.Option ("-DBEHAVIOUR=\"" ++ behaviour' ++ "\"") + , SysTools.Option "-o" + , SysTools.FileOption "" input_fn + ] ++ map (SysTools.FileOption "-I") (includeDirs rtsDetails)) + return True + _ -> return True + | otherwise = return True + +wrapper_behaviour :: DynFlags -> Maybe [Char] -> [PackageId] -> IO [Char] +wrapper_behaviour dflags mode dep_packages = + let seperateBySemiColon strs = tail $ concatMap (';':) strs + in case mode of + Nothing -> do + pkg_lib_paths <- getPackageLibraryPath dflags dep_packages + return ('H' : (seperateBySemiColon pkg_lib_paths)) + Just s -> do + allpkg <- getPreloadPackagesAnd dflags dep_packages + putStrLn (unwords (map (packageIdString . packageConfigId) allpkg)) + return $ 'F':s ++ ';':(seperateBySemiColon (map (packageIdString . packageConfigId) allpkg)) -- generates a Perl skript starting a parallel prg under PVM mk_pvm_wrapper_script :: String -> String -> String -> String @@ -1146,17 +1224,6 @@ mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan = unlines $ ] ----------------------------------------------------------------------------- --- Complain about non-dynamic flags in OPTIONS pragmas - -checkProcessArgsResult :: [String] -> FilePath -> IO () -checkProcessArgsResult flags filename - = do when (notNull flags) (throwDyn (ProgramError ( - showSDoc (hang (text filename <> char ':') - 4 (text "unknown flags in {-# OPTIONS #-} pragma:" <+> - hsep (map text flags))) - ))) - ------------------------------------------------------------------------------ -- Look for the /* GHC_PACKAGES ... */ comment at the top of a .hc file getHCFilePackages :: FilePath -> IO [PackageId] @@ -1193,8 +1260,12 @@ linkBinary dflags o_files dep_packages = do pkg_lib_paths <- getPackageLibraryPath dflags dep_packages let pkg_lib_path_opts = concat (map get_pkg_lib_path_opts pkg_lib_paths) - get_pkg_lib_path_opts l | opt_HardwireLibPaths && not opt_Static = ["-L" ++ l, "-Wl,-rpath", "-Wl," ++ l] - | otherwise = ["-L" ++ l] +#ifdef linux_TARGET_OS + get_pkg_lib_path_opts l | (dynLibLoader dflags)==SystemDependent && not opt_Static = ["-L" ++ l, "-Wl,-rpath", "-Wl," ++ l] + | otherwise = ["-L" ++ l] +#else + get_pkg_lib_path_opts l = ["-L" ++ l] +#endif let lib_paths = libraryPaths dflags let lib_path_opts = map ("-L"++) lib_paths @@ -1215,7 +1286,12 @@ linkBinary dflags o_files dep_packages = do framework_opts = concat [ ["-framework", fw] | fw <- reverse frameworks ] -- reverse because they're added in reverse order from the cmd line #endif - +#ifdef mingw32_TARGET_OS + let dynMain = if not opt_Static then + (head (libraryDirs (getPackageDetails (pkgState dflags) rtsPackageId))) ++ "/Main.dyn_o" + else + "" +#endif -- probably _stub.o files extra_ld_inputs <- readIORef v_Ld_inputs @@ -1257,6 +1333,9 @@ linkBinary dflags o_files dep_packages = do ++ map SysTools.Option ( md_c_flags ++ o_files +#ifdef mingw32_TARGET_OS + ++ [dynMain] +#endif ++ extra_ld_inputs ++ lib_path_opts ++ extra_ld_opts @@ -1276,10 +1355,9 @@ linkBinary dflags o_files dep_packages = do )) -- parallel only: move binary to another dir -- HWL - when (WayPar `elem` ways) - (do success <- runPhase_MoveBinary dflags output_fn - if success then return () - else throwDyn (InstallationError ("cannot move binary to PVM dir"))) + success <- runPhase_MoveBinary dflags output_fn dep_packages + if success then return () + else ghcError (InstallationError ("cannot move binary")) exeFileName :: DynFlags -> FilePath @@ -1360,13 +1438,19 @@ linkDynLib dflags o_files dep_packages = do let verb = getVerbFlag dflags let o_file = outputFile dflags - pkg_lib_paths <- getPackageLibraryPath dflags dep_packages + -- We don't want to link our dynamic libs against the RTS package, + -- because the RTS lib comes in several flavours and we want to be + -- able to pick the flavour when a binary is linked. + pkgs <- getPreloadPackagesAnd dflags dep_packages + let pkgs_no_rts = filter ((/= rtsPackageId) . packageConfigId) pkgs + + let pkg_lib_paths = collectLibraryPaths pkgs_no_rts let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths let lib_paths = libraryPaths dflags let lib_path_opts = map ("-L"++) lib_paths - pkg_link_opts <- getPackageLinkOpts dflags dep_packages + let pkg_link_opts = collectLinkOpts dflags pkgs_no_rts -- probably _stub.o files extra_ld_inputs <- readIORef v_Ld_inputs @@ -1564,6 +1648,5 @@ hscMaybeAdjustTarget dflags stop _ current_hsc_lang -- otherwise, stick to the plan | otherwise = current_hsc_lang -v_Split_info :: IORef (String, Int) GLOBAL_VAR(v_Split_info, ("",0), (String,Int)) -- The split prefix and number of files