X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fmain%2FDriverPipeline.hs;h=59535f040cd6d852d7efbe58bab6a565ba1bf93d;hp=e20bc569409ea3000ffa5a66b03b9e0091e28d10;hb=4c6a3f787abcaed009a574196d82237d9ae64fc8;hpb=0065d5ab628975892cea1ec7303f968c3338cbe1 diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index e20bc56..59535f0 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -12,16 +12,13 @@ module DriverPipeline ( oneShot, compileFile, -- Interfaces for the batch-mode driver - staticLink, + linkBinary, -- Interfaces for the compilation manager (interpreted/batch-mode) preprocess, - compile, CompResult(..), + compile, link, - -- DLL building - doMkDLL, - ) where #include "HsVersions.h" @@ -29,13 +26,13 @@ module DriverPipeline ( import Packages import HeaderInfo import DriverPhases -import SysTools ( newTempName, addFilesToClean, getSysMan, copy ) -import qualified SysTools +import SysTools import HscMain import Finder import HscTypes import Outputable import Module +import LazyUniqFM ( eltsUFM ) import ErrUtils import DynFlags import StaticFlags ( v_Ld_inputs, opt_Static, WayName(..) ) @@ -48,18 +45,20 @@ import Maybes ( expectJust ) import ParserCoreUtils ( getCoreModuleName ) import SrcLoc ( unLoc ) import SrcLoc ( Located(..) ) - -import EXCEPTION -import DATA_IOREF ( readIORef, writeIORef, IORef ) -import GLAEXTS ( Int(..) ) - -import Directory -import System -import IO -import Monad +import FastString + +import Control.Exception as 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 Control.Monad import Data.List ( isSuffixOf ) -import Maybe - +import Data.Maybe +import System.Exit +import System.Environment -- --------------------------------------------------------------------------- -- Pre-process @@ -73,7 +72,8 @@ import Maybe preprocess :: DynFlags -> (FilePath, Maybe Phase) -> IO (DynFlags, FilePath) preprocess dflags (filename, mb_phase) = ASSERT2(isJust mb_phase || isHaskellSrcFilename filename, text filename) - runPipeline anyHsc dflags (filename, mb_phase) Temporary Nothing{-no ModLocation-} + runPipeline anyHsc dflags (filename, mb_phase) + Nothing Temporary Nothing{-no ModLocation-} -- --------------------------------------------------------------------------- -- Compile @@ -88,45 +88,31 @@ preprocess dflags (filename, mb_phase) = -- NB. No old interface can also mean that the source has changed. compile :: HscEnv - -> ModSummary - -> Maybe Linkable -- Just linkable <=> source unchanged - -> Maybe ModIface -- Old interface, if available - -> Int -> Int - -> IO CompResult - -data CompResult - = CompOK ModDetails -- New details - ModIface -- New iface - (Maybe Linkable) -- a Maybe, for the same reasons as hm_linkable - - | CompErrs - - -compile hsc_env mod_summary maybe_old_linkable old_iface mod_index nmods = do - - let dflags0 = ms_hspp_opts mod_summary - this_mod = ms_mod mod_summary - src_flavour = ms_hsc_src mod_summary - - have_object - | Just l <- maybe_old_linkable, isObjectLinkable l = True - | otherwise = False - - -- FIXME: We need to know whether or not we're recompiling the file. Move this to HscMain? - --showPass dflags0 ("Compiling " ++ showModMsg have_object mod_summary) - - let location = ms_location mod_summary - let input_fn = expectJust "compile:hs" (ml_hs_file location) - let input_fnpp = ms_hspp_file mod_summary + -> ModSummary -- summary for module being compiled + -> Int -> Int -- module N of M + -> Maybe ModIface -- old interface, if we have one + -> 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 + = do + let dflags0 = ms_hspp_opts summary + this_mod = ms_mod summary + src_flavour = ms_hsc_src summary + location = ms_location summary + input_fn = expectJust "compile:hs" (ml_hs_file location) + input_fnpp = ms_hspp_file summary debugTraceMsg dflags0 2 (text "compile: input file" <+> text input_fnpp) - let (basename, _) = splitFilename input_fn + let basename = dropExtension input_fn -- We add the directory in which the .hs files resides) to the import path. -- This is needed when we try to compile the .hc file later, if it -- imports a _stub.h file that we created here. - let current_dir = directoryOf basename + let current_dir = case takeDirectory basename of + "" -> "." -- XXX Hack + d -> d old_paths = includePaths dflags0 dflags = dflags0 { includePaths = current_dir : old_paths } @@ -135,16 +121,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 @@ -153,36 +139,43 @@ compile hsc_env mod_summary maybe_old_linkable old_iface mod_index nmods = do = do stub_o <- compileStub dflags' this_mod location return [ DotO stub_o ] - handleBatch (HscNoRecomp, iface, details) + handleBatch HscNoRecomp = ASSERT (isJust maybe_old_linkable) - return (CompOK details iface maybe_old_linkable) - handleBatch (HscRecomp hasStub, iface, details) + return maybe_old_linkable + + handleBatch (HscRecomp hasStub) | isHsBoot src_flavour - = return (CompOK details iface Nothing) + = do when (isObjectTarget hsc_lang) $ -- interpreted reaches here too + SysTools.touch dflags' "Touching object file" + object_filename + return maybe_old_linkable + | otherwise = do stub_unlinked <- getStubLinkable hasStub (hs_unlinked, unlinked_time) <- case hsc_lang of HscNothing - -> return ([], ms_hs_date mod_summary) + -> return ([], ms_hs_date summary) -- We're in --make mode: finish the compilation pipeline. _other - -> do runPipeline StopLn dflags (output_fn,Nothing) Persistent + -> do runPipeline StopLn dflags (output_fn,Nothing) + (Just basename) + Persistent (Just location) -- The object filename comes from the ModLocation o_time <- getModificationTime object_filename return ([DotO object_filename], o_time) let linkable = LM unlinked_time this_mod (hs_unlinked ++ stub_unlinked) - return (CompOK details iface (Just linkable)) + return (Just linkable) - handleInterpreted (InteractiveNoRecomp, iface, details) + handleInterpreted InteractiveNoRecomp = ASSERT (isJust maybe_old_linkable) - return (CompOK details iface maybe_old_linkable) - handleInterpreted (InteractiveRecomp hasStub comp_bc, iface, details) + return maybe_old_linkable + handleInterpreted (InteractiveRecomp hasStub comp_bc modBreaks) = do stub_unlinked <- getStubLinkable hasStub - let hs_unlinked = [BCOs comp_bc] - unlinked_time = ms_hs_date mod_summary + let hs_unlinked = [BCOs comp_bc modBreaks] + unlinked_time = ms_hs_date summary -- Why do we use the timestamp of the source file here, -- rather than the current time? This works better in -- the case where the local clock is out of sync @@ -191,24 +184,31 @@ compile hsc_env mod_summary maybe_old_linkable old_iface mod_index nmods = do -- be out of date. let linkable = LM unlinked_time this_mod (hs_unlinked ++ stub_unlinked) - return (CompOK details iface (Just linkable)) + return (Just linkable) - let runCompiler compiler handle - = do mbResult <- compiler hsc_env' mod_summary - source_unchanged old_iface + let -- runCompiler :: Compiler result -> (result -> Maybe Linkable) + -- -> IO (Maybe HomeModInfo) + runCompiler compiler handle + = do mbResult <- compiler hsc_env' summary source_unchanged mb_old_iface (Just (mod_index, nmods)) case mbResult of - Nothing -> return CompErrs - Just result -> handle result + Nothing -> return Nothing + Just (result, iface, details) -> do + linkable <- handle result + return (Just HomeModInfo{ hm_details = details, + hm_iface = iface, + hm_linkable = linkable }) -- run the compiler case hsc_lang of - HscInterpreted | not (isHsBoot src_flavour) -- We can't compile boot files to - -- bytecode so don't even try. - -> runCompiler hscCompileInteractive handleInterpreted - HscNothing - -> runCompiler hscCompileNothing handleBatch - _other - -> runCompiler hscCompileBatch handleBatch + HscInterpreted + | isHsBoot src_flavour -> + runCompiler hscCompileNothing handleBatch + | otherwise -> + runCompiler hscCompileInteractive handleInterpreted + HscNothing -> + runCompiler hscCompileNothing handleBatch + _other -> + runCompiler hscCompileBatch handleBatch ----------------------------------------------------------------------------- -- stub .h and .c files (for foreign export support) @@ -231,12 +231,12 @@ compile hsc_env mod_summary maybe_old_linkable old_iface mod_index nmods = do compileStub :: DynFlags -> Module -> ModLocation -> IO FilePath compileStub dflags mod location = do - let (o_base, o_ext) = splitFilename (ml_obj_file location) - stub_o = o_base ++ "_stub" `joinFileExt` o_ext + 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 mod location - runPipeline StopLn dflags (stub_c,Nothing) + let (stub_c,_,_) = mkStubPaths dflags (moduleName mod) location + runPipeline StopLn dflags (stub_c,Nothing) Nothing (SpecificFile stub_o) Nothing{-no ModLocation-} return stub_o @@ -245,10 +245,10 @@ compileStub dflags mod location = do -- --------------------------------------------------------------------------- -- Link -link :: GhcMode -- interactive or batch - -> DynFlags -- dynamic flags - -> Bool -- attempt linking in batch mode? - -> HomePackageTable -- what to link +link :: GhcLink -- interactive or batch + -> DynFlags -- dynamic flags + -> Bool -- attempt linking in batch mode? + -> HomePackageTable -- what to link -> IO SuccessFlag -- For the moment, in the batch linker, we don't bother to tell doLink @@ -259,73 +259,82 @@ link :: GhcMode -- interactive or batch -- will succeed. #ifdef GHCI -link Interactive dflags batch_attempt_linking hpt +link LinkInMemory _ _ _ = do -- Not Linking...(demand linker will do the job) - return Succeeded + return Succeeded #endif -link JustTypecheck dflags batch_attempt_linking hpt +link NoLink _ _ _ = return Succeeded -link BatchCompile dflags batch_attempt_linking hpt +link LinkBinary dflags batch_attempt_linking hpt | batch_attempt_linking - = do - let - home_mod_infos = moduleEnvElts hpt + = do + let + home_mod_infos = eltsUFM hpt - -- the packages we depend on - pkg_deps = concatMap (dep_pkgs . mi_deps . hm_iface) home_mod_infos + -- the packages we depend on + pkg_deps = concatMap (dep_pkgs . mi_deps . hm_iface) home_mod_infos - -- the linkables to link - linkables = map (expectJust "link".hm_linkable) home_mod_infos + -- the linkables to link + linkables = map (expectJust "link".hm_linkable) home_mod_infos debugTraceMsg dflags 3 (text "link: linkables are ..." $$ vcat (map ppr linkables)) - -- check for the -no-link flag - if isNoLink (ghcLink dflags) - then do debugTraceMsg dflags 3 (text "link(batch): linking omitted (-c flag given).") - return Succeeded - else do - - let getOfiles (LM _ _ us) = map nameOfObject (filter isObject us) - obj_files = concatMap getOfiles linkables - - exe_file = exeFileName dflags - - -- 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). - e_exe_time <- IO.try $ getModificationTime exe_file - let linking_needed - | Left _ <- e_exe_time = True - | Right t <- e_exe_time = - any (t <) (map linkableTime linkables) - - if dopt Opt_RecompChecking dflags && not linking_needed - then do debugTraceMsg dflags 1 (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 - <+> text "...") - - -- Don't showPass in Batch mode; doLink will do that for us. - let link = case ghcLink dflags of - MkDLL -> doMkDLL - StaticLink -> staticLink - link dflags obj_files pkg_deps + -- check for the -no-link flag + if isNoLink (ghcLink dflags) + then do debugTraceMsg dflags 3 (text "link(batch): linking omitted (-c flag given).") + return Succeeded + else do + + let getOfiles (LM _ _ us) = map nameOfObject (filter isObject us) + obj_files = concatMap getOfiles linkables + + exe_file = exeFileName dflags + + -- 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). + e_exe_time <- IO.try $ getModificationTime exe_file + extra_ld_inputs <- readIORef v_Ld_inputs + extra_times <- mapM (IO.try . getModificationTime) extra_ld_inputs + let other_times = map linkableTime linkables + ++ [ t' | Right t' <- extra_times ] + linking_needed = case e_exe_time of + Left _ -> True + 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.")) + return Succeeded + else do + + debugTraceMsg dflags 1 (ptext SLIT("Linking") <+> text exe_file + <+> text "...") + + -- Don't showPass in Batch mode; doLink will do that for us. + let link = case ghcLink dflags of + LinkBinary -> linkBinary + LinkDynLib -> linkDynLib + other -> panicBadLink other + link dflags obj_files pkg_deps debugTraceMsg dflags 3 (text "link: done") - -- staticLink only returns if it succeeds + -- linkBinary only returns if it succeeds return Succeeded | otherwise = do debugTraceMsg dflags 3 (text "link(batch): upsweep (partially) failed OR" $$ text " Main.main not exported; not linking.") return Succeeded - +-- warning suppression +link other _ _ _ = panicBadLink other + +panicBadLink :: GhcLink -> a +panicBadLink other = panic ("link: GHC not built to link this way: " ++ + show other) -- ----------------------------------------------------------------------------- -- Compile files in one-shot mode. @@ -356,10 +365,11 @@ compileFile dflags stop_phase (src, mb_phase) = do stop_phase' = case stop_phase of As | split -> SplitAs - other -> stop_phase + _ -> stop_phase (_, out_file) <- runPipeline stop_phase' dflags - (src, mb_phase) output Nothing{-no ModLocation-} + (src, mb_phase) Nothing output + Nothing{-no ModLocation-} return out_file @@ -371,14 +381,13 @@ doLink dflags stop_phase o_files | otherwise = case ghcLink dflags of NoLink -> return () - StaticLink -> staticLink dflags o_files link_pkgs - MkDLL -> doMkDLL dflags o_files link_pkgs + LinkBinary -> linkBinary dflags o_files link_pkgs + LinkDynLib -> linkDynLib dflags o_files [] + other -> panicBadLink other 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] -- --------------------------------------------------------------------------- @@ -407,18 +416,24 @@ runPipeline :: Phase -- When to stop -> DynFlags -- Dynamic flags -> (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 dflags (input_fn, mb_phase) output maybe_loc +runPipeline stop_phase dflags0 (input_fn, mb_phase) mb_basename output maybe_loc = do - let (basename, suffix) = splitFilename input_fn + let + (input_basename, suffix) = splitExtension input_fn + suffix' = drop 1 suffix -- strip off the . + basename | Just b <- mb_basename = b + | otherwise = input_basename + + -- Decide where dump files should go based on the pipeline output + dflags = dflags0 { dumpPrefix = Just (basename ++ ".") } -- If we were given a -x flag, then use that phase to start from - start_phase - | Just x_phase <- mb_phase = x_phase - | otherwise = startPhase suffix + start_phase = fromMaybe (startPhase suffix') mb_phase -- We want to catch cases of "you can't get there from here" before -- we start the pipeline, because otherwise it will just run off the @@ -434,32 +449,34 @@ 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) <- pipeLoop dflags start_phase stop_phase input_fn - basename suffix get_output_fn maybe_loc + basename suffix' get_output_fn maybe_loc -- Sometimes, a compilation phase doesn't actually generate any output -- (eg. the CPP phase when -fcpp is not turned on). If we end on this -- stage, but we wanted to keep the output, then we have to explicitly - -- copy the file. + -- copy the file, remembering to prepend a {-# LINE #-} pragma so that + -- further compilation stages can tell what the original filename was. case output of Temporary -> return (dflags', output_fn) _other -> - do final_fn <- get_output_fn stop_phase maybe_loc - when (final_fn /= output_fn) $ - copy dflags ("Copying `" ++ output_fn ++ "' to `" ++ final_fn - ++ "'") output_fn final_fn + do final_fn <- get_output_fn dflags' stop_phase maybe_loc + when (final_fn /= output_fn) $ do + let msg = ("Copying `" ++ output_fn ++"' to `" ++ final_fn ++ "'") + line_prag = Just ("{-# LINE 1 \"" ++ input_fn ++ "\" #-}\n") + copyWithHeader dflags msg line_prag output_fn final_fn return (dflags', final_fn) - + 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 +503,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 @@ -526,11 +543,11 @@ getOutputFilename dflags stop_phase output basename | StopLn <- next_phase = return odir_persistent | otherwise = return persistent - persistent = basename `joinFileExt` suffix + persistent = basename <.> suffix odir_persistent | Just loc <- maybe_location = ml_obj_file loc - | Just d <- odir = d `joinFileName` persistent + | Just d <- odir = d persistent | otherwise = persistent @@ -550,7 +567,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 @@ -566,17 +583,22 @@ 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 - output_fn <- get_output_fn (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 - ]) + = do + output_fn <- get_output_fn dflags (Cpp sf) maybe_loc + + 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) @@ -587,14 +609,14 @@ runPhase (Unlit sf) _stop dflags _basename _suff input_fn get_output_fn maybe_lo 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 `joinFileExt` suff) + checkProcessArgsResult unhandled_flags (basename <.> suff) if not (dopt Opt_Cpp dflags) then -- no need to preprocess CPP, just pass input file along -- 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) @@ -608,8 +630,8 @@ runPhase (HsPp sf) _stop dflags basename suff input_fn get_output_fn maybe_loc return (Hsc sf, dflags, maybe_loc, input_fn) else do let hspp_opts = getOpts dflags opt_F - let orig_fn = basename `joinFileExt` suff - output_fn <- get_output_fn (Hsc sf) maybe_loc + let orig_fn = basename <.> suff + output_fn <- get_output_fn dflags (Hsc sf) maybe_loc SysTools.runPp dflags ( [ SysTools.Option orig_fn , SysTools.Option input_fn @@ -628,23 +650,25 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma = do -- normal Hsc mode, not mkdependHS -- we add the current directory (i.e. the directory in which - -- the .hs files resides) to the import path, since this is + -- the .hs files resides) to the include path, since this is -- what gcc does, and it's probably what you want. - let current_dir = directoryOf basename + let current_dir = case takeDirectory basename of + "" -> "." -- XXX Hack + d -> d paths = includePaths dflags0 dflags = dflags0 { includePaths = current_dir : paths } -- gather the imports and module name - (hspp_buf,mod_name) <- + (hspp_buf,mod_name,imps,src_imps) <- 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 - ; return (Just buf, mod_name) } + _ -> do { buf <- hGetStringBuffer input_fn + ; (src_imps,imps,L _ mod_name) <- getImports dflags buf input_fn (basename <.> suff) + ; return (Just buf, mod_name, imps, src_imps) } -- Build a ModLocation to pass to hscMain. -- The source filename is rather irrelevant by now, but it's used @@ -677,22 +701,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 +711,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 <.> 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 +732,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 +741,20 @@ 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 + 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 = imps, + ms_srcimps = src_imps } -- run the compiler! mbResult <- hscCompileOneShot hsc_env @@ -749,7 +772,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 @@ -760,17 +783,17 @@ 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 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) -runPhase Cmm stop dflags basename suff input_fn get_output_fn maybe_loc +runPhase Cmm stop dflags basename _ 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, @@ -788,8 +811,8 @@ runPhase Cmm stop dflags basename suff 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 - | cc_phase `eqPhase` Cc || cc_phase `eqPhase` HCc +runPhase cc_phase _stop dflags _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 hcc = cc_phase `eqPhase` HCc @@ -806,18 +829,24 @@ runPhase cc_phase stop dflags basename suff input_fn get_output_fn maybe_loc (cmdline_include_paths ++ pkg_include_dirs) let (md_c_flags, md_regd_c_flags) = machdepCCOpts dflags + gcc_extra_viac_flags <- getExtraViaCOpts dflags let pic_c_flags = picCCOpts dflags let verb = getVerbFlag dflags pkg_extra_cc_opts <- 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" ] | otherwise = [ ] - let excessPrecision = dopt Opt_ExcessPrecision dflags - let cc_opt | optLevel dflags >= 2 = "-O2" | otherwise = "-O" @@ -827,7 +856,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 = @@ -836,7 +865,9 @@ runPhase cc_phase stop dflags basename suff input_fn get_output_fn maybe_loc -- than a double, which leads to unpredictable results. -- By default, we turn this off with -ffloat-store unless -- the user specified -fexcess-precision. - (if excessPrecision then [] else [ "-ffloat-store" ]) ++ + (if dopt Opt_ExcessPrecision dflags + then [] + else [ "-ffloat-store" ]) ++ #endif -- gcc's -fstrict-aliasing allows two accesses to memory -- to be considered non-aliasing if they have different types. @@ -851,7 +882,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,14 +891,33 @@ 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 []) + ++ (if hcc + then if mangle + then gcc_extra_viac_flags + else filter (=="-fwrapv") + gcc_extra_viac_flags + -- still want -fwrapv even for unreg'd + else []) ++ (if hcc then more_hcc_opts else []) ++ [ verb, "-S", "-Wimplicit", cc_opt ] ++ [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ] +#ifdef darwin_TARGET_OS + ++ framework_paths +#endif ++ cc_opts ++ split_opt ++ include_paths @@ -880,7 +931,7 @@ 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 +runPhase Mangle _stop dflags _basename _suff input_fn get_output_fn maybe_loc = do let mangler_opts = getOpts dflags opt_m #if i386_TARGET_ARCH @@ -893,7 +944,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 @@ -906,7 +957,7 @@ 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 dflags _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) split_s_prefix <- SysTools.newTempName dflags "split" @@ -933,19 +984,29 @@ runPhase SplitMangle stop dflags _basename _suff input_fn get_output_fn maybe_lo ----------------------------------------------------------------------------- -- As phase -runPhase As stop dflags _basename _suff input_fn get_output_fn maybe_loc +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. - createDirectoryHierarchy (directoryOf output_fn) + createDirectoryHierarchy (takeDirectory output_fn) 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" @@ -955,91 +1016,128 @@ 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 - = do - output_fn <- get_output_fn StopLn maybe_loc - - let (base_o, _) = splitFilename output_fn - split_odir = base_o ++ "_split" - osuf = objectSuf dflags - - createDirectoryHierarchy 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 <- getDirectoryContents split_odir - mapM_ removeFile $ map (split_odir `joinFileName`) - $ filter (osuf `isSuffixOf`) fs - - let as_opts = getOpts dflags opt_a - - (split_s_prefix, n) <- readIORef v_Split_info - - let split_s n = split_s_prefix ++ "__" ++ show n `joinFileExt` "s" - split_obj n = split_odir `joinFileName` - filenameOf base_o ++ "__" ++ show n - `joinFileExt` osuf - - let assemble_file n - = SysTools.runAs dflags - (map SysTools.Option as_opts ++ - [ SysTools.Option "-c" - , SysTools.Option "-o" - , SysTools.FileOption "" (split_obj n) - , SysTools.FileOption "" (split_s n) - ]) - - mapM_ assemble_file [1..n] - - -- and join the split objects into a single object file: - let ld_r args = SysTools.runLink dflags ([ - SysTools.Option "-nostdlib", - SysTools.Option "-nodefaultlibs", - SysTools.Option "-Wl,-r", - SysTools.Option ld_x_flag, - SysTools.Option "-o", - SysTools.FileOption "" output_fn ] ++ args) +runPhase SplitAs _stop dflags _basename _suff _input_fn get_output_fn maybe_loc + = do + output_fn <- get_output_fn dflags StopLn maybe_loc + + let base_o = dropExtension output_fn + split_odir = base_o ++ "_split" + osuf = objectSuf dflags + + createDirectoryHierarchy 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 <- getDirectoryContents split_odir + mapM_ removeFile $ map (split_odir ) $ filter (osuf `isSuffixOf`) fs + + let as_opts = getOpts dflags opt_a + + (split_s_prefix, n) <- readIORef v_Split_info + + let split_s n = split_s_prefix ++ "__" ++ show n <.> "s" + split_obj n = split_odir + takeFileName base_o ++ "__" ++ show n <.> osuf + + let assemble_file n + = SysTools.runAs dflags + (map SysTools.Option as_opts ++ + [ SysTools.Option "-c" + , SysTools.Option "-o" + , SysTools.FileOption "" (split_obj n) + , SysTools.FileOption "" (split_s n) + ]) + + mapM_ assemble_file [1..n] + + -- and join the split objects into a single object file: + let ld_r args = SysTools.runLink dflags ([ + SysTools.Option "-nostdlib", + SysTools.Option "-nodefaultlibs", + SysTools.Option "-Wl,-r", + SysTools.Option ld_x_flag, + SysTools.Option "-o", + SysTools.FileOption "" output_fn ] ++ args) ld_x_flag | null cLD_X = "" - | otherwise = "-Wl,-x" - - if cLdIsGNULd == "YES" - then do - let script = split_odir `joinFileName` "ld.script" - writeFile script $ - "INPUT(" ++ unwords (map split_obj [1..n]) ++ ")" - ld_r [SysTools.FileOption "" script] - else do - ld_r (map (SysTools.FileOption "" . split_obj) [1..n]) - - return (StopLn, dflags, maybe_loc, output_fn) - - + | otherwise = "-Wl,-x" + + if cLdIsGNULd == "YES" + then do + let script = split_odir "ld.script" + writeFile script $ + "INPUT(" ++ unwords (map split_obj [1..n]) ++ ")" + ld_r [SysTools.FileOption "" script] + else do + ld_r (map (SysTools.FileOption "" . split_obj) [1..n]) + + return (StopLn, dflags, maybe_loc, output_fn) + +-- warning suppression +runPhase other _stop _dflags _basename _suff _input_fn _get_output_fn _maybe_loc = + panic ("runPhase: don't know how to run phase " ++ show other) ----------------------------------------------------------------------------- -- MoveBinary sort-of-phase -- After having produced a binary, move it somewhere else and generate a -- wrapper script calling the binary. Currently, we need this only in -- a parallel way (i.e. in GUM), because PVM expects the binary in a -- central directory. --- This is called from staticLink below, after linking. I haven't made it +-- This is called from linkBinary below, after linking. I haven't made it -- a separate phase to minimise interfering with other modules, and -- 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 - = do - sysMan <- getSysMan +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? - system ("rm -f " ++ pvm_executable) + Panic.try (removeFile pvm_executable) -- move the newly created binary into PVM land - system ("cp -p " ++ input_fn ++ " " ++ pvm_executable) + 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 @@ -1074,18 +1172,18 @@ mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan = unlines $ "", "args: while ($a = shift(@ARGV)) {", " if ( $a eq '+RTS' ) {", - " $in_RTS_args = 1;", + " $in_RTS_args = 1;", " } elsif ( $a eq '-RTS' ) {", - " $in_RTS_args = 0;", + " $in_RTS_args = 0;", " }", " if ( $a eq '-d' && $in_RTS_args ) {", - " $debug = '-';", + " $debug = '-';", " } elsif ( $a =~ /^-qN(\\d+)/ && $in_RTS_args ) {", - " $nprocessors = $1;", + " $nprocessors = $1;", " } elsif ( $a =~ /^-qp(\\d+)/ && $in_RTS_args ) {", - " $nprocessors = $1;", + " $nprocessors = $1;", " } else {", - " push(@nonPVM_args, $a);", + " push(@nonPVM_args, $a);", " }", "}", "", @@ -1101,6 +1199,7 @@ 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 ':') @@ -1113,7 +1212,7 @@ checkProcessArgsResult flags filename getHCFilePackages :: FilePath -> IO [PackageId] getHCFilePackages filename = - EXCEPTION.bracket (openFile filename ReadMode) hClose $ \h -> do + Exception.bracket (openFile filename ReadMode) hClose $ \h -> do l <- hGetLine h case l of '/':'*':' ':'G':'H':'C':'_':'P':'A':'C':'K':'A':'G':'E':'S':rest -> @@ -1134,8 +1233,8 @@ getHCFilePackages filename = -- read any interface files), so the user must explicitly specify all -- the packages. -staticLink :: DynFlags -> [FilePath] -> [PackageId] -> IO () -staticLink dflags o_files dep_packages = do +linkBinary :: DynFlags -> [FilePath] -> [PackageId] -> IO () +linkBinary dflags o_files dep_packages = do let verb = getVerbFlag dflags output_fn = exeFileName dflags @@ -1144,7 +1243,13 @@ staticLink dflags o_files dep_packages = do -- dependencies, and eliminating duplicates. pkg_lib_paths <- getPackageLibraryPath dflags dep_packages - let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths + let pkg_lib_path_opts = concat (map get_pkg_lib_path_opts pkg_lib_paths) +#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 @@ -1165,7 +1270,12 @@ staticLink 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 @@ -1196,6 +1306,8 @@ staticLink dflags o_files dep_packages = do ] | otherwise = [] + rc_objs <- maybeCreateManifest dflags output_fn + let (md_c_flags, _) = machdepCCOpts dflags SysTools.runLink dflags ( [ SysTools.Option verb @@ -1205,9 +1317,13 @@ staticLink 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 + ++ rc_objs #ifdef darwin_TARGET_OS ++ framework_path_opts ++ framework_opts @@ -1223,18 +1339,17 @@ 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 - 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 throwDyn (InstallationError ("cannot move binary")) exeFileName :: DynFlags -> FilePath exeFileName dflags - | Just s <- outputFile dflags = + | Just s <- outputFile dflags = #if defined(mingw32_HOST_OS) - if null (suffixOf s) - then s `joinFileExt` "exe" + if null (takeExtension s) + then s <.> "exe" else s #else s @@ -1246,16 +1361,66 @@ exeFileName dflags "a.out" #endif ------------------------------------------------------------------------------ --- Making a DLL (only for Win32) +maybeCreateManifest + :: DynFlags + -> FilePath -- filename of executable + -> IO [FilePath] -- extra objects to embed, maybe +#ifndef mingw32_TARGET_OS +maybeCreateManifest _ _ = do + return [] +#else +maybeCreateManifest dflags exe_filename = do + if not (dopt Opt_GenManifest dflags) then return [] else do + + let manifest_filename = exe_filename <.> "manifest" + + writeFile manifest_filename $ + "\n"++ + " \n"++ + " \n\n"++ + " \n"++ + " \n"++ + " \n"++ + " \n"++ + " \n"++ + " \n"++ + " \n"++ + "\n" + + -- Windows will find the manifest file if it is named foo.exe.manifest. + -- However, for extra robustness, and so that we can move the binary around, + -- we can embed the manifest in the binary itself using windres: + if not (dopt Opt_EmbedManifest dflags) then return [] else do + + rc_filename <- newTempName dflags "rc" + rc_obj_filename <- newTempName dflags (objectSuf dflags) + + writeFile rc_filename $ + "1 24 MOVEABLE PURE " ++ show manifest_filename ++ "\n" + -- magic numbers :-) + -- show is a bit hackish above, but we need to escape the + -- backslashes in the path. + + let wr_opts = getOpts dflags opt_windres + runWindres dflags $ map SysTools.Option $ + ["--input="++rc_filename, + "--output="++rc_obj_filename, + "--output-format=coff"] + ++ wr_opts + -- no FileOptions here: windres doesn't like seeing + -- backslashes, apparently + + return [rc_obj_filename] +#endif + -doMkDLL :: DynFlags -> [String] -> [PackageId] -> IO () -doMkDLL dflags o_files dep_packages = do +linkDynLib :: DynFlags -> [String] -> [PackageId] -> IO () +linkDynLib dflags o_files dep_packages = do let verb = getVerbFlag dflags - let static = opt_Static - let no_hs_main = dopt Opt_NoHsMain dflags let o_file = outputFile dflags - let output_fn = case o_file of { Just s -> s; Nothing -> "HSdll.dll"; } pkg_lib_paths <- getPackageLibraryPath dflags dep_packages let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths @@ -1268,24 +1433,88 @@ doMkDLL dflags o_files dep_packages = do -- probably _stub.o files extra_ld_inputs <- readIORef v_Ld_inputs - -- opts from -optdll- - let extra_ld_opts = getOpts dflags opt_dll + let (md_c_flags, _) = machdepCCOpts dflags + let extra_ld_opts = getOpts dflags opt_l +#if defined(mingw32_HOST_OS) + ----------------------------------------------------------------------------- + -- Making a DLL + ----------------------------------------------------------------------------- + let output_fn = case o_file of { Just s -> s; Nothing -> "HSdll.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 + SysTools.runLink dflags + ([ SysTools.Option verb + , SysTools.Option "-o" + , SysTools.FileOption "" output_fn + , SysTools.Option "-shared" + , SysTools.FileOption "-Wl,--out-implib=" (output_fn ++ ".a") + ] + ++ map (SysTools.FileOption "") o_files + ++ map SysTools.Option ( + md_c_flags + ++ extra_ld_inputs + ++ lib_path_opts + ++ extra_ld_opts + ++ pkg_lib_path_opts + ++ pkg_link_opts + )) +#elif defined(darwin_TARGET_OS) + ----------------------------------------------------------------------------- + -- Making a darwin dylib + ----------------------------------------------------------------------------- + -- About the options used for Darwin: + -- -dynamiclib + -- Apple's way of saying -shared + -- -undefined dynamic_lookup: + -- Without these options, we'd have to specify the correct dependencies + -- for each of the dylibs. Note that we could (and should) do without this + -- for all libraries except the RTS; all we need to do is to pass the + -- correct HSfoo_dyn.dylib files to the link command. + -- This feature requires Mac OS X 10.3 or later; there is a similar feature, + -- -flat_namespace -undefined suppress, which works on earlier versions, + -- but it has other disadvantages. + -- -single_module + -- Build the dynamic library as a single "module", i.e. no dynamic binding + -- nonsense when referring to symbols from within the library. The NCG + -- assumes that this option is specified (on i386, at least). + -- -Wl,-macosx_version_min -Wl,10.3 + -- Tell the linker its safe to assume that the library will run on 10.3 or + -- later, so that it will not complain about the use of the option + -- -undefined dynamic_lookup above. + -- -install_name + -- Causes the dynamic linker to ignore the DYLD_LIBRARY_PATH when loading + -- this lib and instead look for it at its absolute path. + -- When installing the .dylibs (see target.mk), we'll change that path to + -- point to the place they are installed. Therefore, we won't have to set + -- up DYLD_LIBRARY_PATH specifically for ghc. + ----------------------------------------------------------------------------- + + let output_fn = case o_file of { Just s -> s; Nothing -> "a.out"; } + + pwd <- getCurrentDirectory + SysTools.runLink dflags + ([ SysTools.Option verb + , SysTools.Option "-dynamiclib" + , SysTools.Option "-o" + , SysTools.FileOption "" output_fn + ] + ++ map SysTools.Option ( + md_c_flags + ++ o_files + ++ [ "-undefined", "dynamic_lookup", "-single_module", "-Wl,-macosx_version_min","-Wl,10.3", "-install_name " ++ (pwd output_fn) ] + ++ extra_ld_inputs + ++ lib_path_opts + ++ extra_ld_opts + ++ pkg_lib_path_opts + ++ pkg_link_opts + )) +#else + ----------------------------------------------------------------------------- + -- Making a DSO + ----------------------------------------------------------------------------- - let extra_os = if static || no_hs_main - then [] - else [ head (libraryDirs rts_pkg) ++ "/Main.dll_o", - head (libraryDirs base_pkg) ++ "/PrelMain.dll_o" ] + let output_fn = case o_file of { Just s -> s; Nothing -> "a.out"; } - let (md_c_flags, _) = machdepCCOpts dflags - SysTools.runMkDLL dflags + SysTools.runLink dflags ([ SysTools.Option verb , SysTools.Option "-o" , SysTools.FileOption "" output_fn @@ -1293,18 +1522,14 @@ doMkDLL dflags o_files dep_packages = do ++ map SysTools.Option ( md_c_flags ++ o_files - ++ extra_os - ++ [ "--target=i386-mingw32" ] + ++ [ "-shared", "-Wl,-Bsymbolic" ] -- we need symbolic linking to resolve non-PIC intra-package-relocations ++ extra_ld_inputs ++ lib_path_opts ++ extra_ld_opts ++ pkg_lib_path_opts ++ pkg_link_opts - ++ (if "--def" `elem` (concatMap words extra_ld_opts) - then [ "" ] - else [ "--export-all" ]) )) - +#endif -- ----------------------------------------------------------------------------- -- Running CPP @@ -1358,8 +1583,10 @@ doCpp dflags raw include_cc_opts input_fn output_fn = do , SysTools.FileOption "" output_fn ]) +cHaskell1Version :: String cHaskell1Version = "5" -- i.e., Haskell 98 +hsSourceCppOpts :: [String] -- Default CPP defines in Haskell source hsSourceCppOpts = [ "-D__HASKELL1__="++cHaskell1Version @@ -1373,8 +1600,8 @@ hsSourceCppOpts = -- Misc. hscNextPhase :: DynFlags -> HscSource -> HscTarget -> Phase -hscNextPhase dflags HsBootFile hsc_lang = StopLn -hscNextPhase dflags other hsc_lang = +hscNextPhase _ HsBootFile _ = StopLn +hscNextPhase dflags _ hsc_lang = case hsc_lang of HscC -> HCc HscAsm | dopt Opt_SplitObjs dflags -> SplitMangle @@ -1385,9 +1612,7 @@ hscNextPhase dflags other hsc_lang = hscMaybeAdjustTarget :: DynFlags -> Phase -> HscSource -> HscTarget -> HscTarget -hscMaybeAdjustTarget dflags stop HsBootFile current_hsc_lang - = HscNothing -- No output (other than Foo.hi-boot) for hs-boot files -hscMaybeAdjustTarget dflags stop other current_hsc_lang +hscMaybeAdjustTarget dflags stop _ current_hsc_lang = hsc_lang where keep_hc = dopt Opt_KeepHcFiles dflags