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