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