X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fmain%2FDriverPipeline.hs;h=22ce8c43245abdd478b3a45117a2bc2f92034404;hb=b17eae42ad936fd88ddcc356ba876e8a0910d46b;hp=c0ea4fc58688e9154c316772718c69dfa758c705;hpb=e2782137c799a08711cac0844418cc0345a7ceb5;p=ghc-hetmet.git diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs index c0ea4fc..22ce8c4 100644 --- a/compiler/main/DriverPipeline.hs +++ b/compiler/main/DriverPipeline.hs @@ -1,3 +1,10 @@ +{-# OPTIONS -w #-} +-- The above warning supression flag is a temporary kludge. +-- While working on this module you are encouraged to remove it and fix +-- any warnings in the module. See +-- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings +-- for details + ----------------------------------------------------------------------------- -- -- GHC Driver @@ -6,13 +13,6 @@ -- ----------------------------------------------------------------------------- -{-# OPTIONS -w #-} --- The above warning supression flag is a temporary kludge. --- While working on this module you are encouraged to remove it and fix --- any warnings in the module. See --- http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings --- for details - module DriverPipeline ( -- Run a series of compilation steps in a pipeline, for a -- collection of source files. @@ -23,7 +23,7 @@ module DriverPipeline ( -- Interfaces for the compilation manager (interpreted/batch-mode) preprocess, - compile, CompResult(..), + compile, link, ) where @@ -93,36 +93,25 @@ 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 + -> 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 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 location = ms_location summary let input_fn = expectJust "compile:hs" (ml_hs_file location) - let input_fnpp = ms_hspp_file mod_summary + let input_fnpp = ms_hspp_file summary debugTraceMsg dflags0 2 (text "compile: input file" <+> text input_fnpp) @@ -158,21 +147,23 @@ 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 = do when (isObjectTarget hsc_lang) $ -- interpreted reaches here too SysTools.touch dflags' "Touching object file" object_filename - return (CompOK details iface Nothing) + 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) @@ -184,15 +175,15 @@ compile hsc_env mod_summary maybe_old_linkable old_iface mod_index nmods = do 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 modBreaks, iface, details) + return maybe_old_linkable + handleInterpreted (InteractiveRecomp hasStub comp_bc modBreaks) = do stub_unlinked <- getStubLinkable hasStub let hs_unlinked = [BCOs comp_bc modBreaks] - unlinked_time = ms_hs_date mod_summary + 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 @@ -201,22 +192,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 - | isHsBoot src_flavour -> runCompiler hscCompileNothing handleBatch - | otherwise -> 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) @@ -253,10 +253,10 @@ compileStub dflags mod location = do -- --------------------------------------------------------------------------- -- Link -link :: GhcLink -- 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 @@ -269,7 +269,7 @@ link :: GhcLink -- interactive or batch #ifdef GHCI link LinkInMemory dflags batch_attempt_linking hpt = do -- Not Linking...(demand linker will do the job) - return Succeeded + return Succeeded #endif link NoLink dflags batch_attempt_linking hpt @@ -277,62 +277,65 @@ link NoLink dflags batch_attempt_linking hpt link LinkBinary dflags batch_attempt_linking hpt | batch_attempt_linking - = do - let - home_mod_infos = eltsUFM 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 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 - 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 + | Left _ <- e_exe_time = True + | Right t <- e_exe_time = 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 + link dflags obj_files pkg_deps debugTraceMsg dflags 3 (text "link: done") - -- linkBinary 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 - + -- ----------------------------------------------------------------------------- -- Compile files in one-shot mode. @@ -656,7 +659,7 @@ runPhase (Hsc src_flavour) stop dflags0 basename suff input_fn get_output_fn _ma ; return (Nothing, mkModuleName m, [], []) } other -> do { buf <- hGetStringBuffer input_fn - ; (src_imps,imps,L _ mod_name) <- getImports dflags buf input_fn + ; (src_imps,imps,L _ mod_name) <- getImports dflags buf input_fn (basename `joinFileExt` suff) ; return (Just buf, mod_name, imps, src_imps) } -- Build a ModLocation to pass to hscMain. @@ -1330,8 +1333,10 @@ maybeCreateManifest dflags exe_filename = do rc_obj_filename <- newTempName dflags (objectSuf dflags) writeFile rc_filename $ - "1 24 MOVEABLE PURE \"" ++ manifest_filename ++ "\"\n" + "1 24 MOVEABLE PURE " ++ show manifest_filename ++ "\n" -- magic numbers :-) + -- show is a bit hackish above, but we need to esacpe the + -- backslashes in the path. let wr_opts = getOpts dflags opt_windres runWindres dflags $ map SysTools.Option $ @@ -1377,7 +1382,6 @@ linkDynLib dflags o_files dep_packages = do , SysTools.Option "-o" , SysTools.FileOption "" output_fn , SysTools.Option "-shared" - , SysTools.Option "-Wl,--export-all-symbols" , SysTools.FileOption "-Wl,--out-implib=" (output_fn ++ ".a") ] ++ map (SysTools.FileOption "") o_files