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