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