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