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