[project @ 2002-02-27 16:29: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         let o_file = 
533                 case expl_o_file of
534                   Nothing -> unJust "source_unchanged" (ml_obj_file location)
535                   Just x  -> x
536         source_unchanged <- 
537           if not (do_recomp && ( todo == DoLink || todo == StopBefore Ln ))
538              then return False
539              else do t1 <- getModificationTime (basename ++ '.':suff)
540                      o_file_exists <- doesFileExist o_file
541                      if not o_file_exists
542                         then return False       -- Need to recompile
543                         else do t2 <- getModificationTime o_file
544                                 if t2 > t1
545                                   then return True
546                                   else return False
547
548   -- get the DynFlags
549         dyn_flags <- getDynFlags
550
551         let dyn_flags' = dyn_flags { hscOutName = output_fn,
552                                      hscStubCOutName = basename ++ "_stub.c",
553                                      hscStubHOutName = basename ++ "_stub.h",
554                                      extCoreName = basename ++ ".hcr" }
555
556   -- run the compiler!
557         pcs <- initPersistentCompilerState
558         result <- hscMain OneShot
559                           dyn_flags' mod
560                           location{ ml_hspp_file=Just input_fn }
561                           source_unchanged
562                           False
563                           Nothing        -- no iface
564                           emptyModuleEnv -- HomeSymbolTable
565                           emptyModuleEnv -- HomeIfaceTable
566                           pcs
567
568         case result of {
569
570             HscFail pcs -> throwDyn (PhaseFailed "hsc" (ExitFailure 1));
571
572             HscNoRecomp pcs details iface -> do { SysTools.touch "Touching object file" o_file
573                                                 ; return Nothing } ;
574
575             HscRecomp pcs details iface stub_h_exists stub_c_exists
576                       _maybe_interpreted_code -> do
577
578                             -- deal with stubs
579                             maybe_stub_o <- compileStub dyn_flags' stub_c_exists
580                             case maybe_stub_o of
581                               Nothing -> return ()
582                               Just stub_o -> add v_Ld_inputs stub_o
583                             case hscLang dyn_flags of
584                               HscNothing -> return Nothing
585                               _ -> return (Just output_fn)
586     }
587
588 -----------------------------------------------------------------------------
589 -- Cc phase
590
591 -- we don't support preprocessing .c files (with -E) now.  Doing so introduces
592 -- way too many hacks, and I can't say I've ever used it anyway.
593
594 run_phase cc_phase basename suff input_fn output_fn
595    | cc_phase == Cc || cc_phase == HCc
596    = do cc_opts              <- getOpts opt_c
597         cmdline_include_paths <- readIORef v_Include_paths
598
599         let hcc = cc_phase == HCc
600
601                 -- add package include paths even if we're just compiling
602                 -- .c files; this is the Value Add(TM) that using
603                 -- ghc instead of gcc gives you :)
604         pkg_include_dirs <- getPackageIncludePath
605         let include_paths = foldr (\ x xs -> "-I" : x : xs) []
606                               (cmdline_include_paths ++ pkg_include_dirs)
607
608         mangle <- readIORef v_Do_asm_mangling
609         (md_c_flags, md_regd_c_flags) <- machdepCCOpts
610
611         verb <- getVerbFlag
612
613         o2 <- readIORef v_minus_o2_for_C
614         let opt_flag | o2        = "-O2"
615                      | otherwise = "-O"
616
617         pkg_extra_cc_opts <- getPackageExtraCcOpts
618
619         split_objs <- readIORef v_Split_object_files
620         let split_opt | hcc && split_objs = [ "-DUSE_SPLIT_MARKERS" ]
621                       | otherwise         = [ ]
622
623         excessPrecision <- readIORef v_Excess_precision
624
625         -- force the C compiler to interpret this file as C when
626         -- compiling .hc files, by adding the -x c option.
627         let langopt
628                 | cc_phase == HCc = [ SysTools.Option "-x", SysTools.Option "c"]
629                 | otherwise       = [ ]
630
631         SysTools.runCc (langopt ++
632                         [ SysTools.FileOption "" input_fn
633                         , SysTools.Option "-o"
634                         , SysTools.FileOption "" output_fn
635                         ]
636                        ++ map SysTools.Option (
637                           md_c_flags
638                        ++ (if cc_phase == HCc && mangle
639                              then md_regd_c_flags
640                              else [])
641                        ++ [ verb, "-S", "-Wimplicit", opt_flag ]
642                        ++ [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ]
643                        ++ cc_opts
644                        ++ split_opt
645                        ++ (if excessPrecision then [] else [ "-ffloat-store" ])
646                        ++ include_paths
647                        ++ pkg_extra_cc_opts
648                        ))
649         return (Just output_fn)
650
651         -- ToDo: postprocess the output from gcc
652
653 -----------------------------------------------------------------------------
654 -- Mangle phase
655
656 run_phase Mangle _basename _suff input_fn output_fn
657   = do mangler_opts <- getOpts opt_m
658        machdep_opts <- if (prefixMatch "i386" cTARGETPLATFORM)
659                        then do n_regs <- dynFlag stolen_x86_regs
660                                return [ show n_regs ]
661                        else return []
662
663        SysTools.runMangle (map SysTools.Option mangler_opts
664                           ++ [ SysTools.FileOption "" input_fn
665                              , SysTools.FileOption "" output_fn
666                              ]
667                           ++ map SysTools.Option machdep_opts)
668        return (Just output_fn)
669
670 -----------------------------------------------------------------------------
671 -- Splitting phase
672
673 run_phase SplitMangle _basename _suff input_fn output_fn
674   = do  -- tmp_pfx is the prefix used for the split .s files
675         -- We also use it as the file to contain the no. of split .s files (sigh)
676         split_s_prefix <- SysTools.newTempName "split"
677         let n_files_fn = split_s_prefix
678
679         SysTools.runSplit [ SysTools.FileOption "" input_fn
680                           , SysTools.FileOption "" split_s_prefix
681                           , SysTools.FileOption "" n_files_fn
682                           ]
683
684         -- Save the number of split files for future references
685         s <- readFile n_files_fn
686         let n_files = read s :: Int
687         writeIORef v_Split_info (split_s_prefix, n_files)
688
689         -- Remember to delete all these files
690         addFilesToClean [ split_s_prefix ++ "__" ++ show n ++ ".s"
691                         | n <- [1..n_files]]
692
693         return (Just output_fn)
694
695 -----------------------------------------------------------------------------
696 -- As phase
697
698 run_phase As _basename _suff input_fn output_fn
699   = do  as_opts               <- getOpts opt_a
700         cmdline_include_paths <- readIORef v_Include_paths
701
702         SysTools.runAs (map SysTools.Option as_opts
703                        ++ [ SysTools.Option ("-I" ++ p) | p <- cmdline_include_paths ]
704                        ++ [ SysTools.Option "-c"
705                           , SysTools.FileOption "" input_fn
706                           , SysTools.Option "-o"
707                           , SysTools.FileOption "" output_fn
708                           ])
709         return (Just output_fn)
710
711 run_phase SplitAs basename _suff _input_fn output_fn
712   = do  as_opts <- getOpts opt_a
713
714         (split_s_prefix, n) <- readIORef v_Split_info
715
716         odir <- readIORef v_Output_dir
717         let real_odir = case odir of
718                                 Nothing -> basename ++ "_split"
719                                 Just d  -> d
720
721         let assemble_file n
722               = do  let input_s  = split_s_prefix ++ "__" ++ show n ++ ".s"
723                     let output_o = newdir real_odir 
724                                         (basename ++ "__" ++ show n ++ ".o")
725                     real_o <- osuf_ify output_o
726                     SysTools.runAs (map SysTools.Option as_opts ++
727                                     [ SysTools.Option "-c"
728                                     , SysTools.Option "-o"
729                                     , SysTools.FileOption "" real_o
730                                     , SysTools.FileOption "" input_s
731                                     ])
732         
733         mapM_ assemble_file [1..n]
734         return (Just output_fn)
735
736 #ifdef ILX
737 -----------------------------------------------------------------------------
738 -- Ilx2Il phase
739 -- Run ilx2il over the ILX output, getting an IL file
740
741 run_phase Ilx2Il _basename _suff input_fn output_fn
742   = do  ilx2il_opts <- getOpts opt_I
743         SysTools.runIlx2il (map SysTools.Option ilx2il_opts
744                            ++ [ SysTools.Option "--no-add-suffix-to-assembly",
745                                 SysTools.Option "mscorlib",
746                                 SysTools.Option "-o",
747                                 SysTools.FileOption "" output_fn,
748                                 SysTools.FileOption "" input_fn ])
749         return (Just output_fn)
750
751 -----------------------------------------------------------------------------
752 -- Ilasm phase
753 -- Run ilasm over the IL, getting a DLL
754
755 run_phase Ilasm _basename _suff input_fn output_fn
756   = do  ilasm_opts <- getOpts opt_i
757         SysTools.runIlasm (map SysTools.Option ilasm_opts
758                            ++ [ SysTools.Option "/QUIET",
759                                 SysTools.Option "/DLL",
760                                 SysTools.FileOption "/OUT=" output_fn,
761                                 SysTools.FileOption "" input_fn ])
762         return (Just output_fn)
763
764 #endif -- ILX
765
766 -----------------------------------------------------------------------------
767 -- MoveBinary sort-of-phase
768 -- After having produced a binary, move it somewhere else and generate a
769 -- wrapper script calling the binary. Currently, we need this only in 
770 -- a parallel way (i.e. in GUM), because PVM expects the binary in a
771 -- central directory.
772 -- This is called from doLink below, after linking. I haven't made it
773 -- a separate phase to minimise interfering with other modules, and
774 -- we don't need the generality of a phase (MoveBinary is always
775 -- done after linking and makes only sense in a parallel setup)   -- HWL
776
777 run_phase_MoveBinary input_fn
778   = do  
779         sysMan   <- getSysMan
780         pvm_root <- getEnv "PVM_ROOT"
781         pvm_arch <- getEnv "PVM_ARCH"
782         let 
783            pvm_executable_base = "=" ++ input_fn
784            pvm_executable = pvm_root ++ "/bin/" ++ pvm_arch ++ "/" ++ pvm_executable_base
785         -- nuke old binary; maybe use configur'ed names for cp and rm?
786         system ("rm -f " ++ pvm_executable)
787         -- move the newly created binary into PVM land
788         system ("cp -p " ++ input_fn ++ " " ++ pvm_executable)
789         -- generate a wrapper script for running a parallel prg under PVM
790         writeFile input_fn (mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan)
791         return True
792
793 -- generates a Perl skript starting a parallel prg under PVM
794 mk_pvm_wrapper_script :: String -> String -> String -> String
795 mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan = unlines $
796  [
797   "eval 'exec perl -S $0 ${1+\"$@\"}'", 
798   "  if $running_under_some_shell;",
799   "# =!=!=!=!=!=!=!=!=!=!=!",
800   "# This script is automatically generated: DO NOT EDIT!!!",
801   "# Generated by Glasgow Haskell Compiler",
802   "# ngoqvam choHbogh vaj' vIHoHnISbej !!!!",
803   "#",
804   "$pvm_executable      = '" ++ pvm_executable ++ "';",
805   "$pvm_executable_base = '" ++ pvm_executable_base ++ "';",
806   "$SysMan = '" ++ sysMan ++ "';",
807   "",
808   {- ToDo: add the magical shortcuts again iff we actually use them -- HWL
809   "# first, some magical shortcuts to run "commands" on the binary",
810   "# (which is hidden)",
811   "if ($#ARGV == 1 && $ARGV[0] eq '+RTS' && $ARGV[1] =~ /^--((size|file|strip|rm|nm).*)/ ) {",
812   "    local($cmd) = $1;",
813   "    system("$cmd $pvm_executable");",
814   "    exit(0); # all done",
815   "}", -}
816   "",
817   "# Now, run the real binary; process the args first",
818   "$ENV{'PE'} = $pvm_executable_base;", --  ++ pvm_executable_base,
819   "$debug = '';",
820   "$nprocessors = 0; # the default: as many PEs as machines in PVM config",
821   "@nonPVM_args = ();",
822   "$in_RTS_args = 0;",
823   "",
824   "args: while ($a = shift(@ARGV)) {",
825   "    if ( $a eq '+RTS' ) {",
826   "     $in_RTS_args = 1;",
827   "    } elsif ( $a eq '-RTS' ) {",
828   "     $in_RTS_args = 0;",
829   "    }",
830   "    if ( $a eq '-d' && $in_RTS_args ) {",
831   "     $debug = '-';",
832   "    } elsif ( $a =~ /^-qN(\\d+)/ && $in_RTS_args ) {",
833   "     $nprocessors = $1;",
834   "    } elsif ( $a =~ /^-qp(\\d+)/ && $in_RTS_args ) {",
835   "     $nprocessors = $1;",
836   "    } else {",
837   "     push(@nonPVM_args, $a);",
838   "    }",
839   "}",
840   "",
841   "local($return_val) = 0;",
842   "# Start the parallel execution by calling SysMan",
843   "system(\"$SysMan $debug $pvm_executable $nprocessors @nonPVM_args\");",
844   "$return_val = $?;",
845   "# ToDo: fix race condition moving files and flushing them!!",
846   "system(\"cp $ENV{'HOME'}/$pvm_executable_base.???.gr .\") if -f \"$ENV{'HOME'}/$pvm_executable_base.002.gr\";",
847   "exit($return_val);"
848  ]
849
850 -----------------------------------------------------------------------------
851 -- Complain about non-dynamic flags in OPTIONS pragmas
852
853 checkProcessArgsResult flags basename suff
854   = do when (not (null flags)) (throwDyn (ProgramError (
855            basename ++ "." ++ suff 
856            ++ ": static flags are not allowed in {-# OPTIONS #-} pragmas:\n\t" 
857            ++ unwords flags)) (ExitFailure 1))
858
859 -----------------------------------------------------------------------------
860 -- Linking
861
862 doLink :: [String] -> IO ()
863 doLink o_files = do
864     verb       <- getVerbFlag
865     static     <- readIORef v_Static
866     no_hs_main <- readIORef v_NoHsMain
867
868     o_file <- readIORef v_Output_file
869     let output_fn = case o_file of { Just s -> s; Nothing -> "a.out"; }
870
871     pkg_lib_paths <- getPackageLibraryPath
872     let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths
873
874     lib_paths <- readIORef v_Library_paths
875     let lib_path_opts = map ("-L"++) lib_paths
876
877     pkg_libs <- getPackageLibraries
878     let imp          = if static then "" else "_imp"
879         pkg_lib_opts = map (\lib -> "-l" ++ lib ++ imp) pkg_libs
880
881     libs <- readIORef v_Cmdline_libraries
882     let lib_opts = map ("-l"++) (reverse libs)
883          -- reverse because they're added in reverse order from the cmd line
884
885     pkg_extra_ld_opts <- getPackageExtraLdOpts
886
887         -- probably _stub.o files
888     extra_ld_inputs <- readIORef v_Ld_inputs
889
890         -- opts from -optl-<blah>
891     extra_ld_opts <- getStaticOpts v_Opt_l
892
893     rts_pkg <- getPackageDetails ["rts"]
894     std_pkg <- getPackageDetails ["std"]
895     let extra_os = if static || no_hs_main
896                    then []
897                    else [ head (library_dirs (head rts_pkg)) ++ "/Main.dll_o",
898                           head (library_dirs (head std_pkg)) ++ "/PrelMain.dll_o" ]
899
900     (md_c_flags, _) <- machdepCCOpts
901     SysTools.runLink ( [ SysTools.Option verb
902                        , SysTools.Option "-o"
903                        , SysTools.FileOption "" output_fn
904                        ]
905                       ++ map SysTools.Option (
906                          md_c_flags
907                       ++ o_files
908                       ++ extra_os
909                       ++ extra_ld_inputs
910                       ++ lib_path_opts
911                       ++ lib_opts
912                       ++ pkg_lib_path_opts
913                       ++ pkg_lib_opts
914                       ++ pkg_extra_ld_opts
915                       ++ extra_ld_opts
916                       ++ if static && not no_hs_main then
917                             [ "-u", prefixUnderscore "Main_zdmain_closure"] 
918                          else []))
919
920     -- parallel only: move binary to another dir -- HWL
921     ways_ <- readIORef v_Ways
922     when (WayPar `elem` ways_)
923          (do success <- run_phase_MoveBinary output_fn
924              if success then return ()
925                         else throwDyn (InstallationError ("cannot move binary to PVM dir")))
926
927 -----------------------------------------------------------------------------
928 -- Making a DLL (only for Win32)
929
930 doMkDLL :: [String] -> IO ()
931 doMkDLL o_files = do
932     verb       <- getVerbFlag
933     static     <- readIORef v_Static
934     no_hs_main <- readIORef v_NoHsMain
935
936     o_file <- readIORef v_Output_file
937     let output_fn = case o_file of { Just s -> s; Nothing -> "HSdll.dll"; }
938
939     pkg_lib_paths <- getPackageLibraryPath
940     let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths
941
942     lib_paths <- readIORef v_Library_paths
943     let lib_path_opts = map ("-L"++) lib_paths
944
945     pkg_libs <- getPackageLibraries
946     let imp = if static then "" else "_imp"
947         pkg_lib_opts = map (\lib -> "-l" ++ lib ++ imp) pkg_libs
948
949     libs <- readIORef v_Cmdline_libraries
950     let lib_opts = map ("-l"++) (reverse libs)
951          -- reverse because they're added in reverse order from the cmd line
952
953     pkg_extra_ld_opts <- getPackageExtraLdOpts
954
955         -- probably _stub.o files
956     extra_ld_inputs <- readIORef v_Ld_inputs
957
958         -- opts from -optdll-<blah>
959     extra_ld_opts <- getStaticOpts v_Opt_dll
960
961     rts_pkg <- getPackageDetails ["rts"]
962     std_pkg <- getPackageDetails ["std"]
963
964     let extra_os = if static || no_hs_main
965                    then []
966                    else [ head (library_dirs (head rts_pkg)) ++ "/Main.dll_o",
967                           head (library_dirs (head std_pkg)) ++ "/PrelMain.dll_o" ]
968
969     (md_c_flags, _) <- machdepCCOpts
970     SysTools.runMkDLL
971          ([ SysTools.Option verb
972           , SysTools.Option "-o"
973           , SysTools.FileOption "" output_fn
974           ]
975          ++ map SysTools.Option (
976             md_c_flags
977          ++ o_files
978          ++ extra_os
979          ++ [ "--target=i386-mingw32" ]
980          ++ extra_ld_inputs
981          ++ lib_path_opts
982          ++ lib_opts
983          ++ pkg_lib_path_opts
984          ++ pkg_lib_opts
985          ++ pkg_extra_ld_opts
986          ++ (if "--def" `elem` (concatMap words extra_ld_opts)
987                then [ "" ]
988                else [ "--export-all" ])
989          ++ extra_ld_opts
990         ))
991
992 -----------------------------------------------------------------------------
993 -- Just preprocess a file, put the result in a temp. file (used by the
994 -- compilation manager during the summary phase).
995
996 preprocess :: FilePath -> IO FilePath
997 preprocess filename =
998   ASSERT(haskellish_src_file filename) 
999   do restoreDynFlags    -- Restore to state of last save
1000      let fInfo = (filename, getFileSuffix filename)
1001      pipeline <- genPipeline (StopBefore Hsc) ("preprocess") False 
1002                              defaultHscLang fInfo
1003      (fn,_)   <- runPipeline pipeline fInfo
1004                              False{-no linking-} False{-no -o flag-}
1005      return fn
1006
1007 -----------------------------------------------------------------------------
1008 -- Compile a single module, under the control of the compilation manager.
1009 --
1010 -- This is the interface between the compilation manager and the
1011 -- compiler proper (hsc), where we deal with tedious details like
1012 -- reading the OPTIONS pragma from the source file, and passing the
1013 -- output of hsc through the C compiler.
1014
1015 -- The driver sits between 'compile' and 'hscMain', translating calls
1016 -- to the former into calls to the latter, and results from the latter
1017 -- into results from the former.  It does things like preprocessing
1018 -- the .hs file if necessary, and compiling up the .stub_c files to
1019 -- generate Linkables.
1020
1021 -- NB.  No old interface can also mean that the source has changed.
1022
1023 compile :: GhciMode                -- distinguish batch from interactive
1024         -> ModSummary              -- summary, including source
1025         -> Bool                    -- True <=> source unchanged
1026         -> Bool                    -- True <=> have object
1027         -> Maybe ModIface          -- old interface, if available
1028         -> HomeSymbolTable         -- for home module ModDetails
1029         -> HomeIfaceTable          -- for home module Ifaces
1030         -> PersistentCompilerState -- persistent compiler state
1031         -> IO CompResult
1032
1033 data CompResult
1034    = CompOK   PersistentCompilerState   -- updated PCS
1035               ModDetails  -- new details (HST additions)
1036               ModIface    -- new iface   (HIT additions)
1037               (Maybe Linkable)
1038                        -- new code; Nothing => compilation was not reqd
1039                        -- (old code is still valid)
1040
1041    | CompErrs PersistentCompilerState   -- updated PCS
1042
1043
1044 compile ghci_mode summary source_unchanged have_object 
1045         old_iface hst hit pcs = do 
1046    dyn_flags <- restoreDynFlags         -- Restore to the state of the last save
1047
1048
1049    showPass dyn_flags 
1050         (showSDoc (text "Compiling" <+> ppr (modSummaryName summary)))
1051
1052    let verb       = verbosity dyn_flags
1053    let location   = ms_location summary
1054    let input_fn   = unJust "compile:hs" (ml_hs_file location) 
1055    let input_fnpp = unJust "compile:hspp" (ml_hspp_file location)
1056
1057    when (verb >= 2) (hPutStrLn stderr ("compile: input file " ++ input_fnpp))
1058
1059    opts <- getOptionsFromSource input_fnpp
1060    processArgs dynamic_flags opts []
1061    dyn_flags <- getDynFlags
1062
1063    let hsc_lang      = hscLang dyn_flags
1064        (basename, _) = splitFilename input_fn
1065        
1066    keep_hc <- readIORef v_Keep_hc_files
1067 #ifdef ILX
1068    keep_il <- readIORef v_Keep_il_files
1069 #endif
1070    keep_s  <- readIORef v_Keep_s_files
1071
1072    output_fn <- 
1073         case hsc_lang of
1074            HscAsm  | keep_s    -> return (basename ++ '.':phaseInputExt As)
1075                    | otherwise -> newTempName (phaseInputExt As)
1076            HscC    | keep_hc   -> return (basename ++ '.':phaseInputExt HCc)
1077                    | otherwise -> newTempName (phaseInputExt HCc)
1078            HscJava             -> newTempName "java" -- ToDo
1079 #ifdef ILX
1080            HscILX  | keep_il   -> return (basename ++ '.':phaseInputExt Ilasm)
1081                    | otherwise -> newTempName (phaseInputExt Ilx2Il)    
1082 #endif
1083            HscInterpreted      -> return (error "no output file")
1084            HscNothing          -> return (error "no output file")
1085
1086    let dyn_flags' = dyn_flags { hscOutName = output_fn,
1087                                 hscStubCOutName = basename ++ "_stub.c",
1088                                 hscStubHOutName = basename ++ "_stub.h",
1089                                 extCoreName = basename ++ ".hcr" }
1090
1091    -- figure out which header files to #include in a generated .hc file
1092    c_includes <- getPackageCIncludes
1093    cmdline_includes <- dynFlag cmdlineHcIncludes -- -#include options
1094
1095    let cc_injects = unlines (map mk_include 
1096                                  (c_includes ++ reverse cmdline_includes))
1097        mk_include h_file = 
1098         case h_file of 
1099            '"':_{-"-} -> "#include "++h_file
1100            '<':_      -> "#include "++h_file
1101            _          -> "#include \""++h_file++"\""
1102
1103    writeIORef v_HCHeader cc_injects
1104
1105    -- -no-recomp should also work with --make
1106    do_recomp <- readIORef v_Recomp
1107    let source_unchanged' = source_unchanged && do_recomp
1108
1109    -- run the compiler
1110    hsc_result <- hscMain ghci_mode dyn_flags'
1111                          (ms_mod summary) location
1112                          source_unchanged' have_object old_iface hst hit pcs
1113
1114    case hsc_result of
1115       HscFail pcs -> return (CompErrs pcs)
1116
1117       HscNoRecomp pcs details iface -> return (CompOK pcs details iface Nothing)
1118
1119       HscRecomp pcs details iface
1120         stub_h_exists stub_c_exists maybe_interpreted_code -> do
1121            let 
1122            maybe_stub_o <- compileStub dyn_flags' stub_c_exists
1123            let stub_unlinked = case maybe_stub_o of
1124                                   Nothing -> []
1125                                   Just stub_o -> [ DotO stub_o ]
1126
1127            (hs_unlinked, unlinked_time) <-
1128              case hsc_lang of
1129
1130                 -- in interpreted mode, just return the compiled code
1131                 -- as our "unlinked" object.
1132                 HscInterpreted -> 
1133                     case maybe_interpreted_code of
1134 #ifdef GHCI
1135                        Just (bcos,itbl_env) -> do tm <- getClockTime 
1136                                                   return ([BCOs bcos itbl_env], tm)
1137 #endif
1138                        Nothing -> panic "compile: no interpreted code"
1139
1140                 -- we're in batch mode: finish the compilation pipeline.
1141                 _other -> do pipe <- genPipeline (StopBefore Ln) "" True 
1142                                         hsc_lang (output_fn, getFileSuffix output_fn)
1143                              -- runPipeline takes input_fn so it can split off 
1144                              -- the base name and use it as the base of 
1145                              -- the output object file.
1146                              let (basename, suffix) = splitFilename input_fn
1147                              (o_file,_) <- 
1148                                  pipeLoop pipe (output_fn, getFileSuffix output_fn)
1149                                                False False 
1150                                                basename suffix
1151                              o_time <- getModificationTime o_file
1152                              return ([DotO o_file], o_time)
1153
1154            let linkable = LM unlinked_time (modSummaryName summary)
1155                              (hs_unlinked ++ stub_unlinked)
1156
1157            return (CompOK pcs details iface (Just linkable))
1158
1159
1160 -----------------------------------------------------------------------------
1161 -- stub .h and .c files (for foreign export support)
1162
1163 compileStub dflags stub_c_exists
1164   | not stub_c_exists = return Nothing
1165   | stub_c_exists = do
1166         -- compile the _stub.c file w/ gcc
1167         let stub_c = hscStubCOutName dflags
1168         pipeline   <- genPipeline (StopBefore Ln) "" True defaultHscLang (stub_c,"c")
1169         (stub_o,_) <- runPipeline pipeline (stub_c,"c") False{-no linking-} 
1170                                   False{-no -o option-}
1171         return (Just stub_o)