[project @ 2005-01-27 15:55:38 by simonpj]
[ghc-hetmet.git] / ghc / compiler / main / DriverPipeline.hs
1 -----------------------------------------------------------------------------
2 --
3 -- GHC Driver
4 --
5 -- (c) The University of Glasgow 2002
6 --
7 -----------------------------------------------------------------------------
8
9 #include "../includes/ghcconfig.h"
10
11 module DriverPipeline (
12
13         -- Interfaces for the batch-mode driver
14    compileFile, staticLink,
15
16         -- Interfaces for the compilation manager (interpreted/batch-mode)
17    preprocess, 
18    compile, CompResult(..), 
19    link, 
20
21         -- DLL building
22    doMkDLL
23   ) where
24
25 #include "HsVersions.h"
26
27 import Packages
28 import GetImports
29 import DriverState
30 import DriverUtil
31 import DriverPhases
32 import DriverFlags
33 import SysTools         ( newTempName, addFilesToClean, getSysMan, copy )
34 import qualified SysTools       
35 import HscMain
36 import Finder
37 import HscTypes
38 import Outputable
39 import Module
40 import ErrUtils
41 import CmdLineOpts
42 import Config
43 import RdrName          ( GlobalRdrEnv )
44 import Panic
45 import Util
46 import StringBuffer     ( hGetStringBuffer )
47 import BasicTypes       ( SuccessFlag(..) )
48 import Maybes           ( expectJust )
49
50 import ParserCoreUtils ( getCoreModuleName )
51
52 import EXCEPTION
53 import DATA_IOREF       ( readIORef, writeIORef )
54
55 import Directory
56 import System
57 import IO
58 import Monad
59 import Maybe
60
61
62 -- ---------------------------------------------------------------------------
63 -- Pre-process
64
65 -- Just preprocess a file, put the result in a temp. file (used by the
66 -- compilation manager during the summary phase).
67 --
68 -- We return the augmented DynFlags, because they contain the result
69 -- of slurping in the OPTIONS pragmas
70
71 preprocess :: DynFlags -> FilePath -> IO (DynFlags, FilePath)
72 preprocess dflags filename =
73   ASSERT2(isHaskellSrcFilename filename, text filename) 
74   runPipeline (StopBefore anyHsc) dflags ("preprocess") 
75         False{-temporary output file-}
76         Nothing{-no specific output file-}
77         filename
78         Nothing{-no ModLocation-}
79
80
81
82 -- ---------------------------------------------------------------------------
83 --              Compile a file
84 --      This is used in batch mode 
85 compileFile :: GhcMode -> DynFlags -> FilePath -> IO FilePath
86 compileFile mode dflags src = do
87    exists <- doesFileExist src
88    when (not exists) $ 
89         throwDyn (CmdLineError ("file `" ++ src ++ "' does not exist"))
90    
91    o_file  <- readIORef v_Output_file
92    no_link <- readIORef v_NoLink        -- Set by -c or -no-link
93         -- When linking, the -o argument refers to the linker's output. 
94         -- otherwise, we use it as the name for the pipeline's output.
95    let maybe_o_file | no_link   = o_file
96                     | otherwise = Nothing
97
98    stop_flag <- readIORef v_GhcModeFlag
99    (_, out_file) <- runPipeline mode dflags stop_flag True maybe_o_file
100                                 src Nothing{-no ModLocation-}
101    return out_file
102
103
104 -- ---------------------------------------------------------------------------
105 -- Compile
106
107 -- Compile a single module, under the control of the compilation manager.
108 --
109 -- This is the interface between the compilation manager and the
110 -- compiler proper (hsc), where we deal with tedious details like
111 -- reading the OPTIONS pragma from the source file, and passing the
112 -- output of hsc through the C compiler.
113
114 -- The driver sits between 'compile' and 'hscMain', translating calls
115 -- to the former into calls to the latter, and results from the latter
116 -- into results from the former.  It does things like preprocessing
117 -- the .hs file if necessary, and compiling up the .stub_c files to
118 -- generate Linkables.
119
120 -- NB.  No old interface can also mean that the source has changed.
121
122 compile :: HscEnv
123         -> ModSummary
124         -> Bool                 -- True <=> source unchanged
125         -> Bool                 -- True <=> have object
126         -> Maybe ModIface       -- Old interface, if available
127         -> IO CompResult
128
129 data CompResult
130    = CompOK   ModDetails                -- New details
131               (Maybe GlobalRdrEnv)      -- Lexical environment for the module
132                                         -- (Maybe because we may have loaded it from
133                                         --  its precompiled interface)
134               ModIface                  -- New iface
135               (Maybe Linkable)  -- New code; Nothing => compilation was not reqd
136                                 --                      (old code is still valid)
137
138    | CompErrs 
139
140
141 compile hsc_env mod_summary
142         source_unchanged have_object old_iface = do 
143
144    let dyn_flags   = hsc_dflags hsc_env
145        this_mod    = ms_mod mod_summary
146        src_flavour = ms_hsc_src mod_summary
147
148    showPass dyn_flags ("Compiling " ++ showModMsg have_object mod_summary)
149
150    let verb       = verbosity dyn_flags
151    let location   = ms_location mod_summary
152    let input_fn   = expectJust "compile:hs" (ml_hs_file location) 
153    let input_fnpp = expectJust "compile:hspp" (ms_hspp_file mod_summary)
154
155    when (verb >= 2) (hPutStrLn stderr ("compile: input file " ++ input_fnpp))
156
157    -- Add in the OPTIONS from the source file
158    -- This is nasty: we've done this once already, in the compilation manager
159    -- It might be better to cache the flags in the ml_hspp_file field,say
160    opts <- getOptionsFromSource input_fnpp
161    (dyn_flags,unhandled_flags) <- processDynamicFlags opts dyn_flags
162    checkProcessArgsResult unhandled_flags input_fn
163
164    let (basename, _) = splitFilename input_fn
165
166   -- We add the directory in which the .hs files resides) to the import path.
167   -- This is needed when we try to compile the .hc file later, if it
168   -- imports a _stub.h file that we created here.
169    let current_dir = directoryOf basename
170    old_paths <- readIORef v_Include_paths
171    writeIORef v_Include_paths (current_dir : old_paths)
172    -- put back the old include paths afterward.
173    later (writeIORef v_Include_paths old_paths) $ do
174
175    -- Figure out what lang we're generating
176    todo     <- readIORef v_GhcMode
177    hsc_lang <- hscMaybeAdjustTarget todo src_flavour (hscTarget dyn_flags)
178    -- ... and what the next phase should be
179    next_phase <- hscNextPhase src_flavour hsc_lang
180    -- ... and what file to generate the output into
181    get_output_fn <- genOutputFilenameFunc next_phase False Nothing basename
182    output_fn     <- get_output_fn next_phase (Just location)
183
184    let dyn_flags' = dyn_flags { hscTarget = hsc_lang,
185                                 hscOutName = output_fn,
186                                 hscStubCOutName = basename ++ "_stub.c",
187                                 hscStubHOutName = basename ++ "_stub.h",
188                                 extCoreName = basename ++ ".hcr" }
189
190    -- -no-recomp should also work with --make
191    let do_recomp = recompFlag dyn_flags
192        source_unchanged' = source_unchanged && do_recomp
193        hsc_env' = hsc_env { hsc_dflags = dyn_flags' }
194
195    -- run the compiler
196    hsc_result <- hscMain hsc_env' printErrorsAndWarnings mod_summary
197                          source_unchanged' have_object old_iface
198
199    case hsc_result of
200       HscFail -> return CompErrs
201
202       HscNoRecomp details iface -> return (CompOK details Nothing iface Nothing)
203
204       HscRecomp details rdr_env iface
205                 stub_h_exists stub_c_exists maybe_interpreted_code 
206
207         | isHsBoot src_flavour  -- No further compilation to do
208         -> return (CompOK details rdr_env iface Nothing)
209
210         | otherwise             -- Normal Haskell source files
211         -> do
212            let 
213            maybe_stub_o <- compileStub dyn_flags' stub_c_exists
214            let stub_unlinked = case maybe_stub_o of
215                                   Nothing -> []
216                                   Just stub_o -> [ DotO stub_o ]
217
218            (hs_unlinked, unlinked_time) <-
219              case hsc_lang of
220
221                 -- in interpreted mode, just return the compiled code
222                 -- as our "unlinked" object.
223                 HscInterpreted -> 
224                     case maybe_interpreted_code of
225 #ifdef GHCI
226                        Just comp_bc -> return ([BCOs comp_bc], ms_hs_date mod_summary)
227                         -- Why do we use the timestamp of the source file here,
228                         -- rather than the current time?  This works better in
229                         -- the case where the local clock is out of sync
230                         -- with the filesystem's clock.  It's just as accurate:
231                         -- if the source is modified, then the linkable will
232                         -- be out of date.
233 #endif
234                        Nothing -> panic "compile: no interpreted code"
235
236                 -- we're in batch mode: finish the compilation pipeline.
237                 _other -> do
238                    let object_filename = ml_obj_file location
239
240                    runPipeline DoLink dyn_flags ""
241                                True Nothing output_fn (Just location)
242                         -- the object filename comes from the ModLocation
243
244                    o_time <- getModificationTime object_filename
245                    return ([DotO object_filename], o_time)
246
247            let linkable = LM unlinked_time this_mod
248                              (hs_unlinked ++ stub_unlinked)
249
250            return (CompOK details rdr_env iface (Just linkable))
251
252 -----------------------------------------------------------------------------
253 -- stub .h and .c files (for foreign export support)
254
255 compileStub dflags stub_c_exists
256   | not stub_c_exists = return Nothing
257   | stub_c_exists = do
258         -- compile the _stub.c file w/ gcc
259         let stub_c = hscStubCOutName dflags
260         (_, stub_o) <- runPipeline DoLink dflags "stub-compile"
261                             True{-persistent output-} 
262                             Nothing{-no specific output file-}
263                             stub_c
264                             Nothing{-no ModLocation-}
265         return (Just stub_o)
266
267
268 -- ---------------------------------------------------------------------------
269 -- Link
270
271 link :: GhciMode                -- interactive or batch
272      -> DynFlags                -- dynamic flags
273      -> Bool                    -- attempt linking in batch mode?
274      -> HomePackageTable        -- what to link
275      -> IO SuccessFlag
276
277 -- For the moment, in the batch linker, we don't bother to tell doLink
278 -- which packages to link -- it just tries all that are available.
279 -- batch_attempt_linking should only be *looked at* in batch mode.  It
280 -- should only be True if the upsweep was successful and someone
281 -- exports main, i.e., we have good reason to believe that linking
282 -- will succeed.
283
284 #ifdef GHCI
285 link Interactive dflags batch_attempt_linking hpt
286     = do -- Not Linking...(demand linker will do the job)
287          return Succeeded
288 #endif
289
290 link Batch dflags batch_attempt_linking hpt
291    | batch_attempt_linking
292    = do 
293         let 
294             home_mod_infos = moduleEnvElts hpt
295
296             -- the packages we depend on
297             pkg_deps  = concatMap (dep_pkgs . mi_deps . hm_iface) home_mod_infos
298
299             -- the linkables to link
300             linkables = map hm_linkable home_mod_infos
301
302         when (verb >= 3) $ do
303              hPutStrLn stderr "link: linkables are ..."
304              hPutStrLn stderr (showSDoc (vcat (map ppr linkables)))
305
306         -- check for the -no-link flag
307         omit_linking <- readIORef v_NoLink
308         if omit_linking 
309           then do when (verb >= 3) $
310                     hPutStrLn stderr "link(batch): linking omitted (-c flag given)."
311                   return Succeeded
312           else do
313
314         when (verb >= 1) $
315              hPutStrLn stderr "Linking ..."
316
317         let getOfiles (LM _ _ us) = map nameOfObject (filter isObject us)
318             obj_files = concatMap getOfiles linkables
319
320         -- Don't showPass in Batch mode; doLink will do that for us.
321         staticLink dflags obj_files pkg_deps
322
323         when (verb >= 3) (hPutStrLn stderr "link: done")
324
325         -- staticLink only returns if it succeeds
326         return Succeeded
327
328    | otherwise
329    = do when (verb >= 3) $ do
330             hPutStrLn stderr "link(batch): upsweep (partially) failed OR"
331             hPutStrLn stderr "   Main.main not exported; not linking."
332         return Succeeded
333    where
334       verb = verbosity dflags
335       
336 -- ---------------------------------------------------------------------------
337 -- Run a compilation pipeline, consisting of multiple phases.
338
339 -- The DynFlags can be modified by phases in the pipeline (eg. by
340 -- OPTIONS pragmas), and the changes affect later phases in the
341 -- pipeline, but we throw away the resulting DynFlags at the end.
342
343 runPipeline
344   :: GhcMode            -- when to stop
345   -> DynFlags           -- dynamic flags
346   -> String             -- "stop after" flag
347   -> Bool               -- final output is persistent?
348   -> Maybe FilePath     -- where to put the output, optionally
349   -> FilePath           -- input filename
350   -> Maybe ModLocation  -- a ModLocation for this module, if we have one
351   -> IO (DynFlags, FilePath)    -- (final flags, output filename)
352
353 runPipeline todo dflags stop_flag keep_output 
354   maybe_output_filename input_fn maybe_loc
355   = do
356   split <- readIORef v_Split_object_files
357   let (basename, suffix) = splitFilename input_fn
358       start_phase = startPhase suffix
359
360       todo' = case todo of
361                 StopBefore As | split -> StopBefore SplitAs
362                 other                 -> todo
363
364   -- We want to catch cases of "you can't get there from here" before
365   -- we start the pipeline, because otherwise it will just run off the
366   -- end.
367   --
368   -- There is a partial ordering on phases, where A < B iff A occurs
369   -- before B in a normal compilation pipeline.
370   --
371   let stop_phase = case todo' of 
372                         StopBefore phase -> phase
373                         other            -> StopLn
374
375   when (not (start_phase `happensBefore` stop_phase)) $
376         throwDyn (UsageError 
377                     ("flag `" ++ stop_flag
378                      ++ "' is incompatible with source file `"
379                      ++ input_fn ++ "'"))
380
381   -- generate a function which will be used to calculate output file names
382   -- as we go along.
383   get_output_fn <- genOutputFilenameFunc stop_phase keep_output 
384                                          maybe_output_filename basename
385
386   -- Execute the pipeline...
387   (dflags', output_fn, maybe_loc) <- pipeLoop todo' dflags start_phase stop_phase input_fn 
388                                               basename suffix get_output_fn maybe_loc
389
390   -- Sometimes, a compilation phase doesn't actually generate any output
391   -- (eg. the CPP phase when -fcpp is not turned on).  If we end on this
392   -- stage, but we wanted to keep the output, then we have to explicitly
393   -- copy the file.
394   if keep_output 
395         then do final_fn <- get_output_fn stop_phase maybe_loc
396                 when (final_fn /= output_fn) $
397                   copy dflags ("Copying `" ++ output_fn ++ "' to `" ++ final_fn
398                         ++ "'") output_fn final_fn
399                 return (dflags', final_fn)
400         else
401                 return (dflags', output_fn)
402
403
404 pipeLoop :: GhcMode -> DynFlags -> Phase -> Phase 
405          -> FilePath  -> String -> Suffix
406          -> (Phase -> Maybe ModLocation -> IO FilePath)
407          -> Maybe ModLocation
408          -> IO (DynFlags, FilePath, Maybe ModLocation)
409
410 pipeLoop orig_todo dflags phase stop_phase 
411          input_fn orig_basename orig_suff 
412          orig_get_output_fn maybe_loc
413
414   | phase `eqPhase` stop_phase            -- All done
415   = return (dflags, input_fn, maybe_loc)
416
417   | not (phase `happensBefore` stop_phase)
418         -- Something has gone wrong.  We'll try to cover all the cases when
419         -- this could happen, so if we reach here it is a panic.
420         -- eg. it might happen if the -C flag is used on a source file that
421         -- has {-# OPTIONS -fasm #-}.
422   = panic ("pipeLoop: at phase " ++ show phase ++ 
423            " but I wanted to stop at phase " ++ show stop_phase)
424
425   | otherwise 
426   = do  { (next_phase, dflags', maybe_loc, output_fn)
427                 <- runPhase phase orig_todo dflags orig_basename 
428                             orig_suff input_fn orig_get_output_fn maybe_loc
429         ; pipeLoop orig_todo dflags' next_phase stop_phase output_fn
430                    orig_basename orig_suff orig_get_output_fn maybe_loc }
431
432 genOutputFilenameFunc :: Phase -> Bool -> Maybe FilePath -> String
433   -> IO (Phase{-next phase-} -> Maybe ModLocation -> IO FilePath)
434 genOutputFilenameFunc stop_phase keep_final_output maybe_output_filename basename
435  = do
436    hcsuf      <- readIORef v_HC_suf
437    odir       <- readIORef v_Output_dir
438    osuf       <- readIORef v_Object_suf
439    keep_hc    <- readIORef v_Keep_hc_files
440 #ifdef ILX
441    keep_il    <- readIORef v_Keep_il_files
442    keep_ilx   <- readIORef v_Keep_ilx_files
443 #endif
444    keep_raw_s <- readIORef v_Keep_raw_s_files
445    keep_s     <- readIORef v_Keep_s_files
446    let
447         myPhaseInputExt HCc    = hcsuf
448         myPhaseInputExt StopLn = osuf
449         myPhaseInputExt other  = phaseInputExt other
450
451         func next_phase maybe_location
452                 | is_last_phase, Just f <- maybe_output_filename = return f
453                 | is_last_phase && keep_final_output = persistent_fn
454                 | keep_this_output                   = persistent_fn
455                 | otherwise                          = newTempName suffix
456
457            where
458                 is_last_phase = next_phase `eqPhase` stop_phase
459
460                 -- sometimes, we keep output from intermediate stages
461                 keep_this_output = 
462                      case next_phase of
463                              StopLn              -> True
464                              Mangle | keep_raw_s -> True
465                              As     | keep_s     -> True
466                              HCc    | keep_hc    -> True
467                              _other              -> False
468
469                 suffix = myPhaseInputExt next_phase
470
471                 -- persistent object files get put in odir
472                 persistent_fn 
473                    | StopLn <- next_phase = return odir_persistent
474                    | otherwise            = return persistent
475
476                 persistent = basename ++ '.':suffix
477
478                 odir_persistent
479                    | Just loc <- maybe_location = ml_obj_file loc
480                    | Just d <- odir = replaceFilenameDirectory persistent d
481                    | otherwise      = persistent
482
483    return func
484
485
486 -- -----------------------------------------------------------------------------
487 -- Each phase in the pipeline returns the next phase to execute, and the
488 -- name of the file in which the output was placed.
489 --
490 -- We must do things dynamically this way, because we often don't know
491 -- what the rest of the phases will be until part-way through the
492 -- compilation: for example, an {-# OPTIONS -fasm #-} at the beginning
493 -- of a source file can change the latter stages of the pipeline from
494 -- taking the via-C route to using the native code generator.
495
496 runPhase :: Phase
497          -> GhcMode
498          -> DynFlags
499          -> String      -- basename of original input source
500          -> String      -- its extension
501          -> FilePath    -- name of file which contains the input to this phase.
502          -> (Phase -> Maybe ModLocation -> IO FilePath)
503                         -- how to calculate the output filename
504          -> Maybe ModLocation           -- the ModLocation, if we have one
505          -> IO (Phase,                  -- next phase
506                 DynFlags,               -- new dynamic flags
507                 Maybe ModLocation,      -- the ModLocation, if we have one
508                 FilePath)               -- output filename
509
510         -- Invariant: the output filename always contains the output
511         -- Interesting case: Hsc when there is no recompilation to do
512         --                   Then the output filename is still a .o file 
513
514 -------------------------------------------------------------------------------
515 -- Unlit phase 
516
517 runPhase (Unlit sf) _todo dflags _basename _suff input_fn get_output_fn maybe_loc
518   = do let unlit_flags = getOpts dflags opt_L
519        -- The -h option passes the file name for unlit to put in a #line directive
520        output_fn <- get_output_fn (Cpp sf) maybe_loc
521
522        SysTools.runUnlit dflags 
523                 (map SysTools.Option unlit_flags ++
524                           [ SysTools.Option     "-h"
525                           , SysTools.Option     input_fn
526                           , SysTools.FileOption "" input_fn
527                           , SysTools.FileOption "" output_fn
528                           ])
529
530        return (Cpp sf, dflags, maybe_loc, output_fn)
531
532 -------------------------------------------------------------------------------
533 -- Cpp phase : (a) gets OPTIONS out of file
534 --             (b) runs cpp if necessary
535
536 runPhase (Cpp sf) _todo dflags basename suff input_fn get_output_fn maybe_loc
537   = do src_opts <- getOptionsFromSource input_fn
538        (dflags,unhandled_flags) <- processDynamicFlags src_opts dflags
539        checkProcessArgsResult unhandled_flags (basename++'.':suff)
540
541        if not (cppFlag dflags) then
542            -- no need to preprocess CPP, just pass input file along
543            -- to the next phase of the pipeline.
544           return (HsPp sf, dflags, maybe_loc, input_fn)
545         else do
546             output_fn <- get_output_fn (HsPp sf) maybe_loc
547             doCpp dflags True{-raw-} False{-no CC opts-} input_fn output_fn
548             return (HsPp sf, dflags, maybe_loc, output_fn)
549
550 -------------------------------------------------------------------------------
551 -- HsPp phase 
552
553 runPhase (HsPp sf) _todo dflags basename suff input_fn get_output_fn maybe_loc
554   = do if not (ppFlag dflags) then
555            -- no need to preprocess, just pass input file along
556            -- to the next phase of the pipeline.
557           return (Hsc sf, dflags, maybe_loc, input_fn)
558         else do
559             let hspp_opts = getOpts dflags opt_F
560             hs_src_pp_opts <- readIORef v_Hs_source_pp_opts
561             let orig_fn = basename ++ '.':suff
562             output_fn <- get_output_fn (Hsc sf) maybe_loc
563             SysTools.runPp dflags
564                            ( [ SysTools.Option     orig_fn
565                              , SysTools.Option     input_fn
566                              , SysTools.FileOption "" output_fn
567                              ] ++
568                              map SysTools.Option hs_src_pp_opts ++
569                              map SysTools.Option hspp_opts
570                            )
571             return (Hsc sf, dflags, maybe_loc, output_fn)
572
573 -----------------------------------------------------------------------------
574 -- Hsc phase
575
576 -- Compilation of a single module, in "legacy" mode (_not_ under
577 -- the direction of the compilation manager).
578 runPhase (Hsc src_flavour) todo dflags basename suff input_fn get_output_fn _maybe_loc 
579  = do   -- normal Hsc mode, not mkdependHS
580
581   -- we add the current directory (i.e. the directory in which
582   -- the .hs files resides) to the import path, since this is
583   -- what gcc does, and it's probably what you want.
584         let current_dir = directoryOf basename
585         
586         paths <- readIORef v_Include_paths
587         writeIORef v_Include_paths (current_dir : paths)
588         
589   -- gather the imports and module name
590         (hspp_buf,mod_name) <- 
591             case src_flavour of
592                 ExtCoreFile -> do {  -- no explicit imports in ExtCore input.
593                                   ; m <- getCoreModuleName input_fn
594                                   ; return (Nothing, mkModule m) }
595
596                 other -> do { buf <- hGetStringBuffer input_fn
597                             ; (_,_,mod_name) <- getImports dflags buf input_fn
598                             ; return (Just buf, mod_name) }
599
600   -- Build a ModLocation to pass to hscMain.
601   -- The source filename is rather irrelevant by now, but it's used
602   -- by hscMain for messages.  hscMain also needs 
603   -- the .hi and .o filenames, and this is as good a way
604   -- as any to generate them, and better than most. (e.g. takes 
605   -- into accout the -osuf flags)
606         location1 <- mkHomeModLocation2 mod_name basename suff
607
608   -- Boot-ify it if necessary
609         let location2 | isHsBoot src_flavour = addBootSuffixLocn location1
610                       | otherwise            = location1 
611                                         
612
613   -- Take -ohi into account if present
614   -- This can't be done in mkHomeModuleLocation because
615   -- it only applies to the module being compiles
616         ohi <- readIORef v_Output_hi
617         let location3 | Just fn <- ohi = location2{ ml_hi_file = fn }
618                       | otherwise      = location2
619
620   -- Take -o into account if present
621   -- Very like -ohi, but we must *only* do this if we aren't linking
622   -- (If we're linking then the -o applies to the linked thing, not to
623   -- the object file for one module.)
624   -- Note the nasty duplication with the same computation in compileFile above
625         expl_o_file <- readIORef v_Output_file
626         no_link     <- readIORef v_NoLink
627         let location4 | Just ofile <- expl_o_file, no_link 
628                       = location3 { ml_obj_file = ofile }
629                       | otherwise = location3
630
631   -- Tell the finder cache about this module
632         addHomeModuleToFinder mod_name location4
633
634   -- Make the ModSummary to hand to hscMain
635         src_timestamp <- getModificationTime (basename ++ '.':suff)
636         let
637             unused_field = panic "runPhase:ModSummary field"
638                 -- Some fields are not looked at by hscMain
639             mod_summary = ModSummary {  ms_mod       = mod_name, 
640                                         ms_hsc_src   = src_flavour,
641                                         ms_hspp_file = Just input_fn,
642                                         ms_hspp_buf  = hspp_buf,
643                                         ms_location  = location4,
644                                         ms_hs_date   = src_timestamp,
645                                         ms_imps      = unused_field,
646                                         ms_srcimps   = unused_field }
647
648             o_file = ml_obj_file location4      -- The real object file
649
650
651   -- Figure out if the source has changed, for recompilation avoidance.
652   -- only do this if we're eventually going to generate a .o file.
653   -- (ToDo: do when generating .hc files too?)
654   --
655   -- Setting source_unchanged to True means that M.o seems
656   -- to be up to date wrt M.hs; so no need to recompile unless imports have
657   -- changed (which the compiler itself figures out).
658   -- Setting source_unchanged to False tells the compiler that M.o is out of
659   -- date wrt M.hs (or M.o doesn't exist) so we must recompile regardless.
660         let do_recomp = recompFlag dflags
661         source_unchanged <- 
662           if not (do_recomp && case todo of { DoLink -> True; other -> False })
663              then return False
664              else do o_file_exists <- doesFileExist o_file
665                      if not o_file_exists
666                         then return False       -- Need to recompile
667                         else do t2 <- getModificationTime o_file
668                                 if t2 > src_timestamp
669                                   then return True
670                                   else return False
671
672   -- get the DynFlags
673         hsc_lang   <- hscMaybeAdjustTarget todo src_flavour (hscTarget dflags)
674         next_phase <- hscNextPhase src_flavour hsc_lang
675         output_fn  <- get_output_fn next_phase (Just location4)
676
677         let dflags' = dflags { hscTarget = hsc_lang,
678                                hscOutName = output_fn,
679                                hscStubCOutName = basename ++ "_stub.c",
680                                hscStubHOutName = basename ++ "_stub.h",
681                                extCoreName = basename ++ ".hcr" }
682
683         hsc_env <- newHscEnv OneShot dflags'
684
685   -- run the compiler!
686         result <- hscMain hsc_env printErrorsAndWarnings
687                           mod_summary source_unchanged 
688                           False         -- No object file
689                           Nothing       -- No iface
690
691         case result of
692
693             HscFail -> throwDyn (PhaseFailed "hsc" (ExitFailure 1))
694
695             HscNoRecomp details iface -> do
696                 SysTools.touch dflags' "Touching object file" o_file
697                 return (StopLn, dflags', Just location4, o_file)
698
699             HscRecomp _details _rdr_env _iface 
700                       stub_h_exists stub_c_exists
701                       _maybe_interpreted_code -> do
702
703                 -- Deal with stubs 
704                 maybe_stub_o <- compileStub dflags' stub_c_exists
705                 case maybe_stub_o of
706                       Nothing     -> return ()
707                       Just stub_o -> add v_Ld_inputs stub_o
708
709                 -- In the case of hs-boot files, generate a dummy .o-boot 
710                 -- stamp file for the benefit of Make
711                 case src_flavour of
712                   HsBootFile -> SysTools.touch dflags' "Touching object file" o_file
713                   other      -> return ()
714
715                 return (next_phase, dflags', Just location4, output_fn)
716
717 -----------------------------------------------------------------------------
718 -- Cmm phase
719
720 runPhase CmmCpp todo dflags basename suff input_fn get_output_fn maybe_loc
721   = do
722        output_fn <- get_output_fn Cmm maybe_loc
723        doCpp dflags False{-not raw-} True{-include CC opts-} input_fn output_fn 
724        return (Cmm, dflags, maybe_loc, output_fn)
725
726 runPhase Cmm todo dflags basename suff input_fn get_output_fn maybe_loc
727   = do
728         hsc_lang <- hscMaybeAdjustTarget todo HsSrcFile (hscTarget dflags)
729         next_phase <- hscNextPhase HsSrcFile hsc_lang
730         output_fn <- get_output_fn next_phase maybe_loc
731
732         let dflags' = dflags { hscTarget = hsc_lang,
733                                hscOutName = output_fn,
734                                hscStubCOutName = basename ++ "_stub.c",
735                                hscStubHOutName = basename ++ "_stub.h",
736                                extCoreName = basename ++ ".hcr" }
737
738         ok <- hscCmmFile dflags' input_fn
739
740         when (not ok) $ throwDyn (PhaseFailed "cmm" (ExitFailure 1))
741
742         return (next_phase, dflags, maybe_loc, output_fn)
743
744 -----------------------------------------------------------------------------
745 -- Cc phase
746
747 -- we don't support preprocessing .c files (with -E) now.  Doing so introduces
748 -- way too many hacks, and I can't say I've ever used it anyway.
749
750 runPhase cc_phase todo dflags basename suff input_fn get_output_fn maybe_loc
751    | cc_phase `eqPhase` Cc || cc_phase `eqPhase` HCc
752    = do let cc_opts = getOpts dflags opt_c
753             hcc = cc_phase `eqPhase` HCc
754
755         cmdline_include_paths <- readIORef v_Include_paths
756
757         -- HC files have the dependent packages stamped into them
758         pkgs <- if hcc then getHCFilePackages input_fn else return []
759
760         -- add package include paths even if we're just compiling .c
761         -- files; this is the Value Add(TM) that using ghc instead of
762         -- gcc gives you :)
763         pkg_include_dirs <- getPackageIncludePath dflags pkgs
764         let include_paths = foldr (\ x xs -> "-I" : x : xs) []
765                               (cmdline_include_paths ++ pkg_include_dirs)
766
767         (md_c_flags, md_regd_c_flags) <- machdepCCOpts dflags
768
769         let verb = getVerbFlag dflags
770
771         pkg_extra_cc_opts <- getPackageExtraCcOpts dflags pkgs
772
773         split_objs <- readIORef v_Split_object_files
774         let split_opt | hcc && split_objs = [ "-DUSE_SPLIT_MARKERS" ]
775                       | otherwise         = [ ]
776
777         excessPrecision <- readIORef v_Excess_precision
778
779         -- Decide next phase
780         mangle <- readIORef v_Do_asm_mangling
781         let next_phase
782                 | hcc && mangle     = Mangle
783                 | otherwise         = As
784         output_fn <- get_output_fn next_phase maybe_loc
785
786         -- force the C compiler to interpret this file as C when
787         -- compiling .hc files, by adding the -x c option.
788         let langopt | hcc = [ SysTools.Option "-x", SysTools.Option "c"]
789                     | otherwise = [ ]
790
791         SysTools.runCc dflags (langopt ++
792                         [ SysTools.FileOption "" input_fn
793                         , SysTools.Option "-o"
794                         , SysTools.FileOption "" output_fn
795                         ]
796                        ++ map SysTools.Option (
797                           md_c_flags
798                        ++ (if hcc && mangle
799                              then md_regd_c_flags
800                              else [])
801                        ++ [ verb, "-S", "-Wimplicit", "-O" ]
802                        ++ [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ]
803                        ++ cc_opts
804                        ++ split_opt
805                        ++ (if excessPrecision then [] else [ "-ffloat-store" ])
806                        ++ include_paths
807                        ++ pkg_extra_cc_opts
808                        ))
809
810         return (next_phase, dflags, maybe_loc, output_fn)
811
812         -- ToDo: postprocess the output from gcc
813
814 -----------------------------------------------------------------------------
815 -- Mangle phase
816
817 runPhase Mangle todo dflags _basename _suff input_fn get_output_fn maybe_loc
818    = do let mangler_opts = getOpts dflags opt_m
819         machdep_opts <- if (prefixMatch "i386" cTARGETPLATFORM)
820                           then do let n_regs = stolen_x86_regs dflags
821                                   return [ show n_regs ]
822                           else return []
823
824         split <- readIORef v_Split_object_files
825         let next_phase
826                 | split = SplitMangle
827                 | otherwise = As
828         output_fn <- get_output_fn next_phase maybe_loc
829
830         SysTools.runMangle dflags (map SysTools.Option mangler_opts
831                           ++ [ SysTools.FileOption "" input_fn
832                              , SysTools.FileOption "" output_fn
833                              ]
834                           ++ map SysTools.Option machdep_opts)
835
836         return (next_phase, dflags, maybe_loc, output_fn)
837
838 -----------------------------------------------------------------------------
839 -- Splitting phase
840
841 runPhase SplitMangle todo dflags _basename _suff input_fn get_output_fn maybe_loc
842   = do  -- tmp_pfx is the prefix used for the split .s files
843         -- We also use it as the file to contain the no. of split .s files (sigh)
844         split_s_prefix <- SysTools.newTempName "split"
845         let n_files_fn = split_s_prefix
846
847         SysTools.runSplit dflags
848                           [ SysTools.FileOption "" input_fn
849                           , SysTools.FileOption "" split_s_prefix
850                           , SysTools.FileOption "" n_files_fn
851                           ]
852
853         -- Save the number of split files for future references
854         s <- readFile n_files_fn
855         let n_files = read s :: Int
856         writeIORef v_Split_info (split_s_prefix, n_files)
857
858         -- Remember to delete all these files
859         addFilesToClean [ split_s_prefix ++ "__" ++ show n ++ ".s"
860                         | n <- [1..n_files]]
861
862         return (SplitAs, dflags, maybe_loc, "**splitmangle**")
863           -- we don't use the filename
864
865 -----------------------------------------------------------------------------
866 -- As phase
867
868 runPhase As todo dflags _basename _suff input_fn get_output_fn maybe_loc
869   = do  let as_opts =  getOpts dflags opt_a
870         cmdline_include_paths <- readIORef v_Include_paths
871
872         output_fn <- get_output_fn StopLn maybe_loc
873
874         -- we create directories for the object file, because it
875         -- might be a hierarchical module.
876         createDirectoryHierarchy (directoryOf output_fn)
877
878         SysTools.runAs dflags   
879                        (map SysTools.Option as_opts
880                        ++ [ SysTools.Option ("-I" ++ p) | p <- cmdline_include_paths ]
881                        ++ [ SysTools.Option "-c"
882                           , SysTools.FileOption "" input_fn
883                           , SysTools.Option "-o"
884                           , SysTools.FileOption "" output_fn
885                           ])
886
887         return (StopLn, dflags, maybe_loc, output_fn)
888
889
890 runPhase SplitAs todo dflags basename _suff _input_fn get_output_fn maybe_loc
891   = do  let as_opts = getOpts dflags opt_a
892
893         (split_s_prefix, n) <- readIORef v_Split_info
894
895         odir <- readIORef v_Output_dir
896         let real_odir = case odir of
897                                 Nothing -> basename ++ "_split"
898                                 Just d  -> d
899
900         let assemble_file n
901               = do  let input_s  = split_s_prefix ++ "__" ++ show n ++ ".s"
902                     let output_o = replaceFilenameDirectory
903                                         (basename ++ "__" ++ show n ++ ".o")
904                                          real_odir
905                     real_o <- osuf_ify output_o
906                     SysTools.runAs dflags
907                                  (map SysTools.Option as_opts ++
908                                     [ SysTools.Option "-c"
909                                     , SysTools.Option "-o"
910                                     , SysTools.FileOption "" real_o
911                                     , SysTools.FileOption "" input_s
912                                     ])
913         
914         mapM_ assemble_file [1..n]
915
916         output_fn <- get_output_fn StopLn maybe_loc
917         return (StopLn, dflags, maybe_loc, output_fn)
918
919 #ifdef ILX
920 -----------------------------------------------------------------------------
921 -- Ilx2Il phase
922 -- Run ilx2il over the ILX output, getting an IL file
923
924 runPhase Ilx2Il todo dflags _basename _suff input_fn get_output_fn maybe_loc
925   = do  let ilx2il_opts = getOpts dflags opt_I
926         SysTools.runIlx2il (map SysTools.Option ilx2il_opts
927                            ++ [ SysTools.Option "--no-add-suffix-to-assembly",
928                                 SysTools.Option "mscorlib",
929                                 SysTools.Option "-o",
930                                 SysTools.FileOption "" output_fn,
931                                 SysTools.FileOption "" input_fn ])
932         return True
933
934 -----------------------------------------------------------------------------
935 -- Ilasm phase
936 -- Run ilasm over the IL, getting a DLL
937
938 runPhase Ilasm todo dflags _basename _suff input_fn get_output_fn maybe_loc
939   = do  let ilasm_opts = getOpts dflags opt_i
940         SysTools.runIlasm (map SysTools.Option ilasm_opts
941                            ++ [ SysTools.Option "/QUIET",
942                                 SysTools.Option "/DLL",
943                                 SysTools.FileOption "/OUT=" output_fn,
944                                 SysTools.FileOption "" input_fn ])
945         return True
946
947 #endif /* ILX */
948
949 -----------------------------------------------------------------------------
950 -- MoveBinary sort-of-phase
951 -- After having produced a binary, move it somewhere else and generate a
952 -- wrapper script calling the binary. Currently, we need this only in 
953 -- a parallel way (i.e. in GUM), because PVM expects the binary in a
954 -- central directory.
955 -- This is called from staticLink below, after linking. I haven't made it
956 -- a separate phase to minimise interfering with other modules, and
957 -- we don't need the generality of a phase (MoveBinary is always
958 -- done after linking and makes only sense in a parallel setup)   -- HWL
959
960 runPhase_MoveBinary input_fn
961   = do  
962         sysMan   <- getSysMan
963         pvm_root <- getEnv "PVM_ROOT"
964         pvm_arch <- getEnv "PVM_ARCH"
965         let 
966            pvm_executable_base = "=" ++ input_fn
967            pvm_executable = pvm_root ++ "/bin/" ++ pvm_arch ++ "/" ++ pvm_executable_base
968         -- nuke old binary; maybe use configur'ed names for cp and rm?
969         system ("rm -f " ++ pvm_executable)
970         -- move the newly created binary into PVM land
971         system ("cp -p " ++ input_fn ++ " " ++ pvm_executable)
972         -- generate a wrapper script for running a parallel prg under PVM
973         writeFile input_fn (mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan)
974         return True
975
976 -- generates a Perl skript starting a parallel prg under PVM
977 mk_pvm_wrapper_script :: String -> String -> String -> String
978 mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan = unlines $
979  [
980   "eval 'exec perl -S $0 ${1+\"$@\"}'", 
981   "  if $running_under_some_shell;",
982   "# =!=!=!=!=!=!=!=!=!=!=!",
983   "# This script is automatically generated: DO NOT EDIT!!!",
984   "# Generated by Glasgow Haskell Compiler",
985   "# ngoqvam choHbogh vaj' vIHoHnISbej !!!!",
986   "#",
987   "$pvm_executable      = '" ++ pvm_executable ++ "';",
988   "$pvm_executable_base = '" ++ pvm_executable_base ++ "';",
989   "$SysMan = '" ++ sysMan ++ "';",
990   "",
991   {- ToDo: add the magical shortcuts again iff we actually use them -- HWL
992   "# first, some magical shortcuts to run "commands" on the binary",
993   "# (which is hidden)",
994   "if ($#ARGV == 1 && $ARGV[0] eq '+RTS' && $ARGV[1] =~ /^--((size|file|strip|rm|nm).*)/ ) {",
995   "    local($cmd) = $1;",
996   "    system("$cmd $pvm_executable");",
997   "    exit(0); # all done",
998   "}", -}
999   "",
1000   "# Now, run the real binary; process the args first",
1001   "$ENV{'PE'} = $pvm_executable_base;", --  ++ pvm_executable_base,
1002   "$debug = '';",
1003   "$nprocessors = 0; # the default: as many PEs as machines in PVM config",
1004   "@nonPVM_args = ();",
1005   "$in_RTS_args = 0;",
1006   "",
1007   "args: while ($a = shift(@ARGV)) {",
1008   "    if ( $a eq '+RTS' ) {",
1009   "     $in_RTS_args = 1;",
1010   "    } elsif ( $a eq '-RTS' ) {",
1011   "     $in_RTS_args = 0;",
1012   "    }",
1013   "    if ( $a eq '-d' && $in_RTS_args ) {",
1014   "     $debug = '-';",
1015   "    } elsif ( $a =~ /^-qN(\\d+)/ && $in_RTS_args ) {",
1016   "     $nprocessors = $1;",
1017   "    } elsif ( $a =~ /^-qp(\\d+)/ && $in_RTS_args ) {",
1018   "     $nprocessors = $1;",
1019   "    } else {",
1020   "     push(@nonPVM_args, $a);",
1021   "    }",
1022   "}",
1023   "",
1024   "local($return_val) = 0;",
1025   "# Start the parallel execution by calling SysMan",
1026   "system(\"$SysMan $debug $pvm_executable $nprocessors @nonPVM_args\");",
1027   "$return_val = $?;",
1028   "# ToDo: fix race condition moving files and flushing them!!",
1029   "system(\"cp $ENV{'HOME'}/$pvm_executable_base.???.gr .\") if -f \"$ENV{'HOME'}/$pvm_executable_base.002.gr\";",
1030   "exit($return_val);"
1031  ]
1032
1033 -----------------------------------------------------------------------------
1034 -- Complain about non-dynamic flags in OPTIONS pragmas
1035
1036 checkProcessArgsResult flags filename
1037   = do when (notNull flags) (throwDyn (ProgramError (
1038           showSDoc (hang (text filename <> char ':')
1039                       4 (text "unknown flags in  {-# OPTIONS #-} pragma:" <+>
1040                           hsep (map text flags)))
1041         )))
1042
1043 -----------------------------------------------------------------------------
1044 -- Look for the /* GHC_PACKAGES ... */ comment at the top of a .hc file
1045
1046 getHCFilePackages :: FilePath -> IO [PackageId]
1047 getHCFilePackages filename =
1048   EXCEPTION.bracket (openFile filename ReadMode) hClose $ \h -> do
1049     l <- hGetLine h
1050     case l of
1051       '/':'*':' ':'G':'H':'C':'_':'P':'A':'C':'K':'A':'G':'E':'S':rest ->
1052           return (map stringToPackageId (words rest))
1053       _other ->
1054           return []
1055
1056 -----------------------------------------------------------------------------
1057 -- Static linking, of .o files
1058
1059 -- The list of packages passed to link is the list of packages on
1060 -- which this program depends, as discovered by the compilation
1061 -- manager.  It is combined with the list of packages that the user
1062 -- specifies on the command line with -package flags.  
1063 --
1064 -- In one-shot linking mode, we can't discover the package
1065 -- dependencies (because we haven't actually done any compilation or
1066 -- read any interface files), so the user must explicitly specify all
1067 -- the packages.
1068
1069 staticLink :: DynFlags -> [FilePath] -> [PackageId] -> IO ()
1070 staticLink dflags o_files dep_packages = do
1071     let verb = getVerbFlag dflags
1072     static     <- readIORef v_Static
1073     no_hs_main <- readIORef v_NoHsMain
1074
1075     -- get the full list of packages to link with, by combining the
1076     -- explicit packages with the auto packages and all of their
1077     -- dependencies, and eliminating duplicates.
1078
1079     o_file <- readIORef v_Output_file
1080 #if defined(mingw32_HOST_OS)
1081     let output_fn = case o_file of { Just s -> s; Nothing -> "main.exe"; }
1082 #else
1083     let output_fn = case o_file of { Just s -> s; Nothing -> "a.out"; }
1084 #endif
1085
1086     pkg_lib_paths <- getPackageLibraryPath dflags dep_packages
1087     let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths
1088
1089     lib_paths <- readIORef v_Library_paths
1090     let lib_path_opts = map ("-L"++) lib_paths
1091
1092     pkg_link_opts <- getPackageLinkOpts dflags dep_packages
1093
1094 #ifdef darwin_TARGET_OS
1095     pkg_framework_paths <- getPackageFrameworkPath dflags dep_packages
1096     let pkg_framework_path_opts = map ("-F"++) pkg_framework_paths
1097
1098     framework_paths <- readIORef v_Framework_paths
1099     let framework_path_opts = map ("-F"++) framework_paths
1100
1101     pkg_frameworks <- getPackageFrameworks dflags dep_packages
1102     let pkg_framework_opts = concat [ ["-framework", fw] | fw <- pkg_frameworks ]
1103     frameworks <- readIORef v_Cmdline_frameworks
1104     let framework_opts = concat [ ["-framework", fw] | fw <- reverse frameworks ]
1105          -- reverse because they're added in reverse order from the cmd line
1106 #endif
1107
1108         -- probably _stub.o files
1109     extra_ld_inputs <- readIORef v_Ld_inputs
1110
1111         -- opts from -optl-<blah> (including -l<blah> options)
1112     extra_ld_opts <- getStaticOpts v_Opt_l
1113
1114     ways <- readIORef v_Ways
1115
1116     -- Here are some libs that need to be linked at the *end* of
1117     -- the command line, because they contain symbols that are referred to
1118     -- by the RTS.  We can't therefore use the ordinary way opts for these.
1119     let
1120         debug_opts | WayDebug `elem` ways = [ 
1121 #if defined(HAVE_LIBBFD)
1122                         "-lbfd", "-liberty"
1123 #endif
1124                          ]
1125                    | otherwise            = []
1126
1127     let
1128         thread_opts | WayThreaded `elem` ways = [ 
1129 #if !defined(mingw32_TARGET_OS) && !defined(freebsd_TARGET_OS)
1130                         "-lpthread"
1131 #endif
1132 #if defined(osf3_TARGET_OS)
1133                         , "-lexc"
1134 #endif
1135                         ]
1136                     | otherwise               = []
1137
1138     (md_c_flags, _) <- machdepCCOpts dflags
1139     SysTools.runLink dflags ( 
1140                        [ SysTools.Option verb
1141                        , SysTools.Option "-o"
1142                        , SysTools.FileOption "" output_fn
1143                        ]
1144                       ++ map SysTools.Option (
1145                          md_c_flags
1146                       ++ o_files
1147                       ++ extra_ld_inputs
1148                       ++ lib_path_opts
1149                       ++ extra_ld_opts
1150 #ifdef darwin_TARGET_OS
1151                       ++ framework_path_opts
1152                       ++ framework_opts
1153 #endif
1154                       ++ pkg_lib_path_opts
1155                       ++ pkg_link_opts
1156 #ifdef darwin_TARGET_OS
1157                       ++ pkg_framework_path_opts
1158                       ++ pkg_framework_opts
1159 #endif
1160                       ++ debug_opts
1161                       ++ thread_opts
1162                     ))
1163
1164     -- parallel only: move binary to another dir -- HWL
1165     ways_ <- readIORef v_Ways
1166     when (WayPar `elem` ways_)
1167          (do success <- runPhase_MoveBinary output_fn
1168              if success then return ()
1169                         else throwDyn (InstallationError ("cannot move binary to PVM dir")))
1170
1171 -----------------------------------------------------------------------------
1172 -- Making a DLL (only for Win32)
1173
1174 doMkDLL :: DynFlags -> [String] -> [PackageId] -> IO ()
1175 doMkDLL dflags o_files dep_packages = do
1176     let verb = getVerbFlag dflags
1177     static     <- readIORef v_Static
1178     no_hs_main <- readIORef v_NoHsMain
1179
1180     o_file <- readIORef v_Output_file
1181     let output_fn = case o_file of { Just s -> s; Nothing -> "HSdll.dll"; }
1182
1183     pkg_lib_paths <- getPackageLibraryPath dflags dep_packages
1184     let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths
1185
1186     lib_paths <- readIORef v_Library_paths
1187     let lib_path_opts = map ("-L"++) lib_paths
1188
1189     pkg_link_opts <- getPackageLinkOpts dflags dep_packages
1190
1191         -- probably _stub.o files
1192     extra_ld_inputs <- readIORef v_Ld_inputs
1193
1194         -- opts from -optdll-<blah>
1195     extra_ld_opts <- getStaticOpts v_Opt_dll
1196
1197     let pstate = pkgState dflags
1198         rts_id | ExtPackage id <- rtsPackageId pstate = id
1199                | otherwise = panic "staticLink: rts package missing"
1200         base_id | ExtPackage id <- basePackageId pstate = id
1201                 | otherwise = panic "staticLink: base package missing"
1202         rts_pkg  = getPackageDetails pstate rts_id
1203         base_pkg = getPackageDetails pstate base_id
1204
1205     let extra_os = if static || no_hs_main
1206                    then []
1207                    else [ head (libraryDirs rts_pkg) ++ "/Main.dll_o",
1208                           head (libraryDirs base_pkg) ++ "/PrelMain.dll_o" ]
1209
1210     (md_c_flags, _) <- machdepCCOpts dflags
1211     SysTools.runMkDLL dflags
1212          ([ SysTools.Option verb
1213           , SysTools.Option "-o"
1214           , SysTools.FileOption "" output_fn
1215           ]
1216          ++ map SysTools.Option (
1217             md_c_flags
1218          ++ o_files
1219          ++ extra_os
1220          ++ [ "--target=i386-mingw32" ]
1221          ++ extra_ld_inputs
1222          ++ lib_path_opts
1223          ++ extra_ld_opts
1224          ++ pkg_lib_path_opts
1225          ++ pkg_link_opts
1226          ++ (if "--def" `elem` (concatMap words extra_ld_opts)
1227                then [ "" ]
1228                else [ "--export-all" ])
1229         ))
1230
1231 -- -----------------------------------------------------------------------------
1232 -- Misc.
1233
1234 doCpp :: DynFlags -> Bool -> Bool -> FilePath -> FilePath -> IO ()
1235 doCpp dflags raw include_cc_opts input_fn output_fn = do
1236     let hscpp_opts = getOpts dflags opt_P
1237
1238     cmdline_include_paths <- readIORef v_Include_paths
1239
1240     pkg_include_dirs <- getPackageIncludePath dflags []
1241     let include_paths = foldr (\ x xs -> "-I" : x : xs) []
1242                           (cmdline_include_paths ++ pkg_include_dirs)
1243
1244     let verb = getVerbFlag dflags
1245
1246     cc_opts <- if not include_cc_opts 
1247                   then return []
1248                   else do let optc = getOpts dflags opt_c
1249                           (md_c_flags, _) <- machdepCCOpts dflags
1250                           return (optc ++ md_c_flags)
1251
1252     let cpp_prog args | raw       = SysTools.runCpp dflags args
1253                       | otherwise = SysTools.runCc dflags (SysTools.Option "-E" : args)
1254
1255     let target_defs = 
1256           [ "-D" ++ cTARGETOS   ++ "_TARGET_OS=1",
1257             "-D" ++ cTARGETARCH ++ "_TARGET_ARCH=1" ]
1258
1259     cpp_prog       ([SysTools.Option verb]
1260                     ++ map SysTools.Option include_paths
1261                     ++ map SysTools.Option hsSourceCppOpts
1262                     ++ map SysTools.Option hscpp_opts
1263                     ++ map SysTools.Option cc_opts
1264                     ++ map SysTools.Option target_defs
1265                     ++ [ SysTools.Option     "-x"
1266                        , SysTools.Option     "c"
1267                        , SysTools.Option     input_fn
1268         -- We hackily use Option instead of FileOption here, so that the file
1269         -- name is not back-slashed on Windows.  cpp is capable of
1270         -- dealing with / in filenames, so it works fine.  Furthermore
1271         -- if we put in backslashes, cpp outputs #line directives
1272         -- with *double* backslashes.   And that in turn means that
1273         -- our error messages get double backslashes in them.
1274         -- In due course we should arrange that the lexer deals
1275         -- with these \\ escapes properly.
1276                        , SysTools.Option     "-o"
1277                        , SysTools.FileOption "" output_fn
1278                        ])
1279
1280 -- -----------------------------------------------------------------------------
1281 -- Misc.
1282
1283 hscNextPhase :: HscSource -> HscTarget -> IO Phase
1284 hscNextPhase HsBootFile hsc_lang 
1285   = return StopLn
1286
1287 hscNextPhase other hsc_lang = do
1288   split <- readIORef v_Split_object_files
1289   return (case hsc_lang of
1290                 HscC -> HCc
1291                 HscAsm | split -> SplitMangle
1292                        | otherwise -> As
1293                 HscNothing     -> StopLn
1294                 HscInterpreted -> StopLn
1295                 _other         -> StopLn
1296         )
1297
1298 hscMaybeAdjustTarget :: GhcMode -> HscSource -> HscTarget -> IO HscTarget
1299 hscMaybeAdjustTarget todo HsBootFile current_hsc_lang 
1300   = return HscNothing           -- No output (other than Foo.hi-boot) for hs-boot files
1301 hscMaybeAdjustTarget todo other current_hsc_lang 
1302   = do  { keep_hc <- readIORef v_Keep_hc_files
1303         ; let hsc_lang
1304                 -- don't change the lang if we're interpreting
1305                  | current_hsc_lang == HscInterpreted = current_hsc_lang
1306
1307                 -- force -fvia-C if we are being asked for a .hc file
1308                  | StopBefore HCc <- todo = HscC
1309                  | keep_hc                = HscC
1310                 -- otherwise, stick to the plan
1311                  | otherwise = current_hsc_lang
1312         ; return hsc_lang }