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