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