[project @ 2002-04-05 23:24:25 by sof]
[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         HscCore | split && mangle -> [ Hsc, HCc, Mangle, SplitMangle, SplitAs ]
156                 | mangle          -> [ Hsc, HCc, Mangle, As ]
157                 | split           -> not_valid
158                 | otherwise       -> [ Hsc, HCc, As ]
159
160         HscAsm  | split           -> [ Hsc, SplitMangle, SplitAs ]
161                 | otherwise       -> [ Hsc, As ]
162
163         HscJava | split           -> not_valid
164                 | otherwise       -> error "not implemented: compiling via Java"
165 #ifdef ILX
166         HscILX  | split           -> not_valid
167                 | otherwise       -> [ Hsc, Ilx2Il, Ilasm ]
168 #endif
169         HscNothing                -> [ Hsc, HCc ] -- HCc is a dummy stop phase
170
171       | otherwise = [ ]  -- just pass this file through to the linker
172
173         -- ToDo: this is somewhat cryptic
174     not_valid = throwDyn (UsageError ("invalid option combination"))
175
176     stop_phase = case todo of 
177                         StopBefore As | split -> SplitAs
178 #ifdef ILX
179                                       | real_lang == HscILX -> Ilasm
180 #endif
181                         StopBefore phase      -> phase
182                         DoMkDependHS          -> Ln
183                         DoLink                -> Ln
184                         DoMkDLL               -> Ln
185    ----------- -----  ----   ---   --   --  -  -  -
186
187         -- this shouldn't happen.
188    when (start_phase /= Ln && start_phase `notElem` pipeline)
189         (throwDyn (CmdLineError ("can't find starting phase for "
190                                  ++ filename)))
191         -- if we can't find the phase we're supposed to stop before,
192         -- something has gone wrong.  This test carefully avoids the
193         -- case where we aren't supposed to do any compilation, because the file
194         -- is already in linkable form (for example).
195 --   hPutStrLn stderr (show ((start_phase `elem` pipeline,stop_phase /= Ln,stop_phase `notElem` pipeline), start_phase, stop_phase, pipeline,todo))
196 --   hFlush stderr
197    when (start_phase `elem` pipeline && 
198          (stop_phase /= Ln && stop_phase `notElem` pipeline))
199         (do
200           throwDyn (UsageError 
201                     ("flag `" ++ stop_flag
202                      ++ "' is incompatible with source file `"
203                      ++ filename ++ "'" ++ show pipeline ++ show stop_phase)))
204    let
205         -- .o and .hc suffixes can be overriden by command-line options:
206       myPhaseInputExt Ln  | Just s <- osuf  = s
207       myPhaseInputExt HCc | Just s <- hcsuf = s
208       myPhaseInputExt other                 = phaseInputExt other
209
210       annotatePipeline
211          :: [Phase]             -- raw pipeline
212          -> Phase               -- phase to stop before
213          -> [(Phase, IntermediateFileType, String{-file extension-})]
214       annotatePipeline []     _    = []
215       annotatePipeline (Ln:_) _    = []
216       annotatePipeline (phase:next_phase:ps) stop = 
217           (phase, keep_this_output, myPhaseInputExt next_phase)
218              : annotatePipeline (next_phase:ps) stop
219           where
220                 keep_this_output
221                      | next_phase == stop 
222                      = if persistent_output then Persistent else Temporary
223                      | otherwise
224                      = case next_phase of
225                              Ln -> Persistent
226                              Mangle | keep_raw_s -> Persistent
227                              As     | keep_s     -> Persistent
228                              HCc    | keep_hc    -> Persistent
229 #ifdef ILX
230                              Ilx2Il | keep_ilx   -> Persistent
231                              Ilasm  | keep_il    -> Persistent
232 #endif
233                              _other              -> Temporary
234
235         -- add information about output files to the pipeline
236         -- the suffix on an output file is determined by the next phase
237         -- in the pipeline, so we add linking to the end of the pipeline
238         -- to force the output from the final phase to be a .o file.
239
240       annotated_pipeline = annotatePipeline (pipeline ++ [Ln]) stop_phase
241
242       phase_ne p (p1,_,_) = (p1 /= p)
243    ----------- -----  ----   ---   --   --  -  -  -
244
245    return (
246      takeWhile (phase_ne stop_phase ) $
247      dropWhile (phase_ne start_phase) $
248      annotated_pipeline
249     )
250
251
252 runPipeline
253   :: [ (Phase, IntermediateFileType, String) ] -- phases to run
254   -> (String,String)            -- input file
255   -> Bool                       -- doing linking afterward?
256   -> Bool                       -- take into account -o when generating output?
257   -> IO (String, String)        -- return final filename
258
259 runPipeline pipeline (input_fn,suffix) do_linking use_ofile
260   = pipeLoop pipeline (input_fn,suffix) do_linking use_ofile basename suffix
261   where (basename, _) = splitFilename input_fn
262
263 pipeLoop [] input_fn _ _ _ _ = return input_fn
264 pipeLoop (all_phases@((phase, keep, o_suffix):phases))
265         (input_fn,real_suff) do_linking use_ofile orig_basename orig_suffix
266   = do
267
268      output_fn <- outputFileName (null phases) keep o_suffix
269
270      mbCarryOn <- run_phase phase orig_basename orig_suffix
271                             input_fn output_fn 
272         -- sometimes we bail out early, eg. when the compiler's recompilation
273         -- checker has determined that recompilation isn't necessary.
274      case mbCarryOn of
275        Nothing -> do
276               let (_,keep,final_suffix) = last all_phases
277               ofile <- outputFileName True keep final_suffix
278               return (ofile, final_suffix)
279           -- carry on ...
280        Just fn -> do
281                 {-
282                   Check to see whether we've reached the end of the
283                   pipeline, but did so with an ineffective last stage.
284                   (i.e., it returned the input_fn as the output filename).
285                   
286                   If we did and the output is persistent, copy the contents
287                   of input_fn into the file where the pipeline's output is
288                   expected to end up.
289                 -}
290               atEnd <- finalStage (null phases)
291               when (atEnd && fn == input_fn)
292                    (copy "Saving away compilation pipeline's output"
293                          input_fn
294                          output_fn)
295               {-
296                Notice that in order to keep the invariant that we can
297                determine a compilation pipeline's 'start phase' just
298                by looking at the input filename, the input filename
299                to the next stage/phase is associated here with the suffix
300                of the output file, *even* if it does not have that
301                suffix in reality.
302                
303                Why is this important? Because we may run a compilation
304                pipeline in stages (cf. Main.main.compileFile's two stages),
305                so when generating the next stage we need to be precise
306                about what kind of file (=> suffix) is given as input.
307
308                [Not having to generate a pipeline in stages seems like
309                 the right way to go, but I've punted on this for now --sof]
310                
311               -}
312               pipeLoop phases (fn, o_suffix) do_linking use_ofile
313                         orig_basename orig_suffix
314   where
315      finalStage lastPhase = do
316        o_file <- readIORef v_Output_file
317        return (lastPhase && not do_linking && use_ofile && isJust o_file)
318
319      outputFileName last_phase keep suffix
320         = do o_file <- readIORef v_Output_file
321              atEnd  <- finalStage last_phase
322              if atEnd
323                then case o_file of 
324                        Just s  -> return s
325                        Nothing -> error "outputFileName"
326                else if keep == Persistent
327                            then odir_ify (orig_basename ++ '.':suffix)
328                            else newTempName suffix
329
330 run_phase :: Phase
331           -> String                -- basename of original input source
332           -> String                -- its extension
333           -> FilePath              -- name of file which contains the input to this phase.
334           -> FilePath              -- where to stick the result.
335           -> IO (Maybe FilePath)
336                   -- Nothing => stop the compilation pipeline
337                   -- Just fn => the result of this phase can be found in 'fn'
338                   --            (this can either be 'input_fn' or 'output_fn').
339 -------------------------------------------------------------------------------
340 -- Unlit phase 
341
342 run_phase Unlit _basename _suff input_fn output_fn
343   = do unlit_flags <- getOpts opt_L
344        -- The -h option passes the file name for unlit to put in a #line directive
345        SysTools.runUnlit (map SysTools.Option unlit_flags ++
346                           [ SysTools.Option     "-h"
347                           , SysTools.Option     input_fn
348                           , SysTools.FileOption "" input_fn
349                           , SysTools.FileOption "" output_fn
350                           ])
351        return (Just output_fn)
352
353 -------------------------------------------------------------------------------
354 -- Cpp phase 
355
356 run_phase Cpp basename suff input_fn output_fn
357   = do src_opts <- getOptionsFromSource input_fn
358        unhandled_flags <- processArgs dynamic_flags src_opts []
359        checkProcessArgsResult unhandled_flags basename suff
360
361        do_cpp <- dynFlag cppFlag
362        if not do_cpp then
363            -- no need to preprocess CPP, just pass input file along
364            -- to the next phase of the pipeline.
365           return (Just input_fn)
366         else do
367             hscpp_opts      <- getOpts opt_P
368             hs_src_cpp_opts <- readIORef v_Hs_source_cpp_opts
369
370             cmdline_include_paths <- readIORef v_Include_paths
371             pkg_include_dirs <- getPackageIncludePath
372             let include_paths = foldr (\ x xs -> "-I" : x : xs) []
373                                   (cmdline_include_paths ++ pkg_include_dirs)
374
375             verb <- getVerbFlag
376             (md_c_flags, _) <- machdepCCOpts
377
378             SysTools.runCpp ([SysTools.Option verb]
379                             ++ map SysTools.Option include_paths
380                             ++ map SysTools.Option hs_src_cpp_opts
381                             ++ map SysTools.Option hscpp_opts
382                             ++ map SysTools.Option md_c_flags
383                             ++ [ SysTools.Option     "-x"
384                                , SysTools.Option     "c"
385                                , SysTools.Option     input_fn
386         -- We hackily use Option instead of FileOption here, so that the file
387         -- name is not back-slashed on Windows.  cpp is capable of
388         -- dealing with / in filenames, so it works fine.  Furthermore
389         -- if we put in backslashes, cpp outputs #line directives
390         -- with *double* backslashes.   And that in turn means that
391         -- our error messages get double backslashes in them.
392         -- In due course we should arrange that the lexer deals
393         -- with these \\ escapes properly.
394                                , SysTools.Option     "-o"
395                                , SysTools.FileOption "" output_fn
396                                ])
397             return (Just output_fn)
398
399 -------------------------------------------------------------------------------
400 -- HsPp phase 
401 run_phase HsPp basename suff input_fn output_fn
402   = do src_opts <- getOptionsFromSource input_fn
403        unhandled_flags <- processArgs dynamic_flags src_opts []
404        checkProcessArgsResult unhandled_flags basename suff
405
406        let orig_fn = basename ++ '.':suff
407        do_pp   <- dynFlag ppFlag
408        if not do_pp then
409            -- no need to preprocess, just pass input file along
410            -- to the next phase of the pipeline.
411           return (Just input_fn)
412         else do
413             hspp_opts      <- getOpts opt_F
414             hs_src_pp_opts <- readIORef v_Hs_source_pp_opts
415             SysTools.runPp ( [ SysTools.Option     orig_fn
416                              , SysTools.Option     input_fn
417                              , SysTools.FileOption "" output_fn
418                              ] ++
419                              map SysTools.Option hs_src_pp_opts ++
420                              map SysTools.Option hspp_opts
421                            )
422             return (Just output_fn)
423
424 -----------------------------------------------------------------------------
425 -- MkDependHS phase
426
427 run_phase MkDependHS basename suff input_fn output_fn 
428  = do src <- readFile input_fn
429       let (import_sources, import_normals, _) = getImports src
430       let orig_fn = basename ++ '.':suff
431       deps_sources <- mapM (findDependency True  orig_fn) import_sources
432       deps_normals <- mapM (findDependency False orig_fn) import_normals
433       let deps = deps_sources ++ deps_normals
434
435       osuf_opt <- readIORef v_Object_suf
436       let osuf = case osuf_opt of
437                    Nothing -> phaseInputExt Ln
438                    Just s  -> s
439
440       extra_suffixes <- readIORef v_Dep_suffixes
441       let suffixes = osuf : map (++ ('_':osuf)) extra_suffixes
442           ofiles = map (\suf -> basename ++ '.':suf) suffixes
443
444       objs <- mapM odir_ify ofiles
445
446         -- Handle for file that accumulates dependencies 
447       hdl <- readIORef v_Dep_tmp_hdl
448
449         -- std dependency of the object(s) on the source file
450       hPutStrLn hdl (unwords (map escapeSpaces objs) ++ " : " ++
451                      escapeSpaces (basename ++ '.':suff))
452
453       let genDep (dep, False {- not an hi file -}) = 
454              hPutStrLn hdl (unwords (map escapeSpaces objs) ++ " : " ++
455                             escapeSpaces dep)
456           genDep (dep, True  {- is an hi file -}) = do
457              hisuf <- readIORef v_Hi_suf
458              let dep_base = remove_suffix '.' dep
459                  deps = (dep_base ++ hisuf)
460                         : map (\suf -> dep_base ++ suf ++ '_':hisuf) extra_suffixes
461                   -- length objs should be == length deps
462              sequence_ (zipWith (\o d -> hPutStrLn hdl (escapeSpaces o ++ " : " ++ escapeSpaces d)) objs deps)
463
464       sequence_ (map genDep [ d | Just d <- deps ])
465       return (Just output_fn)
466
467 -- add the lines to dep_makefile:
468            -- always:
469                    -- this.o : this.hs
470
471            -- if the dependency is on something other than a .hi file:
472                    -- this.o this.p_o ... : dep
473            -- otherwise
474                    -- if the import is {-# SOURCE #-}
475                            -- this.o this.p_o ... : dep.hi-boot[-$vers]
476                            
477                    -- else
478                            -- this.o ...   : dep.hi
479                            -- this.p_o ... : dep.p_hi
480                            -- ...
481    
482            -- (where .o is $osuf, and the other suffixes come from
483            -- the cmdline -s options).
484    
485
486 -----------------------------------------------------------------------------
487 -- Hsc phase
488
489 -- Compilation of a single module, in "legacy" mode (_not_ under
490 -- the direction of the compilation manager).
491 run_phase Hsc basename suff input_fn output_fn
492   = do
493         
494   -- we add the current directory (i.e. the directory in which
495   -- the .hs files resides) to the import path, since this is
496   -- what gcc does, and it's probably what you want.
497         let current_dir = getdir basename
498         
499         paths <- readIORef v_Include_paths
500         writeIORef v_Include_paths (current_dir : paths)
501         
502   -- figure out which header files to #include in a generated .hc file
503         c_includes <- getPackageCIncludes
504         cmdline_includes <- dynFlag cmdlineHcIncludes -- -#include options
505
506         let cc_injects = unlines (map mk_include 
507                                  (c_includes ++ reverse cmdline_includes))
508             mk_include h_file = 
509                 case h_file of 
510                    '"':_{-"-} -> "#include "++h_file
511                    '<':_      -> "#include "++h_file
512                    _          -> "#include \""++h_file++"\""
513
514         writeIORef v_HCHeader cc_injects
515
516   -- gather the imports and module name
517         (srcimps,imps,mod_name) <- 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 = unJust "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     pkg_extra_ld_opts <- getPackageExtraLdOpts
897
898         -- probably _stub.o files
899     extra_ld_inputs <- readIORef v_Ld_inputs
900
901         -- opts from -optl-<blah>
902     extra_ld_opts <- getStaticOpts v_Opt_l
903
904     rts_pkg <- getPackageDetails ["rts"]
905     std_pkg <- getPackageDetails ["std"]
906     let extra_os = if static || no_hs_main
907                    then []
908                    else [ head (library_dirs (head rts_pkg)) ++ "/Main.dll_o",
909                           head (library_dirs (head std_pkg)) ++ "/PrelMain.dll_o" ]
910
911     (md_c_flags, _) <- machdepCCOpts
912     SysTools.runLink ( [ SysTools.Option verb
913                        , SysTools.Option "-o"
914                        , SysTools.FileOption "" output_fn
915                        ]
916                       ++ map SysTools.Option (
917                          md_c_flags
918                       ++ o_files
919                       ++ extra_os
920                       ++ extra_ld_inputs
921                       ++ lib_path_opts
922                       ++ lib_opts
923                       ++ pkg_lib_path_opts
924                       ++ pkg_lib_opts
925                       ++ pkg_extra_ld_opts
926                       ++ extra_ld_opts
927                       ++ if static && not no_hs_main then
928                             [ "-u", prefixUnderscore "Main_zdmain_closure"] 
929                          else []))
930
931     -- parallel only: move binary to another dir -- HWL
932     ways_ <- readIORef v_Ways
933     when (WayPar `elem` ways_)
934          (do success <- run_phase_MoveBinary output_fn
935              if success then return ()
936                         else throwDyn (InstallationError ("cannot move binary to PVM dir")))
937
938 -----------------------------------------------------------------------------
939 -- Making a DLL (only for Win32)
940
941 doMkDLL :: [String] -> IO ()
942 doMkDLL o_files = do
943     verb       <- getVerbFlag
944     static     <- readIORef v_Static
945     no_hs_main <- readIORef v_NoHsMain
946
947     o_file <- readIORef v_Output_file
948     let output_fn = case o_file of { Just s -> s; Nothing -> "HSdll.dll"; }
949
950     pkg_lib_paths <- getPackageLibraryPath
951     let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths
952
953     lib_paths <- readIORef v_Library_paths
954     let lib_path_opts = map ("-L"++) lib_paths
955
956     pkg_libs <- getPackageLibraries
957     let imp = if static then "" else "_imp"
958         pkg_lib_opts = map (\lib -> "-l" ++ lib ++ imp) pkg_libs
959
960     libs <- readIORef v_Cmdline_libraries
961     let lib_opts = map ("-l"++) (reverse libs)
962          -- reverse because they're added in reverse order from the cmd line
963
964     pkg_extra_ld_opts <- getPackageExtraLdOpts
965
966         -- probably _stub.o files
967     extra_ld_inputs <- readIORef v_Ld_inputs
968
969         -- opts from -optdll-<blah>
970     extra_ld_opts <- getStaticOpts v_Opt_dll
971
972     rts_pkg <- getPackageDetails ["rts"]
973     std_pkg <- getPackageDetails ["std"]
974
975     let extra_os = if static || no_hs_main
976                    then []
977                    else [ head (library_dirs (head rts_pkg)) ++ "/Main.dll_o",
978                           head (library_dirs (head std_pkg)) ++ "/PrelMain.dll_o" ]
979
980     (md_c_flags, _) <- machdepCCOpts
981     SysTools.runMkDLL
982          ([ SysTools.Option verb
983           , SysTools.Option "-o"
984           , SysTools.FileOption "" output_fn
985           ]
986          ++ map SysTools.Option (
987             md_c_flags
988          ++ o_files
989          ++ extra_os
990          ++ [ "--target=i386-mingw32" ]
991          ++ extra_ld_inputs
992          ++ lib_path_opts
993          ++ lib_opts
994          ++ pkg_lib_path_opts
995          ++ pkg_lib_opts
996          ++ pkg_extra_ld_opts
997          ++ (if "--def" `elem` (concatMap words extra_ld_opts)
998                then [ "" ]
999                else [ "--export-all" ])
1000          ++ extra_ld_opts
1001         ))
1002
1003 -----------------------------------------------------------------------------
1004 -- Just preprocess a file, put the result in a temp. file (used by the
1005 -- compilation manager during the summary phase).
1006
1007 preprocess :: FilePath -> IO FilePath
1008 preprocess filename =
1009   ASSERT(haskellish_src_file filename) 
1010   do restoreDynFlags    -- Restore to state of last save
1011      let fInfo = (filename, getFileSuffix filename)
1012      pipeline <- genPipeline (StopBefore Hsc) ("preprocess") False 
1013                              defaultHscLang fInfo
1014      (fn,_)   <- runPipeline pipeline fInfo
1015                              False{-no linking-} False{-no -o flag-}
1016      return fn
1017
1018 -----------------------------------------------------------------------------
1019 -- Compile a single module, under the control of the compilation manager.
1020 --
1021 -- This is the interface between the compilation manager and the
1022 -- compiler proper (hsc), where we deal with tedious details like
1023 -- reading the OPTIONS pragma from the source file, and passing the
1024 -- output of hsc through the C compiler.
1025
1026 -- The driver sits between 'compile' and 'hscMain', translating calls
1027 -- to the former into calls to the latter, and results from the latter
1028 -- into results from the former.  It does things like preprocessing
1029 -- the .hs file if necessary, and compiling up the .stub_c files to
1030 -- generate Linkables.
1031
1032 -- NB.  No old interface can also mean that the source has changed.
1033
1034 compile :: GhciMode                -- distinguish batch from interactive
1035         -> ModSummary              -- summary, including source
1036         -> Bool                    -- True <=> source unchanged
1037         -> Bool                    -- True <=> have object
1038         -> Maybe ModIface          -- old interface, if available
1039         -> HomeSymbolTable         -- for home module ModDetails
1040         -> HomeIfaceTable          -- for home module Ifaces
1041         -> PersistentCompilerState -- persistent compiler state
1042         -> IO CompResult
1043
1044 data CompResult
1045    = CompOK   PersistentCompilerState   -- updated PCS
1046               ModDetails  -- new details (HST additions)
1047               ModIface    -- new iface   (HIT additions)
1048               (Maybe Linkable)
1049                        -- new code; Nothing => compilation was not reqd
1050                        -- (old code is still valid)
1051
1052    | CompErrs PersistentCompilerState   -- updated PCS
1053
1054
1055 compile ghci_mode summary source_unchanged have_object 
1056         old_iface hst hit pcs = do 
1057    dyn_flags <- restoreDynFlags         -- Restore to the state of the last save
1058
1059
1060    showPass dyn_flags 
1061         (showSDoc (text "Compiling" <+> ppr (modSummaryName summary)))
1062
1063    let verb       = verbosity dyn_flags
1064    let location   = ms_location summary
1065    let input_fn   = unJust "compile:hs" (ml_hs_file location) 
1066    let input_fnpp = unJust "compile:hspp" (ml_hspp_file location)
1067
1068    when (verb >= 2) (hPutStrLn stderr ("compile: input file " ++ input_fnpp))
1069
1070    opts <- getOptionsFromSource input_fnpp
1071    processArgs dynamic_flags opts []
1072    dyn_flags <- getDynFlags
1073
1074    let hsc_lang      = hscLang dyn_flags
1075        (basename, _) = splitFilename input_fn
1076        
1077    keep_hc <- readIORef v_Keep_hc_files
1078 #ifdef ILX
1079    keep_il <- readIORef v_Keep_il_files
1080 #endif
1081    keep_s  <- readIORef v_Keep_s_files
1082
1083    output_fn <- 
1084         case hsc_lang of
1085            HscAsm  | keep_s    -> return (basename ++ '.':phaseInputExt As)
1086                    | otherwise -> newTempName (phaseInputExt As)
1087            HscC    | keep_hc   -> return (basename ++ '.':phaseInputExt HCc)
1088                    | otherwise -> newTempName (phaseInputExt HCc)
1089            HscJava             -> newTempName "java" -- ToDo
1090 #ifdef ILX
1091            HscILX  | keep_il   -> return (basename ++ '.':phaseInputExt Ilasm)
1092                    | otherwise -> newTempName (phaseInputExt Ilx2Il)    
1093 #endif
1094            HscInterpreted      -> return (error "no output file")
1095            HscNothing          -> return (error "no output file")
1096
1097    let dyn_flags' = dyn_flags { hscOutName = output_fn,
1098                                 hscStubCOutName = basename ++ "_stub.c",
1099                                 hscStubHOutName = basename ++ "_stub.h",
1100                                 extCoreName = basename ++ ".hcr" }
1101
1102    -- figure out which header files to #include in a generated .hc file
1103    c_includes <- getPackageCIncludes
1104    cmdline_includes <- dynFlag cmdlineHcIncludes -- -#include options
1105
1106    let cc_injects = unlines (map mk_include 
1107                                  (c_includes ++ reverse cmdline_includes))
1108        mk_include h_file = 
1109         case h_file of 
1110            '"':_{-"-} -> "#include "++h_file
1111            '<':_      -> "#include "++h_file
1112            _          -> "#include \""++h_file++"\""
1113
1114    writeIORef v_HCHeader cc_injects
1115
1116    -- -no-recomp should also work with --make
1117    do_recomp <- readIORef v_Recomp
1118    let source_unchanged' = source_unchanged && do_recomp
1119
1120    -- run the compiler
1121    hsc_result <- hscMain ghci_mode dyn_flags'
1122                          (ms_mod summary) location
1123                          source_unchanged' have_object old_iface hst hit pcs
1124
1125    case hsc_result of
1126       HscFail pcs -> return (CompErrs pcs)
1127
1128       HscNoRecomp pcs details iface -> return (CompOK pcs details iface Nothing)
1129
1130       HscRecomp pcs details iface
1131         stub_h_exists stub_c_exists maybe_interpreted_code -> do
1132            let 
1133            maybe_stub_o <- compileStub dyn_flags' stub_c_exists
1134            let stub_unlinked = case maybe_stub_o of
1135                                   Nothing -> []
1136                                   Just stub_o -> [ DotO stub_o ]
1137
1138            (hs_unlinked, unlinked_time) <-
1139              case hsc_lang of
1140
1141                 -- in interpreted mode, just return the compiled code
1142                 -- as our "unlinked" object.
1143                 HscInterpreted -> 
1144                     case maybe_interpreted_code of
1145 #ifdef GHCI
1146                        Just (bcos,itbl_env) -> do tm <- getClockTime 
1147                                                   return ([BCOs bcos itbl_env], tm)
1148 #endif
1149                        Nothing -> panic "compile: no interpreted code"
1150
1151                 -- we're in batch mode: finish the compilation pipeline.
1152                 _other -> do pipe <- genPipeline (StopBefore Ln) "" True 
1153                                         hsc_lang (output_fn, getFileSuffix output_fn)
1154                              -- runPipeline takes input_fn so it can split off 
1155                              -- the base name and use it as the base of 
1156                              -- the output object file.
1157                              let (basename, suffix) = splitFilename input_fn
1158                              (o_file,_) <- 
1159                                  pipeLoop pipe (output_fn, getFileSuffix output_fn)
1160                                                False False 
1161                                                basename suffix
1162                              o_time <- getModificationTime o_file
1163                              return ([DotO o_file], o_time)
1164
1165            let linkable = LM unlinked_time (modSummaryName summary)
1166                              (hs_unlinked ++ stub_unlinked)
1167
1168            return (CompOK pcs details iface (Just linkable))
1169
1170
1171 -----------------------------------------------------------------------------
1172 -- stub .h and .c files (for foreign export support)
1173
1174 compileStub dflags stub_c_exists
1175   | not stub_c_exists = return Nothing
1176   | stub_c_exists = do
1177         -- compile the _stub.c file w/ gcc
1178         let stub_c = hscStubCOutName dflags
1179         pipeline   <- genPipeline (StopBefore Ln) "" True defaultHscLang (stub_c,"c")
1180         (stub_o,_) <- runPipeline pipeline (stub_c,"c") False{-no linking-} 
1181                                   False{-no -o option-}
1182         return (Just stub_o)