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