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