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