X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fmain%2FDriverPipeline.hs;h=c8cf4c9a804519a5dc91d576469d84378bfb54b1;hp=b05a20a34374abbfb11da47f2bfc937146d35546;hb=527f52a72acf214994921ad36de92f934e9632da;hpb=d51f42f602bf9a6d1b356c41228a534c88723f65 diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index b05a20a..c8cf4c9 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 @@ -16,7 +19,7 @@ module DriverPipeline ( -- Interfaces for the compilation manager (interpreted/batch-mode) preprocess, - compile, + compile, compile', link, ) where @@ -43,57 +46,83 @@ import StringBuffer ( hGetStringBuffer ) import BasicTypes ( SuccessFlag(..) ) import Maybes ( expectJust ) import ParserCoreUtils ( getCoreModuleName ) -import SrcLoc ( unLoc ) -import SrcLoc ( Located(..) ) +import SrcLoc +import FastString +import MonadUtils -import Control.Exception as Exception -import Data.IORef ( readIORef, writeIORef, IORef ) +import Data.Either +import Exception +import Data.IORef ( readIORef ) 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 -- --------------------------------------------------------------------------- -- Pre-process --- Just preprocess a file, put the result in a temp. file (used by the +-- | Just preprocess a file, put the result in a temp. file (used by the -- compilation manager during the summary phase). -- -- 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 :: GhcMonad m => + HscEnv + -> (FilePath, Maybe Phase) -- ^ filename and starting phase + -> m (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-} -- --------------------------------------------------------------------------- --- Compile +-- | Compile +-- -- Compile a single module, under the control of the compilation manager. -- -- This is the interface between the compilation manager and the -- compiler proper (hsc), where we deal with tedious details like -- reading the OPTIONS pragma from the source file, and passing the -- output of hsc through the C compiler. - +-- -- NB. No old interface can also mean that the source has changed. -compile :: HscEnv - -> 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 +compile :: GhcMonad m => + HscEnv + -> ModSummary -- ^ summary for module being compiled + -> Int -- ^ module N ... + -> Int -- ^ ... of M + -> Maybe ModIface -- ^ old interface, if we have one + -> Maybe Linkable -- ^ old linkable, if we have one + -> m HomeModInfo -- ^ the complete HomeModInfo, if successful + +compile = compile' (hscCompileNothing, hscCompileInteractive, hscCompileBatch) + +type Compiler m a = HscEnv -> ModSummary -> Bool + -> Maybe ModIface -> Maybe (Int, Int) + -> m a + +compile' :: GhcMonad m => + (Compiler m (HscStatus, ModIface, ModDetails), + Compiler m (InteractiveStatus, ModIface, ModDetails), + Compiler m (HscStatus, ModIface, ModDetails)) + -> HscEnv + -> ModSummary -- ^ summary for module being compiled + -> Int -- ^ module N ... + -> Int -- ^ ... of M + -> Maybe ModIface -- ^ old interface, if we have one + -> Maybe Linkable -- ^ old linkable, if we have one + -> m HomeModInfo -- ^ the complete HomeModInfo, if successful + +compile' (nothingCompiler, interactiveCompiler, batchCompiler) + hsc_env0 summary mod_index nmods mb_old_iface maybe_old_linkable = do let dflags0 = ms_hspp_opts summary this_mod = ms_mod summary @@ -102,7 +131,7 @@ compile hsc_env summary mod_index nmods mb_old_iface maybe_old_linkable 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) + liftIO $ debugTraceMsg dflags0 2 (text "compile: input file" <+> text input_fnpp) let basename = dropExtension input_fn @@ -114,38 +143,39 @@ 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) -- ... 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 next_phase + output_fn <- liftIO $ getOutputFilename next_phase Temporary basename dflags next_phase (Just location) 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 = ASSERT (isJust maybe_old_linkable) return maybe_old_linkable - handleBatch (HscRecomp hasStub) + handleBatch (HscRecomp hasStub _) | isHsBoot src_flavour = do when (isObjectTarget hsc_lang) $ -- interpreted reaches here too - SysTools.touch dflags' "Touching object file" + liftIO $ SysTools.touch dflags' "Touching object file" object_filename return maybe_old_linkable @@ -157,21 +187,24 @@ 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) -- The object filename comes from the ModLocation - o_time <- getModificationTime object_filename + o_time <- liftIO $ getModificationTime object_filename return ([DotO object_filename], o_time) let linkable = LM unlinked_time this_mod (hs_unlinked ++ stub_unlinked) return (Just linkable) - handleInterpreted InteractiveNoRecomp + handleInterpreted HscNoRecomp = ASSERT (isJust maybe_old_linkable) return maybe_old_linkable - handleInterpreted (InteractiveRecomp hasStub comp_bc modBreaks) + handleInterpreted (HscRecomp _hasStub Nothing) + = ASSERT (isHsBoot src_flavour) + return maybe_old_linkable + handleInterpreted (HscRecomp hasStub (Just (comp_bc, modBreaks))) = do stub_unlinked <- getStubLinkable hasStub let hs_unlinked = [BCOs comp_bc modBreaks] unlinked_time = ms_hs_date summary @@ -186,28 +219,24 @@ compile hsc_env summary mod_index nmods mb_old_iface maybe_old_linkable return (Just linkable) let -- runCompiler :: Compiler result -> (result -> Maybe Linkable) - -- -> IO (Maybe HomeModInfo) + -- -> m HomeModInfo runCompiler compiler handle - = do mbResult <- compiler hsc_env' summary source_unchanged mb_old_iface - (Just (mod_index, nmods)) - case mbResult of - Nothing -> return Nothing - Just (result, iface, details) -> do - linkable <- handle result - return (Just HomeModInfo{ hm_details = details, - hm_iface = iface, - hm_linkable = linkable }) + = do (result, iface, details) + <- compiler hsc_env' summary source_unchanged mb_old_iface + (Just (mod_index, nmods)) + linkable <- handle result + return (HomeModInfo{ hm_details = details, + hm_iface = iface, + hm_linkable = linkable }) -- run the compiler case hsc_lang of - HscInterpreted - | isHsBoot src_flavour -> - runCompiler hscCompileNothing handleBatch - | otherwise -> - runCompiler hscCompileInteractive handleInterpreted + HscInterpreted -> + runCompiler interactiveCompiler handleInterpreted HscNothing -> - runCompiler hscCompileNothing handleBatch + runCompiler nothingCompiler handleBatch _other -> - runCompiler hscCompileBatch handleBatch + runCompiler batchCompiler handleBatch + ----------------------------------------------------------------------------- -- stub .h and .c files (for foreign export support) @@ -228,14 +257,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 - let (o_base, o_ext) = splitExtension (ml_obj_file location) - stub_o = (o_base ++ "_stub") <.> o_ext - +compileStub :: GhcMonad m => HscEnv -> Module -> ModLocation + -> m FilePath +compileStub hsc_env mod location = do -- 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,_,stub_o) = 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 @@ -267,6 +296,26 @@ link NoLink _ _ _ = return Succeeded link LinkBinary dflags batch_attempt_linking hpt + = link' dflags batch_attempt_linking hpt + +link LinkDynLib dflags batch_attempt_linking hpt + = link' dflags batch_attempt_linking hpt + +#ifndef GHCI +-- warning suppression +link other _ _ _ = panicBadLink other +#endif + +panicBadLink :: GhcLink -> a +panicBadLink other = panic ("link: GHC not built to link this way: " ++ + show other) + +link' :: DynFlags -- dynamic flags + -> Bool -- attempt linking in batch mode? + -> HomePackageTable -- what to link + -> IO SuccessFlag + +link' dflags batch_attempt_linking hpt | batch_attempt_linking = do let @@ -291,24 +340,14 @@ link LinkBinary dflags batch_attempt_linking hpt 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 + linking_needed <- linkingNeeded dflags linkables pkg_deps 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. @@ -328,27 +367,68 @@ link LinkBinary dflags batch_attempt_linking hpt 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) +linkingNeeded :: DynFlags -> [Linkable] -> [PackageId] -> IO Bool +linkingNeeded dflags linkables pkg_deps = do + -- if the modification time on the executable is later than the + -- modification times on all of the objects and libraries, then omit + -- linking (unless the -fforce-recomp flag was given). + let exe_file = exeFileName dflags + e_exe_time <- IO.try $ getModificationTime exe_file + case e_exe_time of + Left _ -> return True + Right t -> do + -- first check object files and extra_ld_inputs + extra_ld_inputs <- readIORef v_Ld_inputs + e_extra_times <- mapM (IO.try . getModificationTime) extra_ld_inputs + let (errs,extra_times) = splitEithers e_extra_times + let obj_times = map linkableTime linkables ++ extra_times + if not (null errs) || any (t <) obj_times + then return True + else do + + -- next, check libraries. XXX this only checks Haskell libraries, + -- not extra_libraries or -l things from the command line. + let pkg_map = pkgIdMap (pkgState dflags) + pkg_hslibs = [ (libraryDirs c, lib) + | Just c <- map (lookupPackage pkg_map) pkg_deps, + lib <- packageHsLibs dflags c ] + + pkg_libfiles <- mapM (uncurry findHSLib) pkg_hslibs + if any isNothing pkg_libfiles then return True else do + e_lib_times <- mapM (IO.try . getModificationTime) + (catMaybes pkg_libfiles) + let (lib_errs,lib_times) = splitEithers e_lib_times + if not (null lib_errs) || any (t <) lib_times + then return True + else return False + +findHSLib :: [String] -> String -> IO (Maybe FilePath) +findHSLib dirs lib = do + let batch_lib_file = "lib" ++ lib <.> "a" + found <- filterM doesFileExist (map ( batch_lib_file) dirs) + case found of + [] -> return Nothing + (x:_) -> return (Just x) + -- ----------------------------------------------------------------------------- -- 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 :: GhcMonad m => + HscEnv -> Phase -> [(String, Maybe Phase)] -> m () +oneShot hsc_env stop_phase srcs = do + o_files <- mapM (compileFile hsc_env stop_phase) srcs + liftIO $ 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 - exists <- doesFileExist src +compileFile :: GhcMonad m => + HscEnv -> Phase -> (FilePath, Maybe Phase) -> m FilePath +compileFile hsc_env stop_phase (src, mb_phase) = do + exists <- liftIO $ 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 @@ -366,9 +446,9 @@ compileFile dflags stop_phase (src, mb_phase) = do As | split -> SplitAs _ -> stop_phase - (_, out_file) <- runPipeline stop_phase' dflags - (src, mb_phase) Nothing output - Nothing{-no ModLocation-} + ( _, out_file) <- runPipeline stop_phase' hsc_env + (src, mb_phase) Nothing output + Nothing{-no ModLocation-} return out_file @@ -386,43 +466,46 @@ 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 = [] -- --------------------------------------------------------------------------- --- Run a compilation pipeline, consisting of multiple phases. - --- This is the interface to the compilation pipeline, which runs --- a series of compilation steps on a single source file, specifying --- at which stage to stop. - --- The DynFlags can be modified by phases in the pipeline (eg. by --- GHC_OPTIONS pragmas), and the changes affect later phases in the --- pipeline. data PipelineOutput = Temporary - -- output should be to a temporary file: we're going to - -- run more compilation steps on this output later + -- ^ Output should be to a temporary file: we're going to + -- run more compilation steps on this output later. | Persistent - -- we want a persistent file, i.e. a file in the current directory + -- ^ We want a persistent file, i.e. a file in the current directory -- derived from the input filename, but with the appropriate extension. -- eg. in "ghc -c Foo.hs" the output goes into ./Foo.o. | SpecificFile FilePath - -- the output must go into the specified file. + -- ^ The output must go into the specified file. +-- | Run a compilation pipeline, consisting of multiple phases. +-- +-- This is the interface to the compilation pipeline, which runs +-- a series of compilation steps on a single source file, specifying +-- at which stage to stop. +-- +-- The DynFlags can be modified by phases in the pipeline (eg. by +-- GHC_OPTIONS pragmas), and the changes affect later phases in the +-- pipeline. 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 dflags0 (input_fn, mb_phase) mb_basename output maybe_loc + :: GhcMonad m => + Phase -- ^ When to stop + -> 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 + -> m (DynFlags, FilePath) -- ^ (final flags, output filename) + +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 @@ -430,6 +513,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 @@ -442,7 +526,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)) @@ -452,7 +536,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 @@ -463,7 +547,7 @@ runPipeline stop_phase dflags0 (input_fn, mb_phase) mb_basename output maybe_loc case output of Temporary -> return (dflags', output_fn) - _other -> + _other -> liftIO $ 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 ++ "'") @@ -473,18 +557,19 @@ runPipeline stop_phase dflags0 (input_fn, mb_phase) mb_basename output maybe_loc -pipeLoop :: DynFlags -> Phase -> Phase +pipeLoop :: GhcMonad m => + HscEnv -> Phase -> Phase -> FilePath -> String -> Suffix -> (DynFlags -> Phase -> Maybe ModLocation -> IO FilePath) -> Maybe ModLocation - -> IO (DynFlags, FilePath, Maybe ModLocation) + -> m (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 @@ -495,11 +580,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 @@ -551,7 +637,7 @@ getOutputFilename stop_phase output basename -- ----------------------------------------------------------------------------- --- Each phase in the pipeline returns the next phase to execute, and the +-- | Each phase in the pipeline returns the next phase to execute, and the -- name of the file in which the output was placed. -- -- We must do things dynamically this way, because we often don't know @@ -559,20 +645,21 @@ getOutputFilename stop_phase output basename -- compilation: for example, an {-# OPTIONS -fasm #-} at the beginning -- of a source file can change the latter stages of the pipeline from -- taking the via-C route to using the native code generator. - -runPhase :: Phase -- Do this phase first - -> Phase -- Stop just before this phase - -> DynFlags - -> String -- basename of original input source - -> String -- its extension - -> FilePath -- name of file which contains the input to this phase. +-- +runPhase :: GhcMonad m => + Phase -- ^ Do this phase first + -> Phase -- ^ Stop just before this phase + -> HscEnv + -> String -- ^ basename of original input source + -> String -- ^ its extension + -> FilePath -- ^ name of file which contains the input to this phase. -> (DynFlags -> Phase -> Maybe ModLocation -> IO FilePath) - -- how to calculate the output filename - -> Maybe ModLocation -- the ModLocation, if we have one - -> IO (Phase, -- next phase - DynFlags, -- new dynamic flags - Maybe ModLocation, -- the ModLocation, if we have one - FilePath) -- output filename + -- ^ how to calculate the output filename + -> Maybe ModLocation -- ^ the ModLocation, if we have one + -> m (Phase, -- next phase + DynFlags, -- new dynamic flags + Maybe ModLocation, -- the ModLocation, if we have one + FilePath) -- output filename -- Invariant: the output filename always contains the output -- Interesting case: Hsc when there is no recompilation to do @@ -581,9 +668,10 @@ runPhase :: Phase -- Do this phase first ------------------------------------------------------------------------------- -- Unlit phase -runPhase (Unlit sf) _stop dflags _basename _suff input_fn get_output_fn maybe_loc +runPhase (Unlit sf) _stop hsc_env _basename _suff input_fn get_output_fn maybe_loc = do - output_fn <- get_output_fn dflags (Cpp sf) maybe_loc + let dflags = hsc_dflags hsc_env + output_fn <- liftIO $ get_output_fn dflags (Cpp sf) maybe_loc let unlit_flags = getOpts dflags opt_L flags = map SysTools.Option unlit_flags ++ @@ -597,7 +685,7 @@ runPhase (Unlit sf) _stop dflags _basename _suff input_fn get_output_fn maybe_lo , SysTools.FileOption "" output_fn ] - SysTools.runUnlit dflags flags + liftIO $ SysTools.runUnlit dflags flags return (Cpp sf, dflags, maybe_loc, output_fn) @@ -605,33 +693,37 @@ 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 <- liftIO $ getOptionsFromFile dflags0 input_fn + (dflags, unhandled_flags, warns) + <- liftIO $ parseDynamicNoPackageFlags 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 -- to the next phase of the pipeline. return (HsPp sf, dflags, maybe_loc, input_fn) else do - output_fn <- get_output_fn dflags (HsPp sf) maybe_loc - doCpp dflags True{-raw-} False{-no CC opts-} input_fn output_fn + output_fn <- liftIO $ get_output_fn dflags (HsPp sf) maybe_loc + liftIO $ doCpp dflags True{-raw-} False{-no CC opts-} input_fn output_fn return (HsPp sf, dflags, maybe_loc, output_fn) ------------------------------------------------------------------------------- -- 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) else do let hspp_opts = getOpts dflags opt_F let orig_fn = basename <.> suff - output_fn <- get_output_fn dflags (Hsc sf) maybe_loc - SysTools.runPp dflags + output_fn <- liftIO $ get_output_fn dflags (Hsc sf) maybe_loc + liftIO $ SysTools.runPp dflags ( [ SysTools.Option orig_fn , SysTools.Option input_fn , SysTools.FileOption "" output_fn @@ -645,8 +737,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 @@ -661,13 +754,14 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma -- gather the imports and module 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, mkModuleName m, [], []) } + ExtCoreFile -> do -- no explicit imports in ExtCore input. + m <- liftIO $ getCoreModuleName input_fn + return (Nothing, mkModuleName m, [], []) - _ -> 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) } + _ -> do + buf <- liftIO $ 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 @@ -675,7 +769,7 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma -- the .hi and .o filenames, and this is as good a way -- as any to generate them, and better than most. (e.g. takes -- into accout the -osuf flags) - location1 <- mkHomeModLocation2 dflags mod_name basename suff + location1 <- liftIO $ mkHomeModLocation2 dflags mod_name basename suff -- Boot-ify it if necessary let location2 | isHsBoot src_flavour = addBootSuffixLocn location1 @@ -710,20 +804,20 @@ 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. - src_timestamp <- getModificationTime (basename <.> suff) + src_timestamp <- liftIO $ getModificationTime (basename <.> suff) let force_recomp = dopt Opt_ForceRecomp dflags - source_unchanged <- + source_unchanged <- 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) then return False -- Otherwise look at file modification dates - else do o_file_exists <- doesFileExist o_file + else do o_file_exists <- liftIO $ doesFileExist o_file if not o_file_exists then return False -- Need to recompile - else do t2 <- getModificationTime o_file + else do t2 <- liftIO $ getModificationTime o_file if t2 > src_timestamp then return True else return False @@ -731,16 +825,16 @@ 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 dflags next_phase (Just location4) + output_fn <- liftIO $ get_output_fn dflags next_phase (Just location4) let dflags' = dflags { hscTarget = hsc_lang, 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 <- liftIO $ addHomeModuleToFinder hsc_env' mod_name location4 -- Make the ModSummary to hand to hscMain let @@ -756,51 +850,56 @@ 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 + result <- 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)) - Just HscNoRecomp - -> do SysTools.touch dflags' "Touching object file" o_file + case result of + HscNoRecomp + -> do liftIO $ SysTools.touch dflags' "Touching object file" o_file -- The .o file must have a later modification date -- than the source file (else we wouldn't be in HscNoRecomp) -- but we touch it anyway, to keep 'make' happy (we think). return (StopLn, dflags', Just location4, o_file) - Just (HscRecomp hasStub) + (HscRecomp hasStub _) -> do when hasStub $ - do stub_o <- compileStub dflags' mod location4 - consIORef v_Ld_inputs stub_o + do stub_o <- compileStub hsc_env' mod location4 + liftIO $ 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 when (isHsBoot src_flavour) $ - SysTools.touch dflags' "Touching object file" o_file + liftIO $ SysTools.touch dflags' "Touching object file" o_file return (next_phase, dflags', Just location4, output_fn) ----------------------------------------------------------------------------- -- 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 - output_fn <- get_output_fn dflags Cmm maybe_loc - doCpp dflags False{-not raw-} True{-include CC opts-} input_fn output_fn + let dflags = hsc_dflags hsc_env + output_fn <- liftIO $ get_output_fn dflags Cmm maybe_loc + liftIO $ 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 + output_fn <- liftIO $ get_output_fn dflags next_phase 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 + hscCmmFile hsc_env' input_fn - when (not ok) $ throwDyn (PhaseFailed "cmm" (ExitFailure 1)) + -- XXX: catch errors above and convert them into ghcError? Original + -- code was: + -- + --when (not ok) $ ghcError (PhaseFailed "cmm" (ExitFailure 1)) return (next_phase, dflags, maybe_loc, output_fn) @@ -810,33 +909,40 @@ 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 -- HC files have the dependent packages stamped into them - pkgs <- if hcc then getHCFilePackages input_fn else return [] + pkgs <- if hcc then liftIO (getHCFilePackages input_fn) else return [] -- add package include paths even if we're just compiling .c -- files; this is the Value Add(TM) that using ghc instead of -- gcc gives you :) - pkg_include_dirs <- getPackageIncludePath dflags pkgs + pkg_include_dirs <- liftIO $ getPackageIncludePath dflags pkgs let include_paths = foldr (\ x xs -> "-I" : x : xs) [] (cmdline_include_paths ++ pkg_include_dirs) let (md_c_flags, md_regd_c_flags) = machdepCCOpts dflags - gcc_extra_viac_flags <- getExtraViaCOpts dflags + gcc_extra_viac_flags <- liftIO $ getExtraViaCOpts dflags let pic_c_flags = picCCOpts dflags 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 liftIO $ getPackageExtraCcOpts dflags pkgs #ifdef darwin_TARGET_OS - pkg_framework_paths <- getPackageFrameworkPath dflags pkgs + pkg_framework_paths <- liftIO $ getPackageFrameworkPath dflags pkgs let cmdline_framework_paths = frameworkPaths dflags let framework_paths = map ("-F"++) (cmdline_framework_paths ++ pkg_framework_paths) @@ -855,7 +961,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 dflags next_phase maybe_loc + output_fn <- liftIO $ get_output_fn dflags next_phase maybe_loc let more_hcc_opts = @@ -876,7 +982,7 @@ runPhase cc_phase _stop dflags _basename _suff input_fn get_output_fn maybe_loc - SysTools.runCc dflags ( + liftIO $ SysTools.runCc dflags ( -- force the C compiler to interpret this file as C when -- compiling .hc files, by adding the -x c option. -- Also useful for plain .c files, just in case GHC saw a @@ -899,6 +1005,13 @@ runPhase cc_phase _stop dflags _basename _suff input_fn get_output_fn maybe_loc -- This is a temporary hack. ++ ["-mcpu=v9"] #endif +#if defined(darwin_TARGET_OS) && defined(i386_TARGET_ARCH) + -- By default, gcc on OS X will generate SSE + -- instructions, which need things 16-byte aligned, + -- but we don't 16-byte align things. Thus drop + -- back to generic i686 compatibility. Trac #2983. + ++ ["-march=i686"] +#endif ++ (if hcc && mangle then md_regd_c_flags else []) @@ -930,8 +1043,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) ] @@ -943,9 +1057,9 @@ runPhase Mangle _stop dflags _basename _suff input_fn get_output_fn maybe_loc next_phase | split = SplitMangle | otherwise = As - output_fn <- get_output_fn dflags next_phase maybe_loc + output_fn <- liftIO $ get_output_fn dflags next_phase maybe_loc - SysTools.runMangle dflags (map SysTools.Option mangler_opts + liftIO $ SysTools.runMangle dflags (map SysTools.Option mangler_opts ++ [ SysTools.FileOption "" input_fn , SysTools.FileOption "" output_fn ] @@ -956,9 +1070,11 @@ 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 - = do -- tmp_pfx is the prefix used for the split .s files +runPhase SplitMangle _stop hsc_env _basename _suff input_fn _get_output_fn maybe_loc + = liftIO $ + 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 @@ -971,20 +1087,22 @@ runPhase SplitMangle _stop dflags _basename _suff input_fn _get_output_fn maybe_ -- Save the number of split files for future references s <- readFile n_files_fn let n_files = read s :: Int - writeIORef v_Split_info (split_s_prefix, n_files) + dflags' = dflags { splitInfo = Just (split_s_prefix, n_files) } -- Remember to delete all these files - addFilesToClean [ split_s_prefix ++ "__" ++ show n ++ ".s" - | n <- [1..n_files]] + addFilesToClean dflags' [ split_s_prefix ++ "__" ++ show n ++ ".s" + | n <- [1..n_files]] - return (SplitAs, dflags, maybe_loc, "**splitmangle**") + return (SplitAs, dflags', maybe_loc, "**splitmangle**") -- we don't use the filename ----------------------------------------------------------------------------- -- 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 + = liftIO $ + 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 @@ -993,6 +1111,7 @@ runPhase As _stop dflags _basename _suff input_fn get_output_fn maybe_loc -- might be a hierarchical module. createDirectoryHierarchy (takeDirectory output_fn) + let (md_c_flags, _) = machdepCCOpts dflags SysTools.runAs dflags (map SysTools.Option as_opts ++ [ SysTools.Option ("-I" ++ p) | p <- cmdline_include_paths ] @@ -1010,13 +1129,15 @@ runPhase As _stop dflags _basename _suff input_fn get_output_fn maybe_loc , SysTools.FileOption "" input_fn , SysTools.Option "-o" , SysTools.FileOption "" output_fn - ]) + ] + ++ map SysTools.Option md_c_flags) return (StopLn, dflags, maybe_loc, output_fn) -runPhase SplitAs _stop dflags _basename _suff _input_fn get_output_fn maybe_loc - = do +runPhase SplitAs _stop hsc_env _basename _suff _input_fn get_output_fn maybe_loc + = liftIO $ do + let dflags = hsc_dflags hsc_env output_fn <- get_output_fn dflags StopLn maybe_loc let base_o = dropExtension output_fn @@ -1032,20 +1153,34 @@ runPhase SplitAs _stop dflags _basename _suff _input_fn get_output_fn maybe_loc let as_opts = getOpts dflags opt_a - (split_s_prefix, n) <- readIORef v_Split_info + let (split_s_prefix, n) = case splitInfo dflags of + Nothing -> panic "No split info" + Just x -> x let split_s n = split_s_prefix ++ "__" ++ show n <.> "s" split_obj n = split_odir takeFileName base_o ++ "__" ++ show n <.> osuf + let (md_c_flags, _) = machdepCCOpts dflags let assemble_file n = SysTools.runAs dflags (map SysTools.Option as_opts ++ +#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.Option "-o" , SysTools.FileOption "" (split_obj n) , SysTools.FileOption "" (split_s n) - ]) + ] + ++ map SysTools.Option md_c_flags) mapM_ assemble_file [1..n] @@ -1056,7 +1191,9 @@ runPhase SplitAs _stop dflags _basename _suff _input_fn get_output_fn maybe_loc SysTools.Option "-Wl,-r", SysTools.Option ld_x_flag, SysTools.Option "-o", - SysTools.FileOption "" output_fn ] ++ args) + SysTools.FileOption "" output_fn ] + ++ map SysTools.Option md_c_flags + ++ args) ld_x_flag | null cLD_X = "" | otherwise = "-Wl,-x" @@ -1097,7 +1234,7 @@ runPhase_MoveBinary dflags input_fn dep_packages 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 @@ -1108,8 +1245,8 @@ runPhase_MoveBinary dflags input_fn dep_packages 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" + let wrapped_executable | o_ext == "exe" = (o_base ++ ".dyn") <.> o_ext + | otherwise = input_fn ++ ".dyn" behaviour <- wrapper_behaviour dflags wrapmode dep_packages -- THINKME isn't this possible to do a bit nicer? @@ -1196,17 +1333,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] @@ -1253,6 +1379,13 @@ linkBinary dflags o_files dep_packages = do let lib_paths = libraryPaths dflags let lib_path_opts = map ("-L"++) lib_paths + -- The C "main" function is not in the rts but in a separate static + -- library libHSrtsmain.a that sits next to the rts lib files. Assuming + -- we're using a Haskell main function then we need to link it in. + let no_hs_main = dopt Opt_NoHsMain dflags + let main_lib | no_hs_main = [] + | otherwise = [ "-lHSrtsmain" ] + pkg_link_opts <- getPackageLinkOpts dflags dep_packages #ifdef darwin_TARGET_OS @@ -1269,12 +1402,6 @@ 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 @@ -1316,9 +1443,6 @@ 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 @@ -1328,6 +1452,7 @@ linkBinary dflags o_files dep_packages = do ++ framework_opts #endif ++ pkg_lib_path_opts + ++ main_lib ++ pkg_link_opts #ifdef darwin_TARGET_OS ++ pkg_framework_path_opts @@ -1340,7 +1465,7 @@ linkBinary dflags o_files dep_packages = do -- parallel only: move binary to another dir -- HWL success <- runPhase_MoveBinary dflags output_fn dep_packages if success then return () - else throwDyn (InstallationError ("cannot move binary")) + else ghcError (InstallationError ("cannot move binary")) exeFileName :: DynFlags -> FilePath @@ -1412,6 +1537,8 @@ maybeCreateManifest dflags exe_filename = do -- no FileOptions here: windres doesn't like seeing -- backslashes, apparently + removeFile manifest_filename + return [rc_obj_filename] #endif @@ -1421,13 +1548,31 @@ linkDynLib dflags o_files dep_packages = do let verb = getVerbFlag dflags let o_file = outputFile dflags - pkg_lib_paths <- getPackageLibraryPath dflags dep_packages - let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths + -- 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 + + -- On Windows we need to link the RTS import lib as Windows does + -- not allow undefined symbols. +#if !defined(mingw32_HOST_OS) + let pkgs_no_rts = filter ((/= rtsPackageId) . packageConfigId) pkgs +#else + let pkgs_no_rts = pkgs +#endif + let pkg_lib_paths = collectLibraryPaths pkgs_no_rts + let pkg_lib_path_opts = concatMap 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 - 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 @@ -1522,6 +1667,7 @@ linkDynLib dflags o_files dep_packages = do md_c_flags ++ o_files ++ [ "-shared", "-Wl,-Bsymbolic" ] -- we need symbolic linking to resolve non-PIC intra-package-relocations + ++ [ "-Wl,-soname," ++ takeFileName output_fn ] -- set the library soname ++ extra_ld_inputs ++ lib_path_opts ++ extra_ld_opts @@ -1625,6 +1771,3 @@ 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