[project @ 2002-12-18 16:29:25 by simonmar]
[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/config.h"
10
11 module DriverPipeline (
12
13         -- Interfaces for the batch-mode driver
14    genPipeline, runPipeline, pipeLoop, 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 DriverMkDepend
32 import DriverPhases
33 import DriverFlags
34 import SysTools         ( newTempName, addFilesToClean, getSysMan, copy )
35 import qualified SysTools       
36 import HscMain
37 import Finder
38 import HscTypes
39 import Outputable
40 import Module
41 import ErrUtils
42 import CmdLineOpts
43 import Config
44 import Panic
45 import Util
46 import BasicTypes       ( SuccessFlag(..) )
47 import Maybes           ( expectJust )
48
49 import ParserCoreUtils ( getCoreModuleName )
50
51 import EXCEPTION
52 import DATA_IOREF       ( readIORef, writeIORef )
53
54 #ifdef GHCI
55 import Time             ( getClockTime )
56 #endif
57 import Directory
58 import System
59 import IO
60 import Monad
61 import Maybe
62
63
64 -- ---------------------------------------------------------------------------
65 -- Pre-process
66
67 -- Just preprocess a file, put the result in a temp. file (used by the
68 -- compilation manager during the summary phase).
69
70 preprocess :: FilePath -> IO FilePath
71 preprocess filename =
72   ASSERT(haskellish_src_file filename) 
73   do restoreDynFlags    -- Restore to state of last save
74      let fInfo = (filename, getFileSuffix filename)
75      pipeline <- genPipeline (StopBefore Hsc) ("preprocess") False 
76                              defaultHscLang fInfo
77      (fn,_)   <- runPipeline pipeline fInfo
78                              False{-no linking-} False{-no -o flag-}
79      return fn
80
81 -- ---------------------------------------------------------------------------
82 -- Compile
83
84 -- Compile a single module, under the control of the compilation manager.
85 --
86 -- This is the interface between the compilation manager and the
87 -- compiler proper (hsc), where we deal with tedious details like
88 -- reading the OPTIONS pragma from the source file, and passing the
89 -- output of hsc through the C compiler.
90
91 -- The driver sits between 'compile' and 'hscMain', translating calls
92 -- to the former into calls to the latter, and results from the latter
93 -- into results from the former.  It does things like preprocessing
94 -- the .hs file if necessary, and compiling up the .stub_c files to
95 -- generate Linkables.
96
97 -- NB.  No old interface can also mean that the source has changed.
98
99 compile :: GhciMode                -- distinguish batch from interactive
100         -> Module
101         -> ModLocation
102         -> Bool                    -- True <=> source unchanged
103         -> Bool                    -- True <=> have object
104         -> Maybe ModIface          -- old interface, if available
105         -> HomePackageTable        -- For home-module stuff
106         -> PersistentCompilerState -- persistent compiler state
107         -> IO CompResult
108
109 data CompResult
110    = CompOK   PersistentCompilerState   -- Updated PCS
111               ModDetails                -- New details
112               ModIface                  -- New iface
113               (Maybe Linkable)  -- New code; Nothing => compilation was not reqd
114                                 --                      (old code is still valid)
115
116    | CompErrs PersistentCompilerState   -- Updated PCS
117
118
119 compile ghci_mode this_mod location
120         source_unchanged have_object 
121         old_iface hpt pcs = do 
122
123    dyn_flags <- restoreDynFlags         -- Restore to the state of the last save
124
125    showPass dyn_flags 
126         (showSDoc (text "Compiling" <+> ppr this_mod))
127
128    let verb       = verbosity dyn_flags
129    let input_fn   = expectJust "compile:hs" (ml_hs_file location) 
130    let input_fnpp = expectJust "compile:hspp" (ml_hspp_file location)
131    let mod_name   = moduleName this_mod
132
133    when (verb >= 2) (hPutStrLn stderr ("compile: input file " ++ input_fnpp))
134
135    opts <- getOptionsFromSource input_fnpp
136    processArgs dynamic_flags opts []
137    dyn_flags <- getDynFlags
138
139    let hsc_lang      = hscLang dyn_flags
140        (basename, _) = splitFilename input_fn
141        
142    keep_hc <- readIORef v_Keep_hc_files
143 #ifdef ILX
144    keep_il <- readIORef v_Keep_il_files
145 #endif
146    keep_s  <- readIORef v_Keep_s_files
147
148    output_fn <- 
149         case hsc_lang of
150            HscAsm  | keep_s    -> return (basename ++ '.':phaseInputExt As)
151                    | otherwise -> newTempName (phaseInputExt As)
152            HscC    | keep_hc   -> return (basename ++ '.':phaseInputExt HCc)
153                    | otherwise -> newTempName (phaseInputExt HCc)
154            HscJava             -> newTempName "java" -- ToDo
155 #ifdef ILX
156            HscILX  | keep_il   -> return (basename ++ '.':phaseInputExt Ilasm)
157                    | otherwise -> newTempName (phaseInputExt Ilx2Il)    
158 #endif
159            HscInterpreted      -> return (error "no output file")
160            HscNothing          -> return (error "no output file")
161
162    let dyn_flags' = dyn_flags { hscOutName = output_fn,
163                                 hscStubCOutName = basename ++ "_stub.c",
164                                 hscStubHOutName = basename ++ "_stub.h",
165                                 extCoreName = basename ++ ".hcr" }
166
167    -- -no-recomp should also work with --make
168    do_recomp <- readIORef v_Recomp
169    let source_unchanged' = source_unchanged && do_recomp
170        hsc_env = HscEnv { hsc_mode = ghci_mode,
171                           hsc_dflags = dyn_flags',
172                           hsc_HPT    = hpt }
173
174    -- run the compiler
175    hsc_result <- hscMain hsc_env pcs this_mod location
176                          source_unchanged' have_object old_iface
177
178    case hsc_result of
179       HscFail pcs -> return (CompErrs pcs)
180
181       HscNoRecomp pcs details iface -> return (CompOK pcs details iface Nothing)
182
183       HscRecomp pcs details iface
184         stub_h_exists stub_c_exists maybe_interpreted_code -> do
185            let 
186            maybe_stub_o <- compileStub dyn_flags' stub_c_exists
187            let stub_unlinked = case maybe_stub_o of
188                                   Nothing -> []
189                                   Just stub_o -> [ DotO stub_o ]
190
191            (hs_unlinked, unlinked_time) <-
192              case hsc_lang of
193
194                 -- in interpreted mode, just return the compiled code
195                 -- as our "unlinked" object.
196                 HscInterpreted -> 
197                     case maybe_interpreted_code of
198 #ifdef GHCI
199                        Just comp_bc -> do tm <- getClockTime 
200                                           return ([BCOs comp_bc], tm)
201 #endif
202                        Nothing -> panic "compile: no interpreted code"
203
204                 -- we're in batch mode: finish the compilation pipeline.
205                 _other -> do pipe <- genPipeline (StopBefore Ln) "" True 
206                                         hsc_lang (output_fn, getFileSuffix output_fn)
207                              -- runPipeline takes input_fn so it can split off 
208                              -- the base name and use it as the base of 
209                              -- the output object file.
210                              let (basename, suffix) = splitFilename input_fn
211                              (o_file,_) <- 
212                                  pipeLoop pipe (output_fn, getFileSuffix output_fn)
213                                                False False 
214                                                basename suffix
215                              o_time <- getModificationTime o_file
216                              return ([DotO o_file], o_time)
217
218            let linkable = LM unlinked_time mod_name
219                              (hs_unlinked ++ stub_unlinked)
220
221            return (CompOK pcs details iface (Just linkable))
222
223 -----------------------------------------------------------------------------
224 -- stub .h and .c files (for foreign export support)
225
226 compileStub dflags stub_c_exists
227   | not stub_c_exists = return Nothing
228   | stub_c_exists = do
229         -- compile the _stub.c file w/ gcc
230         let stub_c = hscStubCOutName dflags
231         pipeline   <- genPipeline (StopBefore Ln) "" True defaultHscLang (stub_c,"c")
232         (stub_o,_) <- runPipeline pipeline (stub_c,"c") False{-no linking-} 
233                                   False{-no -o option-}
234         return (Just stub_o)
235
236
237 -- ---------------------------------------------------------------------------
238 -- Link
239
240 link :: GhciMode                -- interactive or batch
241      -> DynFlags                -- dynamic flags
242      -> Bool                    -- attempt linking in batch mode?
243      -> HomePackageTable        -- what to link
244      -> IO SuccessFlag
245
246 -- For the moment, in the batch linker, we don't bother to tell doLink
247 -- which packages to link -- it just tries all that are available.
248 -- batch_attempt_linking should only be *looked at* in batch mode.  It
249 -- should only be True if the upsweep was successful and someone
250 -- exports main, i.e., we have good reason to believe that linking
251 -- will succeed.
252
253 #ifdef GHCI
254 link Interactive dflags batch_attempt_linking hpt
255     = do -- Not Linking...(demand linker will do the job)
256          return Succeeded
257 #endif
258
259 link Batch dflags batch_attempt_linking hpt
260    | batch_attempt_linking
261    = do 
262         let 
263             home_mod_infos = moduleEnvElts hpt
264
265             -- the packages we depend on
266             pkg_deps  = concatMap (dep_pkgs . mi_deps . hm_iface) home_mod_infos
267
268             -- the linkables to link
269             linkables = map hm_linkable home_mod_infos
270
271         when (verb >= 3) $ do
272              hPutStrLn stderr "link: linkables are ..."
273              hPutStrLn stderr (showSDoc (vcat (map ppr linkables)))
274
275         -- check for the -no-link flag
276         omit_linking <- readIORef v_NoLink
277         if omit_linking 
278           then do when (verb >= 3) $
279                     hPutStrLn stderr "link(batch): linking omitted (-no-link flag given)."
280                   return Succeeded
281           else do
282
283         when (verb >= 1) $
284              hPutStrLn stderr "Linking ..."
285
286         let getOfiles (LM _ _ us) = map nameOfObject (filter isObject us)
287             obj_files = concatMap getOfiles linkables
288
289         -- Don't showPass in Batch mode; doLink will do that for us.
290         staticLink obj_files pkg_deps
291
292         when (verb >= 3) (hPutStrLn stderr "link: done")
293
294         -- staticLink only returns if it succeeds
295         return Succeeded
296
297    | otherwise
298    = do when (verb >= 3) $ do
299             hPutStrLn stderr "link(batch): upsweep (partially) failed OR"
300             hPutStrLn stderr "   Main.main not exported; not linking."
301         return Succeeded
302    where
303       verb = verbosity dflags
304       
305
306
307
308 -- --------------------------------------------------------------------------
309 -- genPipeline: Pipeline construction
310
311 -- Herein is all the magic about which phases to run in which order, whether
312 -- the intermediate files should be in TMPDIR or in the current directory,
313 -- what the suffix of the intermediate files should be, etc.
314
315 -- The following compilation pipeline algorithm is fairly hacky.  A
316 -- better way to do this would be to express the whole compilation as a
317 -- data flow DAG, where the nodes are the intermediate files and the
318 -- edges are the compilation phases.  This framework would also work
319 -- nicely if a haskell dependency generator was included in the
320 -- driver.
321
322 -- It would also deal much more cleanly with compilation phases that
323 -- generate multiple intermediates, (eg. hsc generates .hc, .hi, and
324 -- possibly stub files), where some of the output files need to be
325 -- processed further (eg. the stub files need to be compiled by the C
326 -- compiler).
327
328 -- A cool thing to do would then be to execute the data flow graph
329 -- concurrently, automatically taking advantage of extra processors on
330 -- the host machine.  For example, when compiling two Haskell files
331 -- where one depends on the other, the data flow graph would determine
332 -- that the C compiler from the first compilation can be overlapped
333 -- with the hsc compilation for the second file.
334
335 data IntermediateFileType
336   = Temporary
337   | Persistent
338   deriving (Eq, Show)
339
340 genPipeline
341    :: GhcMode            -- when to stop
342    -> String             -- "stop after" flag (for error messages)
343    -> Bool               -- True => output is persistent
344    -> HscLang            -- preferred output language for hsc
345    -> (FilePath, String) -- original filename & its suffix 
346    -> IO [              -- list of phases to run for this file
347              (Phase,
348               IntermediateFileType,  -- keep the output from this phase?
349               String)                -- output file suffix
350          ]      
351
352 genPipeline todo stop_flag persistent_output lang (filename,suffix)
353  = do
354    split      <- readIORef v_Split_object_files
355    mangle     <- readIORef v_Do_asm_mangling
356    keep_hc    <- readIORef v_Keep_hc_files
357 #ifdef ILX
358    keep_il    <- readIORef v_Keep_il_files
359    keep_ilx   <- readIORef v_Keep_ilx_files
360 #endif
361    keep_raw_s <- readIORef v_Keep_raw_s_files
362    keep_s     <- readIORef v_Keep_s_files
363    osuf       <- readIORef v_Object_suf
364    hcsuf      <- readIORef v_HC_suf
365
366    let
367    ----------- -----  ----   ---   --   --  -  -  -
368     start = startPhase suffix
369
370       -- special case for mkdependHS: .hspp files go through MkDependHS
371     start_phase | todo == DoMkDependHS && start == Hsc  = MkDependHS
372                 | otherwise = start
373
374     haskellish = haskellish_suffix suffix
375     cish = cish_suffix suffix
376
377        -- for a .hc file we need to force lang to HscC
378     real_lang | start_phase == HCc || start_phase == Mangle = HscC
379               | otherwise                                   = lang
380
381    let
382    ----------- -----  ----   ---   --   --  -  -  -
383     pipeline = preprocess ++ compile
384
385     preprocess
386         | haskellish = [ Unlit, Cpp, HsPp ]
387         | otherwise  = [ ]
388
389     compile
390       | todo == DoMkDependHS = [ MkDependHS ]
391
392       | cish = [ Cc, As ]
393
394       | haskellish = 
395        case real_lang of
396         HscC    | split && mangle -> [ Hsc, HCc, Mangle, SplitMangle, SplitAs ]
397                 | mangle          -> [ Hsc, HCc, Mangle, As ]
398                 | split           -> not_valid
399                 | otherwise       -> [ Hsc, HCc, As ]
400
401         HscAsm  | split           -> [ Hsc, SplitMangle, SplitAs ]
402                 | otherwise       -> [ Hsc, As ]
403
404         HscJava | split           -> not_valid
405                 | otherwise       -> error "not implemented: compiling via Java"
406 #ifdef ILX
407         HscILX  | split           -> not_valid
408                 | otherwise       -> [ Hsc, Ilx2Il, Ilasm ]
409 #endif
410         HscNothing                -> [ Hsc, HCc ] -- HCc is a dummy stop phase
411
412       | otherwise = [ ]  -- just pass this file through to the linker
413
414         -- ToDo: this is somewhat cryptic
415     not_valid = throwDyn (UsageError ("invalid option combination"))
416
417     stop_phase = case todo of 
418                         StopBefore As | split -> SplitAs
419 #ifdef ILX
420                                       | real_lang == HscILX -> Ilasm
421 #endif
422                         StopBefore phase      -> phase
423                         DoMkDependHS          -> Ln
424                         DoLink                -> Ln
425                         DoMkDLL               -> Ln
426    ----------- -----  ----   ---   --   --  -  -  -
427
428         -- this shouldn't happen.
429    when (start_phase /= Ln && start_phase `notElem` pipeline)
430         (throwDyn (CmdLineError ("can't find starting phase for "
431                                  ++ filename)))
432         -- if we can't find the phase we're supposed to stop before,
433         -- something has gone wrong.  This test carefully avoids the
434         -- case where we aren't supposed to do any compilation, because the file
435         -- is already in linkable form (for example).
436 --   hPutStrLn stderr (show ((start_phase `elem` pipeline,stop_phase /= Ln,stop_phase `notElem` pipeline), start_phase, stop_phase, pipeline,todo))
437 --   hFlush stderr
438    when (start_phase `elem` pipeline && 
439          (stop_phase /= Ln && stop_phase `notElem` pipeline))
440         (do
441           throwDyn (UsageError 
442                     ("flag `" ++ stop_flag
443                      ++ "' is incompatible with source file `"
444                      ++ filename ++ "'" ++ show pipeline ++ show stop_phase)))
445    let
446         -- .o and .hc suffixes can be overriden by command-line options:
447       myPhaseInputExt HCc | Just s <- hcsuf = s
448       myPhaseInputExt Ln    = osuf
449       myPhaseInputExt other = phaseInputExt other
450
451       annotatePipeline
452          :: [Phase]             -- raw pipeline
453          -> Phase               -- phase to stop before
454          -> [(Phase, IntermediateFileType, String{-file extension-})]
455       annotatePipeline []     _    = []
456       annotatePipeline (Ln:_) _    = []
457       annotatePipeline (phase:next_phase:ps) stop = 
458           (phase, keep_this_output, myPhaseInputExt next_phase)
459              : annotatePipeline (next_phase:ps) stop
460           where
461                 keep_this_output
462                      | next_phase == stop 
463                      = if persistent_output then Persistent else Temporary
464                      | otherwise
465                      = case next_phase of
466                              Ln -> Persistent
467                              Mangle | keep_raw_s -> Persistent
468                              As     | keep_s     -> Persistent
469                              HCc    | keep_hc    -> Persistent
470 #ifdef ILX
471                              Ilx2Il | keep_ilx   -> Persistent
472                              Ilasm  | keep_il    -> Persistent
473 #endif
474                              _other              -> Temporary
475
476         -- add information about output files to the pipeline
477         -- the suffix on an output file is determined by the next phase
478         -- in the pipeline, so we add linking to the end of the pipeline
479         -- to force the output from the final phase to be a .o file.
480
481       annotated_pipeline = annotatePipeline (pipeline ++ [Ln]) stop_phase
482
483       phase_ne p (p1,_,_) = (p1 /= p)
484    ----------- -----  ----   ---   --   --  -  -  -
485
486    return (
487      takeWhile (phase_ne stop_phase ) $
488      dropWhile (phase_ne start_phase) $
489      annotated_pipeline
490     )
491
492
493 runPipeline
494   :: [ (Phase, IntermediateFileType, String) ] -- phases to run
495   -> (String,String)            -- input file
496   -> Bool                       -- doing linking afterward?
497   -> Bool                       -- take into account -o when generating output?
498   -> IO (String, String)        -- return final filename
499
500 runPipeline pipeline (input_fn,suffix) do_linking use_ofile
501   = pipeLoop pipeline (input_fn,suffix) do_linking use_ofile basename suffix
502   where (basename, _) = splitFilename input_fn
503
504 pipeLoop [] input_fn _ _ _ _ = return input_fn
505 pipeLoop (all_phases@((phase, keep, o_suffix):phases))
506         (input_fn,real_suff) do_linking use_ofile orig_basename orig_suffix
507   = do
508
509      output_fn <- outputFileName (null phases) keep o_suffix
510
511      mbCarryOn <- run_phase phase orig_basename orig_suffix
512                             input_fn output_fn 
513         -- sometimes we bail out early, eg. when the compiler's recompilation
514         -- checker has determined that recompilation isn't necessary.
515      case mbCarryOn of
516        Nothing -> do
517               let (_,keep,final_suffix) = last all_phases
518               ofile <- outputFileName True keep final_suffix
519               return (ofile, final_suffix)
520           -- carry on ...
521        Just fn -> do
522                 {-
523                   Check to see whether we've reached the end of the
524                   pipeline, but did so with an ineffective last stage.
525                   (i.e., it returned the input_fn as the output filename).
526                   
527                   If we did and the output is persistent, copy the contents
528                   of input_fn into the file where the pipeline's output is
529                   expected to end up.
530                 -}
531               atEnd <- finalStage (null phases)
532               when (atEnd && fn == input_fn)
533                    (copy "Saving away compilation pipeline's output"
534                          input_fn
535                          output_fn)
536               {-
537                Notice that in order to keep the invariant that we can
538                determine a compilation pipeline's 'start phase' just
539                by looking at the input filename, the input filename
540                to the next stage/phase is associated here with the suffix
541                of the output file, *even* if it does not have that
542                suffix in reality.
543                
544                Why is this important? Because we may run a compilation
545                pipeline in stages (cf. Main.main.compileFile's two stages),
546                so when generating the next stage we need to be precise
547                about what kind of file (=> suffix) is given as input.
548
549                [Not having to generate a pipeline in stages seems like
550                 the right way to go, but I've punted on this for now --sof]
551                
552               -}
553               pipeLoop phases (fn, o_suffix) do_linking use_ofile
554                         orig_basename orig_suffix
555   where
556      finalStage lastPhase = do
557        o_file <- readIORef v_Output_file
558        return (lastPhase && not do_linking && use_ofile && isJust o_file)
559
560      outputFileName last_phase keep suffix
561         = do o_file <- readIORef v_Output_file
562              atEnd  <- finalStage last_phase
563              if atEnd
564                then case o_file of 
565                        Just s  -> return s
566                        Nothing -> error "outputFileName"
567                else if keep == Persistent
568                            then odir_ify (orig_basename ++ '.':suffix)
569                            else newTempName suffix
570
571 run_phase :: Phase
572           -> String                -- basename of original input source
573           -> String                -- its extension
574           -> FilePath              -- name of file which contains the input to this phase.
575           -> FilePath              -- where to stick the result.
576           -> IO (Maybe FilePath)
577                   -- Nothing => stop the compilation pipeline
578                   -- Just fn => the result of this phase can be found in 'fn'
579                   --            (this can either be 'input_fn' or 'output_fn').
580 -------------------------------------------------------------------------------
581 -- Unlit phase 
582
583 run_phase Unlit _basename _suff input_fn output_fn
584   = do unlit_flags <- getOpts opt_L
585        -- The -h option passes the file name for unlit to put in a #line directive
586        SysTools.runUnlit (map SysTools.Option unlit_flags ++
587                           [ SysTools.Option     "-h"
588                           , SysTools.Option     input_fn
589                           , SysTools.FileOption "" input_fn
590                           , SysTools.FileOption "" output_fn
591                           ])
592        return (Just output_fn)
593
594 -------------------------------------------------------------------------------
595 -- Cpp phase 
596
597 run_phase Cpp basename suff input_fn output_fn
598   = do src_opts <- getOptionsFromSource input_fn
599        unhandled_flags <- processArgs dynamic_flags src_opts []
600        checkProcessArgsResult unhandled_flags basename suff
601
602        do_cpp <- dynFlag cppFlag
603        if not do_cpp then
604            -- no need to preprocess CPP, just pass input file along
605            -- to the next phase of the pipeline.
606           return (Just input_fn)
607         else do
608             hscpp_opts      <- getOpts opt_P
609             hs_src_cpp_opts <- readIORef v_Hs_source_cpp_opts
610
611             cmdline_include_paths <- readIORef v_Include_paths
612
613             pkg_include_dirs <- getPackageIncludePath []
614             let include_paths = foldr (\ x xs -> "-I" : x : xs) []
615                                   (cmdline_include_paths ++ pkg_include_dirs)
616
617             verb <- getVerbFlag
618             (md_c_flags, _) <- machdepCCOpts
619
620             SysTools.runCpp ([SysTools.Option verb]
621                             ++ map SysTools.Option include_paths
622                             ++ map SysTools.Option hs_src_cpp_opts
623                             ++ map SysTools.Option hscpp_opts
624                             ++ map SysTools.Option md_c_flags
625                             ++ [ SysTools.Option     "-x"
626                                , SysTools.Option     "c"
627                                , SysTools.Option     input_fn
628         -- We hackily use Option instead of FileOption here, so that the file
629         -- name is not back-slashed on Windows.  cpp is capable of
630         -- dealing with / in filenames, so it works fine.  Furthermore
631         -- if we put in backslashes, cpp outputs #line directives
632         -- with *double* backslashes.   And that in turn means that
633         -- our error messages get double backslashes in them.
634         -- In due course we should arrange that the lexer deals
635         -- with these \\ escapes properly.
636                                , SysTools.Option     "-o"
637                                , SysTools.FileOption "" output_fn
638                                ])
639             return (Just output_fn)
640
641 -------------------------------------------------------------------------------
642 -- HsPp phase 
643
644 run_phase HsPp basename suff input_fn output_fn
645   = do let orig_fn = basename ++ '.':suff
646        do_pp   <- dynFlag ppFlag
647        if not do_pp then
648            -- no need to preprocess, just pass input file along
649            -- to the next phase of the pipeline.
650           return (Just input_fn)
651         else do
652             hspp_opts      <- getOpts opt_F
653             hs_src_pp_opts <- readIORef v_Hs_source_pp_opts
654             SysTools.runPp ( [ SysTools.Option     orig_fn
655                              , SysTools.Option     input_fn
656                              , SysTools.FileOption "" output_fn
657                              ] ++
658                              map SysTools.Option hs_src_pp_opts ++
659                              map SysTools.Option hspp_opts
660                            )
661             return (Just output_fn)
662
663 -----------------------------------------------------------------------------
664 -- MkDependHS phase
665
666 run_phase MkDependHS basename suff input_fn output_fn 
667  = do src <- readFile input_fn
668       let (import_sources, import_normals, _) = getImports src
669       let orig_fn = basename ++ '.':suff
670       deps_sources <- mapM (findDependency True  orig_fn) import_sources
671       deps_normals <- mapM (findDependency False orig_fn) import_normals
672       let deps = deps_sources ++ deps_normals
673
674       osuf <- readIORef v_Object_suf
675
676       extra_suffixes <- readIORef v_Dep_suffixes
677       let suffixes = osuf : map (++ ('_':osuf)) extra_suffixes
678           ofiles = map (\suf -> basename ++ '.':suf) suffixes
679
680       objs <- mapM odir_ify ofiles
681
682         -- Handle for file that accumulates dependencies 
683       hdl <- readIORef v_Dep_tmp_hdl
684
685         -- std dependency of the object(s) on the source file
686       hPutStrLn hdl (unwords (map escapeSpaces objs) ++ " : " ++
687                      escapeSpaces (basename ++ '.':suff))
688
689       let genDep (dep, False {- not an hi file -}) = 
690              hPutStrLn hdl (unwords (map escapeSpaces objs) ++ " : " ++
691                             escapeSpaces dep)
692           genDep (dep, True  {- is an hi file -}) = do
693              hisuf <- readIORef v_Hi_suf
694              let dep_base = remove_suffix '.' dep
695                  deps = (dep_base ++ hisuf)
696                         : map (\suf -> dep_base ++ suf ++ '_':hisuf) extra_suffixes
697                   -- length objs should be == length deps
698              sequence_ (zipWith (\o d -> hPutStrLn hdl (escapeSpaces o ++ " : " ++ escapeSpaces d)) objs deps)
699
700       sequence_ (map genDep [ d | Just d <- deps ])
701       return (Just output_fn)
702
703 -- add the lines to dep_makefile:
704            -- always:
705                    -- this.o : this.hs
706
707            -- if the dependency is on something other than a .hi file:
708                    -- this.o this.p_o ... : dep
709            -- otherwise
710                    -- if the import is {-# SOURCE #-}
711                            -- this.o this.p_o ... : dep.hi-boot[-$vers]
712                            
713                    -- else
714                            -- this.o ...   : dep.hi
715                            -- this.p_o ... : dep.p_hi
716                            -- ...
717    
718            -- (where .o is $osuf, and the other suffixes come from
719            -- the cmdline -s options).
720    
721
722 -----------------------------------------------------------------------------
723 -- Hsc phase
724
725 -- Compilation of a single module, in "legacy" mode (_not_ under
726 -- the direction of the compilation manager).
727 run_phase Hsc basename suff input_fn output_fn
728   = do
729         
730   -- we add the current directory (i.e. the directory in which
731   -- the .hs files resides) to the import path, since this is
732   -- what gcc does, and it's probably what you want.
733         let current_dir = directoryOf basename
734         
735         paths <- readIORef v_Include_paths
736         writeIORef v_Include_paths (current_dir : paths)
737         
738   -- gather the imports and module name
739         (srcimps,imps,mod_name) <- 
740             if extcoreish_suffix suff
741              then do
742                -- no explicit imports in ExtCore input.
743                m <- getCoreModuleName input_fn
744                return ([], [], mkModuleName m)
745              else 
746                getImportsFromFile input_fn
747
748   -- build a ModLocation to pass to hscMain.
749         let (path,file) = splitFilenameDir basename
750         (mod, location') <- mkHomeModLocation mod_name True path file suff
751
752   -- take -ohi into account if present
753         ohi <- readIORef v_Output_hi
754         let location | Just fn <- ohi = location'{ ml_hi_file = fn }
755                      | otherwise      = location'
756
757   -- figure out if the source has changed, for recompilation avoidance.
758   -- only do this if we're eventually going to generate a .o file.
759   -- (ToDo: do when generating .hc files too?)
760   --
761   -- Setting source_unchanged to True means that M.o seems
762   -- to be up to date wrt M.hs; so no need to recompile unless imports have
763   -- changed (which the compiler itself figures out).
764   -- Setting source_unchanged to False tells the compiler that M.o is out of
765   -- date wrt M.hs (or M.o doesn't exist) so we must recompile regardless.
766         do_recomp   <- readIORef v_Recomp
767         todo        <- readIORef v_GhcMode
768         expl_o_file <- readIORef v_Output_file
769
770         let o_file -- if the -o option is given and IT IS THE OBJECT FILE FOR
771                    -- THIS COMPILATION, then use that to determine if the 
772                    -- source is unchanged.
773                 | Just x <- expl_o_file, todo == StopBefore Ln  =  x
774                 | otherwise = expectJust "source_unchanged" (ml_obj_file location)
775
776         source_unchanged <- 
777           if not (do_recomp && ( todo == DoLink || todo == StopBefore Ln ))
778              then return False
779              else do t1 <- getModificationTime (basename ++ '.':suff)
780                      o_file_exists <- doesFileExist o_file
781                      if not o_file_exists
782                         then return False       -- Need to recompile
783                         else do t2 <- getModificationTime o_file
784                                 if t2 > t1
785                                   then return True
786                                   else return False
787
788   -- get the DynFlags
789         dyn_flags <- getDynFlags
790
791         let dyn_flags' = dyn_flags { hscOutName = output_fn,
792                                      hscStubCOutName = basename ++ "_stub.c",
793                                      hscStubHOutName = basename ++ "_stub.h",
794                                      extCoreName = basename ++ ".hcr" }
795             hsc_env = HscEnv { hsc_mode = OneShot,
796                                hsc_dflags = dyn_flags',
797                                hsc_HPT    = emptyHomePackageTable }
798                         
799
800   -- run the compiler!
801         pcs <- initPersistentCompilerState
802         result <- hscMain hsc_env pcs mod
803                           location{ ml_hspp_file=Just input_fn }
804                           source_unchanged
805                           False
806                           Nothing        -- no iface
807
808         case result of {
809
810             HscFail pcs -> throwDyn (PhaseFailed "hsc" (ExitFailure 1));
811
812             HscNoRecomp pcs details iface -> do { SysTools.touch "Touching object file" o_file
813                                                 ; return Nothing } ;
814
815             HscRecomp pcs details iface stub_h_exists stub_c_exists
816                       _maybe_interpreted_code -> do
817
818                             -- deal with stubs
819                             maybe_stub_o <- compileStub dyn_flags' stub_c_exists
820                             case maybe_stub_o of
821                               Nothing -> return ()
822                               Just stub_o -> add v_Ld_inputs stub_o
823                             case hscLang dyn_flags of
824                               HscNothing -> return Nothing
825                               _ -> return (Just output_fn)
826     }
827
828 -----------------------------------------------------------------------------
829 -- Cc phase
830
831 -- we don't support preprocessing .c files (with -E) now.  Doing so introduces
832 -- way too many hacks, and I can't say I've ever used it anyway.
833
834 run_phase cc_phase basename suff input_fn output_fn
835    | cc_phase == Cc || cc_phase == HCc
836    = do cc_opts              <- getOpts opt_c
837         cmdline_include_paths <- readIORef v_Include_paths
838
839         let hcc = cc_phase == HCc
840
841         -- HC files have the dependent packages stamped into them
842         pkgs <- if hcc then getHCFilePackages input_fn else return []
843
844         -- add package include paths even if we're just compiling .c
845         -- files; this is the Value Add(TM) that using ghc instead of
846         -- gcc gives you :)
847         pkg_include_dirs <- getPackageIncludePath pkgs
848         let include_paths = foldr (\ x xs -> "-I" : x : xs) []
849                               (cmdline_include_paths ++ pkg_include_dirs)
850
851         mangle <- readIORef v_Do_asm_mangling
852         (md_c_flags, md_regd_c_flags) <- machdepCCOpts
853
854         verb <- getVerbFlag
855
856         o2 <- readIORef v_minus_o2_for_C
857         let opt_flag | o2        = "-O2"
858                      | otherwise = "-O"
859
860         pkg_extra_cc_opts <- getPackageExtraCcOpts pkgs
861
862         split_objs <- readIORef v_Split_object_files
863         let split_opt | hcc && split_objs = [ "-DUSE_SPLIT_MARKERS" ]
864                       | otherwise         = [ ]
865
866         excessPrecision <- readIORef v_Excess_precision
867
868         -- force the C compiler to interpret this file as C when
869         -- compiling .hc files, by adding the -x c option.
870         let langopt
871                 | cc_phase == HCc = [ SysTools.Option "-x", SysTools.Option "c"]
872                 | otherwise       = [ ]
873
874         SysTools.runCc (langopt ++
875                         [ SysTools.FileOption "" input_fn
876                         , SysTools.Option "-o"
877                         , SysTools.FileOption "" output_fn
878                         ]
879                        ++ map SysTools.Option (
880                           md_c_flags
881                        ++ (if cc_phase == HCc && mangle
882                              then md_regd_c_flags
883                              else [])
884                        ++ [ verb, "-S", "-Wimplicit", opt_flag ]
885                        ++ [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ]
886                        ++ cc_opts
887                        ++ split_opt
888                        ++ (if excessPrecision then [] else [ "-ffloat-store" ])
889                        ++ include_paths
890                        ++ pkg_extra_cc_opts
891                        ))
892         return (Just output_fn)
893
894         -- ToDo: postprocess the output from gcc
895
896 -----------------------------------------------------------------------------
897 -- Mangle phase
898
899 run_phase Mangle _basename _suff input_fn output_fn
900   = do mangler_opts <- getOpts opt_m
901        machdep_opts <- if (prefixMatch "i386" cTARGETPLATFORM)
902                        then do n_regs <- dynFlag stolen_x86_regs
903                                return [ show n_regs ]
904                        else return []
905
906        SysTools.runMangle (map SysTools.Option mangler_opts
907                           ++ [ SysTools.FileOption "" input_fn
908                              , SysTools.FileOption "" output_fn
909                              ]
910                           ++ map SysTools.Option machdep_opts)
911        return (Just output_fn)
912
913 -----------------------------------------------------------------------------
914 -- Splitting phase
915
916 run_phase SplitMangle _basename _suff input_fn output_fn
917   = do  -- tmp_pfx is the prefix used for the split .s files
918         -- We also use it as the file to contain the no. of split .s files (sigh)
919         split_s_prefix <- SysTools.newTempName "split"
920         let n_files_fn = split_s_prefix
921
922         SysTools.runSplit [ SysTools.FileOption "" input_fn
923                           , SysTools.FileOption "" split_s_prefix
924                           , SysTools.FileOption "" n_files_fn
925                           ]
926
927         -- Save the number of split files for future references
928         s <- readFile n_files_fn
929         let n_files = read s :: Int
930         writeIORef v_Split_info (split_s_prefix, n_files)
931
932         -- Remember to delete all these files
933         addFilesToClean [ split_s_prefix ++ "__" ++ show n ++ ".s"
934                         | n <- [1..n_files]]
935
936         return (Just output_fn)
937
938 -----------------------------------------------------------------------------
939 -- As phase
940
941 run_phase As _basename _suff input_fn output_fn
942   = do  as_opts               <- getOpts opt_a
943         cmdline_include_paths <- readIORef v_Include_paths
944
945         SysTools.runAs (map SysTools.Option as_opts
946                        ++ [ SysTools.Option ("-I" ++ p) | p <- cmdline_include_paths ]
947                        ++ [ SysTools.Option "-c"
948                           , SysTools.FileOption "" input_fn
949                           , SysTools.Option "-o"
950                           , SysTools.FileOption "" output_fn
951                           ])
952         return (Just output_fn)
953
954 run_phase SplitAs basename _suff _input_fn output_fn
955   = do  as_opts <- getOpts opt_a
956
957         (split_s_prefix, n) <- readIORef v_Split_info
958
959         odir <- readIORef v_Output_dir
960         let real_odir = case odir of
961                                 Nothing -> basename ++ "_split"
962                                 Just d  -> d
963
964         let assemble_file n
965               = do  let input_s  = split_s_prefix ++ "__" ++ show n ++ ".s"
966                     let output_o = replaceFilenameDirectory
967                                         (basename ++ "__" ++ show n ++ ".o")
968                                          real_odir
969                     real_o <- osuf_ify output_o
970                     SysTools.runAs (map SysTools.Option as_opts ++
971                                     [ SysTools.Option "-c"
972                                     , SysTools.Option "-o"
973                                     , SysTools.FileOption "" real_o
974                                     , SysTools.FileOption "" input_s
975                                     ])
976         
977         mapM_ assemble_file [1..n]
978         return (Just output_fn)
979
980 #ifdef ILX
981 -----------------------------------------------------------------------------
982 -- Ilx2Il phase
983 -- Run ilx2il over the ILX output, getting an IL file
984
985 run_phase Ilx2Il _basename _suff input_fn output_fn
986   = do  ilx2il_opts <- getOpts opt_I
987         SysTools.runIlx2il (map SysTools.Option ilx2il_opts
988                            ++ [ SysTools.Option "--no-add-suffix-to-assembly",
989                                 SysTools.Option "mscorlib",
990                                 SysTools.Option "-o",
991                                 SysTools.FileOption "" output_fn,
992                                 SysTools.FileOption "" input_fn ])
993         return (Just output_fn)
994
995 -----------------------------------------------------------------------------
996 -- Ilasm phase
997 -- Run ilasm over the IL, getting a DLL
998
999 run_phase Ilasm _basename _suff input_fn output_fn
1000   = do  ilasm_opts <- getOpts opt_i
1001         SysTools.runIlasm (map SysTools.Option ilasm_opts
1002                            ++ [ SysTools.Option "/QUIET",
1003                                 SysTools.Option "/DLL",
1004                                 SysTools.FileOption "/OUT=" output_fn,
1005                                 SysTools.FileOption "" input_fn ])
1006         return (Just output_fn)
1007
1008 #endif -- ILX
1009
1010 -----------------------------------------------------------------------------
1011 -- MoveBinary sort-of-phase
1012 -- After having produced a binary, move it somewhere else and generate a
1013 -- wrapper script calling the binary. Currently, we need this only in 
1014 -- a parallel way (i.e. in GUM), because PVM expects the binary in a
1015 -- central directory.
1016 -- This is called from staticLink below, after linking. I haven't made it
1017 -- a separate phase to minimise interfering with other modules, and
1018 -- we don't need the generality of a phase (MoveBinary is always
1019 -- done after linking and makes only sense in a parallel setup)   -- HWL
1020
1021 run_phase_MoveBinary input_fn
1022   = do  
1023         sysMan   <- getSysMan
1024         pvm_root <- getEnv "PVM_ROOT"
1025         pvm_arch <- getEnv "PVM_ARCH"
1026         let 
1027            pvm_executable_base = "=" ++ input_fn
1028            pvm_executable = pvm_root ++ "/bin/" ++ pvm_arch ++ "/" ++ pvm_executable_base
1029         -- nuke old binary; maybe use configur'ed names for cp and rm?
1030         system ("rm -f " ++ pvm_executable)
1031         -- move the newly created binary into PVM land
1032         system ("cp -p " ++ input_fn ++ " " ++ pvm_executable)
1033         -- generate a wrapper script for running a parallel prg under PVM
1034         writeFile input_fn (mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan)
1035         return True
1036
1037 -- generates a Perl skript starting a parallel prg under PVM
1038 mk_pvm_wrapper_script :: String -> String -> String -> String
1039 mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan = unlines $
1040  [
1041   "eval 'exec perl -S $0 ${1+\"$@\"}'", 
1042   "  if $running_under_some_shell;",
1043   "# =!=!=!=!=!=!=!=!=!=!=!",
1044   "# This script is automatically generated: DO NOT EDIT!!!",
1045   "# Generated by Glasgow Haskell Compiler",
1046   "# ngoqvam choHbogh vaj' vIHoHnISbej !!!!",
1047   "#",
1048   "$pvm_executable      = '" ++ pvm_executable ++ "';",
1049   "$pvm_executable_base = '" ++ pvm_executable_base ++ "';",
1050   "$SysMan = '" ++ sysMan ++ "';",
1051   "",
1052   {- ToDo: add the magical shortcuts again iff we actually use them -- HWL
1053   "# first, some magical shortcuts to run "commands" on the binary",
1054   "# (which is hidden)",
1055   "if ($#ARGV == 1 && $ARGV[0] eq '+RTS' && $ARGV[1] =~ /^--((size|file|strip|rm|nm).*)/ ) {",
1056   "    local($cmd) = $1;",
1057   "    system("$cmd $pvm_executable");",
1058   "    exit(0); # all done",
1059   "}", -}
1060   "",
1061   "# Now, run the real binary; process the args first",
1062   "$ENV{'PE'} = $pvm_executable_base;", --  ++ pvm_executable_base,
1063   "$debug = '';",
1064   "$nprocessors = 0; # the default: as many PEs as machines in PVM config",
1065   "@nonPVM_args = ();",
1066   "$in_RTS_args = 0;",
1067   "",
1068   "args: while ($a = shift(@ARGV)) {",
1069   "    if ( $a eq '+RTS' ) {",
1070   "     $in_RTS_args = 1;",
1071   "    } elsif ( $a eq '-RTS' ) {",
1072   "     $in_RTS_args = 0;",
1073   "    }",
1074   "    if ( $a eq '-d' && $in_RTS_args ) {",
1075   "     $debug = '-';",
1076   "    } elsif ( $a =~ /^-qN(\\d+)/ && $in_RTS_args ) {",
1077   "     $nprocessors = $1;",
1078   "    } elsif ( $a =~ /^-qp(\\d+)/ && $in_RTS_args ) {",
1079   "     $nprocessors = $1;",
1080   "    } else {",
1081   "     push(@nonPVM_args, $a);",
1082   "    }",
1083   "}",
1084   "",
1085   "local($return_val) = 0;",
1086   "# Start the parallel execution by calling SysMan",
1087   "system(\"$SysMan $debug $pvm_executable $nprocessors @nonPVM_args\");",
1088   "$return_val = $?;",
1089   "# ToDo: fix race condition moving files and flushing them!!",
1090   "system(\"cp $ENV{'HOME'}/$pvm_executable_base.???.gr .\") if -f \"$ENV{'HOME'}/$pvm_executable_base.002.gr\";",
1091   "exit($return_val);"
1092  ]
1093
1094 -----------------------------------------------------------------------------
1095 -- Complain about non-dynamic flags in OPTIONS pragmas
1096
1097 checkProcessArgsResult flags basename suff
1098   = do when (notNull flags) (throwDyn (ProgramError (
1099           showSDoc (hang (text basename <> text ('.':suff) <> char ':')
1100                       4 (text "unknown flags in  {-# OPTIONS #-} pragma:" <+>
1101                           hsep (map text flags)))
1102         )))
1103
1104 -----------------------------------------------------------------------------
1105 -- Look for the /* GHC_PACKAGES ... */ comment at the top of a .hc file
1106
1107 getHCFilePackages :: FilePath -> IO [PackageName]
1108 getHCFilePackages filename =
1109   EXCEPTION.bracket (openFile filename ReadMode) hClose $ \h -> do
1110     l <- hGetLine h
1111     case l of
1112       '/':'*':' ':'G':'H':'C':'_':'P':'A':'C':'K':'A':'G':'E':'S':rest ->
1113           return (map mkPackageName (words rest))
1114       _other ->
1115           return []
1116
1117 -----------------------------------------------------------------------------
1118 -- Static linking, of .o files
1119
1120 -- The list of packages passed to link is the list of packages on
1121 -- which this program depends, as discovered by the compilation
1122 -- manager.  It is combined with the list of packages that the user
1123 -- specifies on the command line with -package flags.  
1124 --
1125 -- In one-shot linking mode, we can't discover the package
1126 -- dependencies (because we haven't actually done any compilation or
1127 -- read any interface files), so the user must explicitly specify all
1128 -- the packages.
1129
1130 staticLink :: [FilePath] -> [PackageName] -> IO ()
1131 staticLink o_files dep_packages = do
1132     verb       <- getVerbFlag
1133     static     <- readIORef v_Static
1134     no_hs_main <- readIORef v_NoHsMain
1135
1136     -- get the full list of packages to link with, by combining the
1137     -- explicit packages with the auto packages and all of their
1138     -- dependencies, and eliminating duplicates.
1139
1140     o_file <- readIORef v_Output_file
1141     let output_fn = case o_file of { Just s -> s; Nothing -> "a.out"; }
1142
1143     pkg_lib_paths <- getPackageLibraryPath dep_packages
1144     let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths
1145
1146     lib_paths <- readIORef v_Library_paths
1147     let lib_path_opts = map ("-L"++) lib_paths
1148
1149     pkg_link_opts <- getPackageLinkOpts dep_packages
1150
1151 #ifdef darwin_TARGET_OS
1152     pkg_framework_paths <- getPackageFrameworkPath dep_packages
1153     let pkg_framework_path_opts = map ("-F"++) pkg_framework_paths
1154
1155     framework_paths <- readIORef v_Framework_paths
1156     let framework_path_opts = map ("-F"++) framework_paths
1157
1158     pkg_frameworks <- getPackageFrameworks dep_packages
1159     let pkg_framework_opts = map ("-framework " ++) pkg_frameworks
1160
1161     frameworks <- readIORef v_Cmdline_frameworks
1162     let framework_opts = map ("-framework "++) (reverse frameworks)
1163          -- reverse because they're added in reverse order from the cmd line
1164 #endif
1165
1166         -- probably _stub.o files
1167     extra_ld_inputs <- readIORef v_Ld_inputs
1168
1169         -- opts from -optl-<blah> (including -l<blah> options)
1170     extra_ld_opts <- getStaticOpts v_Opt_l
1171
1172     [rts_pkg, std_pkg] <- getPackageDetails [rtsPackage, basePackage]
1173
1174     let extra_os = if static || no_hs_main
1175                    then []
1176                    else [ head (library_dirs rts_pkg) ++ "/Main.dll_o",
1177                           head (library_dirs std_pkg) ++ "/PrelMain.dll_o" ]
1178
1179     (md_c_flags, _) <- machdepCCOpts
1180     SysTools.runLink ( [ SysTools.Option verb
1181                        , SysTools.Option "-o"
1182                        , SysTools.FileOption "" output_fn
1183                        ]
1184                       ++ map SysTools.Option (
1185                          md_c_flags
1186                       ++ o_files
1187                       ++ extra_os
1188                       ++ extra_ld_inputs
1189                       ++ lib_path_opts
1190                       ++ extra_ld_opts
1191 #ifdef darwin_TARGET_OS
1192                       ++ framework_path_opts
1193                       ++ framework_opts
1194 #endif
1195                       ++ pkg_lib_path_opts
1196                       ++ pkg_link_opts
1197 #ifdef darwin_TARGET_OS
1198                       ++ pkg_framework_path_opts
1199                       ++ pkg_framework_opts
1200 #endif
1201                       ++ if static && not no_hs_main then
1202                             [ "-u", prefixUnderscore "Main_zdmain_closure"] 
1203                          else []))
1204
1205     -- parallel only: move binary to another dir -- HWL
1206     ways_ <- readIORef v_Ways
1207     when (WayPar `elem` ways_)
1208          (do success <- run_phase_MoveBinary output_fn
1209              if success then return ()
1210                         else throwDyn (InstallationError ("cannot move binary to PVM dir")))
1211
1212 -----------------------------------------------------------------------------
1213 -- Making a DLL (only for Win32)
1214
1215 doMkDLL :: [String] -> IO ()
1216 doMkDLL o_files = do
1217     verb       <- getVerbFlag
1218     static     <- readIORef v_Static
1219     no_hs_main <- readIORef v_NoHsMain
1220
1221     o_file <- readIORef v_Output_file
1222     let output_fn = case o_file of { Just s -> s; Nothing -> "HSdll.dll"; }
1223
1224     pkg_lib_paths <- getPackageLibraryPath []
1225     let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths
1226
1227     lib_paths <- readIORef v_Library_paths
1228     let lib_path_opts = map ("-L"++) lib_paths
1229
1230     pkg_link_opts <- getPackageLinkOpts []
1231
1232         -- probably _stub.o files
1233     extra_ld_inputs <- readIORef v_Ld_inputs
1234
1235         -- opts from -optdll-<blah>
1236     extra_ld_opts <- getStaticOpts v_Opt_dll
1237
1238     [rts_pkg, std_pkg] <- getPackageDetails [rtsPackage, basePackage]
1239
1240     let extra_os = if static || no_hs_main
1241                    then []
1242                    else [ head (library_dirs rts_pkg) ++ "/Main.dll_o",
1243                           head (library_dirs std_pkg) ++ "/PrelMain.dll_o" ]
1244
1245     (md_c_flags, _) <- machdepCCOpts
1246     SysTools.runMkDLL
1247          ([ SysTools.Option verb
1248           , SysTools.Option "-o"
1249           , SysTools.FileOption "" output_fn
1250           ]
1251          ++ map SysTools.Option (
1252             md_c_flags
1253          ++ o_files
1254          ++ extra_os
1255          ++ [ "--target=i386-mingw32" ]
1256          ++ extra_ld_inputs
1257          ++ lib_path_opts
1258          ++ extra_ld_opts
1259          ++ pkg_lib_path_opts
1260          ++ pkg_link_opts
1261          ++ (if "--def" `elem` (concatMap words extra_ld_opts)
1262                then [ "" ]
1263                else [ "--export-all" ])
1264         ))