55082a7d9a5a7dbf4c22f74bb57a8dbfc2cda509
[ghc-hetmet.git] / ghc / compiler / main / DriverPipeline.hs
1 -----------------------------------------------------------------------------
2 -- $Id: DriverPipeline.hs,v 1.41 2000/12/12 14:35:08 simonmar Exp $
3 --
4 -- GHC Driver
5 --
6 -- (c) Simon Marlow 2000
7 --
8 -----------------------------------------------------------------------------
9
10 module DriverPipeline (
11
12         -- interfaces for the batch-mode driver
13    GhcMode(..), getGhcMode, v_GhcMode,
14    genPipeline, runPipeline,
15
16         -- interfaces for the compilation manager (interpreted/batch-mode)
17    preprocess, compile, CompResult(..),
18
19         -- batch-mode linking interface
20    doLink
21   ) where
22
23 #include "HsVersions.h"
24
25 import CmStaticInfo ( GhciMode(..) )
26 import CmTypes
27 import GetImports
28 import DriverState
29 import DriverUtil
30 import DriverMkDepend
31 import DriverPhases
32 import DriverFlags
33 import HscMain
34 import TmpFiles
35 import HscTypes
36 import Outputable
37 import Module
38 import ErrUtils
39 import CmdLineOpts
40 import Config
41 import Panic
42 import Util
43
44 import Time             ( getClockTime )
45 import Directory
46 import System
47 import IOExts
48 import Exception
49
50 import IO
51 import Monad
52 import Maybe
53
54 -----------------------------------------------------------------------------
55 -- GHC modes of operation
56
57 data GhcMode
58   = DoMkDependHS                        -- ghc -M
59   | DoMkDLL                             -- ghc -mk-dll
60   | StopBefore Phase                    -- ghc -E | -C | -S | -c
61   | DoMake                              -- ghc --make
62   | DoInteractive                       -- ghc --interactive
63   | DoLink                              -- [ the default ]
64   deriving (Eq)
65
66 GLOBAL_VAR(v_GhcMode, error "todo", GhcMode)
67
68 modeFlag :: String -> Maybe GhcMode
69 modeFlag "-M"            = Just $ DoMkDependHS
70 modeFlag "-E"            = Just $ StopBefore Hsc
71 modeFlag "-C"            = Just $ StopBefore HCc
72 modeFlag "-S"            = Just $ StopBefore As
73 modeFlag "-c"            = Just $ StopBefore Ln
74 modeFlag "--make"        = Just $ DoMake
75 modeFlag "--interactive" = Just $ DoInteractive
76 modeFlag _               = Nothing
77
78 getGhcMode :: [String]
79          -> IO ( [String]   -- rest of command line
80                , GhcMode
81                , String     -- "GhcMode" flag
82                )
83 getGhcMode flags 
84   = case my_partition modeFlag flags of
85         ([]   , rest) -> return (rest, DoLink,  "") -- default is to do linking
86         ([(flag,one)], rest) -> return (rest, one, flag)
87         (_    , _   ) -> 
88           throwDyn (OtherError 
89                 "only one of the flags -M, -E, -C, -S, -c, --make, --interactive is allowed")
90
91 -----------------------------------------------------------------------------
92 -- genPipeline
93 --
94 -- Herein is all the magic about which phases to run in which order, whether
95 -- the intermediate files should be in /tmp or in the current directory,
96 -- what the suffix of the intermediate files should be, etc.
97
98 -- The following compilation pipeline algorithm is fairly hacky.  A
99 -- better way to do this would be to express the whole compilation as a
100 -- data flow DAG, where the nodes are the intermediate files and the
101 -- edges are the compilation phases.  This framework would also work
102 -- nicely if a haskell dependency generator was included in the
103 -- driver.
104
105 -- It would also deal much more cleanly with compilation phases that
106 -- generate multiple intermediates, (eg. hsc generates .hc, .hi, and
107 -- possibly stub files), where some of the output files need to be
108 -- processed further (eg. the stub files need to be compiled by the C
109 -- compiler).
110
111 -- A cool thing to do would then be to execute the data flow graph
112 -- concurrently, automatically taking advantage of extra processors on
113 -- the host machine.  For example, when compiling two Haskell files
114 -- where one depends on the other, the data flow graph would determine
115 -- that the C compiler from the first compilation can be overlapped
116 -- with the hsc compilation for the second file.
117
118 data IntermediateFileType
119   = Temporary
120   | Persistent
121   deriving (Eq, Show)
122
123 genPipeline
124    :: GhcMode           -- when to stop
125    -> String            -- "stop after" flag (for error messages)
126    -> Bool              -- True => output is persistent
127    -> HscLang           -- preferred output language for hsc
128    -> String            -- original filename
129    -> IO [              -- list of phases to run for this file
130              (Phase,
131               IntermediateFileType,  -- keep the output from this phase?
132               String)                -- output file suffix
133          ]      
134
135 genPipeline todo stop_flag persistent_output lang filename 
136  = do
137    split      <- readIORef v_Split_object_files
138    mangle     <- readIORef v_Do_asm_mangling
139    keep_hc    <- readIORef v_Keep_hc_files
140    keep_raw_s <- readIORef v_Keep_raw_s_files
141    keep_s     <- readIORef v_Keep_s_files
142    osuf       <- readIORef v_Object_suf
143
144    let
145    ----------- -----  ----   ---   --   --  -  -  -
146     (_basename, suffix) = splitFilename filename
147
148     start_phase = startPhase suffix
149
150     haskellish = haskellish_suffix suffix
151     cish = cish_suffix suffix
152
153    -- for a .hc file we need to force lang to HscC
154     real_lang | start_phase == HCc  = HscC
155               | otherwise           = lang
156
157    let
158    ----------- -----  ----   ---   --   --  -  -  -
159     pipeline
160       | todo == DoMkDependHS = [ Unlit, Cpp, MkDependHS ]
161
162       | haskellish = 
163        case real_lang of
164         HscC    | split && mangle -> [ Unlit, Cpp, Hsc, HCc, Mangle, 
165                                         SplitMangle, SplitAs ]
166                 | mangle          -> [ Unlit, Cpp, Hsc, HCc, Mangle, As ]
167                 | split           -> not_valid
168                 | otherwise       -> [ Unlit, Cpp, Hsc, HCc, As ]
169
170         HscAsm  | split           -> [ Unlit, Cpp, Hsc, SplitMangle, SplitAs ]
171                 | otherwise       -> [ Unlit, Cpp, Hsc, As ]
172
173         HscJava | split           -> not_valid
174                 | otherwise       -> error "not implemented: compiling via Java"
175
176       | cish      = [ Cc, As ]
177
178       | otherwise = [ ]  -- just pass this file through to the linker
179
180         -- ToDo: this is somewhat cryptic
181     not_valid = throwDyn (OtherError ("invalid option combination"))
182    ----------- -----  ----   ---   --   --  -  -  -
183
184         -- this shouldn't happen.
185    if start_phase /= Ln && start_phase `notElem` pipeline
186         then throwDyn (OtherError ("can't find starting phase for "
187                                     ++ filename))
188         else do
189
190         -- if we can't find the phase we're supposed to stop before,
191         -- something has gone wrong.
192    case todo of
193         StopBefore phase -> 
194            when (phase /= Ln 
195                  && phase `notElem` pipeline
196                  && not (phase == As && SplitAs `elem` pipeline)) $
197               throwDyn (OtherError 
198                 ("flag " ++ stop_flag
199                  ++ " is incompatible with source file `" ++ filename ++ "'"))
200         _ -> return ()
201
202    let
203    ----------- -----  ----   ---   --   --  -  -  -
204       myPhaseInputExt Ln = case osuf of Nothing -> phaseInputExt Ln
205                                         Just s  -> s
206       myPhaseInputExt other = phaseInputExt other
207
208       annotatePipeline
209          :: [Phase]             -- raw pipeline
210          -> Phase               -- phase to stop before
211          -> [(Phase, IntermediateFileType, String{-file extension-})]
212       annotatePipeline []     _    = []
213       annotatePipeline (Ln:_) _    = []
214       annotatePipeline (phase:next_phase:ps) stop = 
215           (phase, keep_this_output, myPhaseInputExt next_phase)
216              : annotatePipeline (next_phase:ps) stop
217           where
218                 keep_this_output
219                      | next_phase == stop 
220                      = if persistent_output then Persistent else Temporary
221                      | otherwise
222                      = case next_phase of
223                              Ln -> Persistent
224                              Mangle | keep_raw_s -> Persistent
225                              As     | keep_s     -> Persistent
226                              HCc    | keep_hc    -> Persistent
227                              _other              -> Temporary
228
229         -- add information about output files to the pipeline
230         -- the suffix on an output file is determined by the next phase
231         -- in the pipeline, so we add linking to the end of the pipeline
232         -- to force the output from the final phase to be a .o file.
233       stop_phase = case todo of StopBefore phase -> phase
234                                 DoMkDependHS     -> Ln
235                                 DoLink           -> Ln
236       annotated_pipeline = annotatePipeline (pipeline ++ [ Ln ]) stop_phase
237
238       phase_ne p (p1,_,_) = (p1 /= p)
239    ----------- -----  ----   ---   --   --  -  -  -
240
241    return $
242      dropWhile (phase_ne start_phase) . 
243         foldr (\p ps -> if phase_ne stop_phase p then p:ps else [])  []
244                 $ annotated_pipeline
245
246
247 runPipeline
248   :: [ (Phase, IntermediateFileType, String) ] -- phases to run
249   -> String                     -- input file
250   -> Bool                       -- doing linking afterward?
251   -> Bool                       -- take into account -o when generating output?
252   -> IO String                  -- return final filename
253
254 runPipeline pipeline input_fn do_linking use_ofile
255   = pipeLoop pipeline input_fn do_linking use_ofile basename suffix
256   where (basename, suffix) = splitFilename input_fn
257
258 pipeLoop [] input_fn _ _ _ _ = return input_fn
259 pipeLoop ((phase, keep, o_suffix):phases) 
260         input_fn do_linking use_ofile orig_basename orig_suffix
261   = do
262
263      output_fn <- outputFileName (null phases) keep o_suffix
264
265      carry_on <- run_phase phase orig_basename orig_suffix input_fn output_fn
266         -- sometimes we bail out early, eg. when the compiler's recompilation
267         -- checker has determined that recompilation isn't necessary.
268      if not carry_on 
269         then do let (_,keep,final_suffix) = last phases
270                 ofile <- outputFileName True keep final_suffix
271                 return ofile
272         else do -- carry on ...
273
274      pipeLoop phases output_fn do_linking use_ofile orig_basename orig_suffix
275
276   where
277      outputFileName last_phase keep suffix
278         = do o_file <- readIORef v_Output_file
279              if last_phase && not do_linking && use_ofile && isJust o_file
280                then case o_file of 
281                        Just s  -> return s
282                        Nothing -> error "outputFileName"
283                else if keep == Persistent
284                            then odir_ify (orig_basename ++ '.':suffix)
285                            else newTempName suffix
286
287 -------------------------------------------------------------------------------
288 -- Unlit phase 
289
290 run_phase Unlit _basename _suff input_fn output_fn
291   = do unlit <- readIORef v_Pgm_L
292        unlit_flags <- getOpts opt_L
293        runSomething "Literate pre-processor"
294           ("echo '# 1 \"" ++input_fn++"\"' > "++output_fn++" && "
295            ++ unlit ++ ' ':input_fn ++ " - >> " ++ output_fn)
296        return True
297
298 -------------------------------------------------------------------------------
299 -- Cpp phase 
300
301 run_phase Cpp basename suff input_fn output_fn
302   = do src_opts <- getOptionsFromSource input_fn
303        unhandled_flags <- processArgs dynamic_flags src_opts []
304
305        when (not (null unhandled_flags)) 
306             (throwDyn (OtherError (
307                           basename ++ "." ++ suff 
308                           ++ ": static flags are not allowed in {-# OPTIONS #-} pragmas:\n\t" 
309                           ++ unwords unhandled_flags)) (ExitFailure 1))
310
311        do_cpp <- readState cpp_flag
312        if do_cpp
313           then do
314             cpp <- readIORef v_Pgm_P
315             hscpp_opts <- getOpts opt_P
316             hs_src_cpp_opts <- readIORef v_Hs_source_cpp_opts
317
318             cmdline_include_paths <- readIORef v_Include_paths
319             pkg_include_dirs <- getPackageIncludePath
320             let include_paths = map (\p -> "-I"++p) (cmdline_include_paths
321                                                         ++ pkg_include_dirs)
322
323             verb <- getVerbFlag
324
325             runSomething "C pre-processor" 
326                 (unwords
327                    (["echo '{-# LINE 1 \"" ++ input_fn ++ "\" -}'", ">", output_fn, "&&",
328                      cpp, verb] 
329                     ++ include_paths
330                     ++ hs_src_cpp_opts
331                     ++ hscpp_opts
332                     ++ [ "-x", "c", input_fn, ">>", output_fn ]
333                    ))
334           else do
335             runSomething "Ineffective C pre-processor"
336                    ("echo '{-# LINE 1 \""  ++ input_fn ++ "\" -}' > " 
337                     ++ output_fn ++ " && cat " ++ input_fn
338                     ++ " >> " ++ output_fn)
339        return True
340
341 -----------------------------------------------------------------------------
342 -- MkDependHS phase
343
344 run_phase MkDependHS basename suff input_fn _output_fn = do 
345    src <- readFile input_fn
346    let (import_sources, import_normals, module_name) = getImports src
347
348    deps_sources <- mapM (findDependency True basename)  import_sources
349    deps_normals <- mapM (findDependency False basename) import_normals
350    let deps = deps_sources ++ deps_normals
351
352    osuf_opt <- readIORef v_Object_suf
353    let osuf = case osuf_opt of
354                         Nothing -> phaseInputExt Ln
355                         Just s  -> s
356
357    extra_suffixes <- readIORef v_Dep_suffixes
358    let suffixes = osuf : map (++ ('_':osuf)) extra_suffixes
359        ofiles = map (\suf -> basename ++ '.':suf) suffixes
360            
361    objs <- mapM odir_ify ofiles
362    
363    hdl <- readIORef v_Dep_tmp_hdl
364
365         -- std dependency of the object(s) on the source file
366    hPutStrLn hdl (unwords objs ++ " : " ++ basename ++ '.':suff)
367
368    let genDep (dep, False {- not an hi file -}) = 
369           hPutStrLn hdl (unwords objs ++ " : " ++ dep)
370        genDep (dep, True  {- is an hi file -}) = do
371           hisuf <- readIORef v_Hi_suf
372           let dep_base = remove_suffix '.' dep
373               deps = (dep_base ++ hisuf)
374                      : map (\suf -> dep_base ++ suf ++ '_':hisuf) extra_suffixes
375                   -- length objs should be == length deps
376           sequence_ (zipWith (\o d -> hPutStrLn hdl (o ++ " : " ++ d)) objs deps)
377
378    mapM genDep [ d | Just d <- deps ]
379
380    return True
381
382 -- add the lines to dep_makefile:
383            -- always:
384                    -- this.o : this.hs
385
386            -- if the dependency is on something other than a .hi file:
387                    -- this.o this.p_o ... : dep
388            -- otherwise
389                    -- if the import is {-# SOURCE #-}
390                            -- this.o this.p_o ... : dep.hi-boot[-$vers]
391                            
392                    -- else
393                            -- this.o ...   : dep.hi
394                            -- this.p_o ... : dep.p_hi
395                            -- ...
396    
397            -- (where .o is $osuf, and the other suffixes come from
398            -- the cmdline -s options).
399    
400 -----------------------------------------------------------------------------
401 -- Hsc phase
402
403 -- Compilation of a single module, in "legacy" mode (_not_ under
404 -- the direction of the compilation manager).
405 run_phase Hsc basename suff input_fn output_fn
406   = do
407         
408   -- we add the current directory (i.e. the directory in which
409   -- the .hs files resides) to the import path, since this is
410   -- what gcc does, and it's probably what you want.
411         let current_dir = getdir basename
412         
413         paths <- readIORef v_Include_paths
414         writeIORef v_Include_paths (current_dir : paths)
415         
416   -- figure out where to put the .hi file
417         ohi    <- readIORef v_Output_hi
418         hisuf  <- readIORef v_Hi_suf
419         let hifile = case ohi of
420                            Nothing -> basename ++ '.':hisuf
421                            Just fn -> fn
422
423   -- figure out if the source has changed, for recompilation avoidance.
424   -- only do this if we're eventually going to generate a .o file.
425   -- (ToDo: do when generating .hc files too?)
426   --
427   -- Setting source_unchanged to True means that M.o seems
428   -- to be up to date wrt M.hs; so no need to recompile unless imports have
429   -- changed (which the compiler itself figures out).
430   -- Setting source_unchanged to False tells the compiler that M.o is out of
431   -- date wrt M.hs (or M.o doesn't exist) so we must recompile regardless.
432         do_recomp <- readIORef v_Recomp
433         todo <- readIORef v_GhcMode
434         o_file' <- odir_ify (basename ++ '.':phaseInputExt Ln)
435         o_file <- osuf_ify o_file'
436         source_unchanged <- 
437           if not (do_recomp && ( todo == DoLink || todo == StopBefore Ln ))
438              then return False
439              else do t1 <- getModificationTime (basename ++ '.':suff)
440                      o_file_exists <- doesFileExist o_file
441                      if not o_file_exists
442                         then return False       -- Need to recompile
443                         else do t2 <- getModificationTime o_file
444                                 if t2 > t1
445                                   then return True
446                                   else return False
447
448    -- build a ModuleLocation to pass to hscMain.
449         let location = ModuleLocation {
450                           ml_hs_file   = Nothing,
451                           ml_hspp_file = Just input_fn,
452                           ml_hi_file   = Just hifile,
453                           ml_obj_file  = Just o_file
454                        }
455
456   -- get the DynFlags
457         dyn_flags <- readIORef v_DynFlags
458
459   -- run the compiler!
460         pcs <- initPersistentCompilerState
461         result <- hscMain OneShot
462                           dyn_flags{ hscOutName = output_fn }
463                           source_unchanged
464                           location
465                           Nothing        -- no iface
466                           emptyModuleEnv -- HomeSymbolTable
467                           emptyModuleEnv -- HomeIfaceTable
468                           pcs
469
470         case result of {
471
472             HscFail pcs -> throwDyn (PhaseFailed "hsc" (ExitFailure 1));
473
474             HscNoRecomp pcs details iface -> 
475                 do {
476                   runSomething "Touching object file" ("touch " ++ o_file);
477                   return False;
478                 };
479
480             HscRecomp pcs details iface maybe_stub_h maybe_stub_c 
481                       _maybe_interpreted_code -> do
482
483             -- deal with stubs
484         maybe_stub_o <- dealWithStubs basename maybe_stub_h maybe_stub_c
485         case maybe_stub_o of
486                 Nothing -> return ()
487                 Just stub_o -> add v_Ld_inputs stub_o
488
489         return True
490     }
491
492 -----------------------------------------------------------------------------
493 -- Cc phase
494
495 -- we don't support preprocessing .c files (with -E) now.  Doing so introduces
496 -- way too many hacks, and I can't say I've ever used it anyway.
497
498 run_phase cc_phase _basename _suff input_fn output_fn
499    | cc_phase == Cc || cc_phase == HCc
500    = do cc <- readIORef v_Pgm_c
501         cc_opts <- (getOpts opt_c)
502         cmdline_include_dirs <- readIORef v_Include_paths
503
504         let hcc = cc_phase == HCc
505
506                 -- add package include paths even if we're just compiling
507                 -- .c files; this is the Value Add(TM) that using
508                 -- ghc instead of gcc gives you :)
509         pkg_include_dirs <- getPackageIncludePath
510         let include_paths = map (\p -> "-I"++p) (cmdline_include_dirs 
511                                                         ++ pkg_include_dirs)
512
513         c_includes <- getPackageCIncludes
514         cmdline_includes <- readState cmdline_hc_includes -- -#include options
515
516         let cc_injects | hcc = unlines (map mk_include 
517                                         (c_includes ++ reverse cmdline_includes))
518                        | otherwise = ""
519             mk_include h_file = 
520                 case h_file of 
521                    '"':_{-"-} -> "#include "++h_file
522                    '<':_      -> "#include "++h_file
523                    _          -> "#include \""++h_file++"\""
524
525         cc_help <- newTempName "c"
526         h <- openFile cc_help WriteMode
527         hPutStr h cc_injects
528         hPutStrLn h ("#include \"" ++ input_fn ++ "\"\n")
529         hClose h
530
531         ccout <- newTempName "ccout"
532
533         mangle <- readIORef v_Do_asm_mangling
534         (md_c_flags, md_regd_c_flags) <- machdepCCOpts
535
536         verb <- getVerbFlag
537
538         o2 <- readIORef v_minus_o2_for_C
539         let opt_flag | o2        = "-O2"
540                      | otherwise = "-O"
541
542         pkg_extra_cc_opts <- getPackageExtraCcOpts
543
544         split_objs <- readIORef v_Split_object_files
545         let split_opt | hcc && split_objs = [ "-DUSE_SPLIT_MARKERS" ]
546                       | otherwise         = [ ]
547
548         excessPrecision <- readIORef v_Excess_precision
549
550         runSomething "C Compiler"
551          (unwords ([ cc, "-x", "c", cc_help, "-o", output_fn ]
552                    ++ md_c_flags
553                    ++ (if cc_phase == HCc && mangle
554                          then md_regd_c_flags
555                          else [])
556                    ++ [ verb, "-S", "-Wimplicit", opt_flag ]
557                    ++ [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ]
558                    ++ cc_opts
559                    ++ split_opt
560                    ++ (if excessPrecision then [] else [ "-ffloat-store" ])
561                    ++ include_paths
562                    ++ pkg_extra_cc_opts
563 --                 ++ [">", ccout]
564                    ))
565         return True
566
567         -- ToDo: postprocess the output from gcc
568
569 -----------------------------------------------------------------------------
570 -- Mangle phase
571
572 run_phase Mangle _basename _suff input_fn output_fn
573   = do mangler <- readIORef v_Pgm_m
574        mangler_opts <- getOpts opt_m
575        machdep_opts <-
576          if (prefixMatch "i386" cTARGETPLATFORM)
577             then do n_regs <- readState stolen_x86_regs
578                     return [ show n_regs ]
579             else return []
580        runSomething "Assembly Mangler"
581         (unwords (mangler : 
582                      mangler_opts
583                   ++ [ input_fn, output_fn ]
584                   ++ machdep_opts
585                 ))
586        return True
587
588 -----------------------------------------------------------------------------
589 -- Splitting phase
590
591 run_phase SplitMangle _basename _suff input_fn _output_fn
592   = do  splitter <- readIORef v_Pgm_s
593
594         -- this is the prefix used for the split .s files
595         tmp_pfx <- readIORef v_TmpDir
596         x <- myGetProcessID
597         let split_s_prefix = tmp_pfx ++ "/ghc" ++ show x
598         writeIORef v_Split_prefix split_s_prefix
599         addFilesToClean [split_s_prefix ++ "__*"] -- d:-)
600
601         -- allocate a tmp file to put the no. of split .s files in (sigh)
602         n_files <- newTempName "n_files"
603
604         runSomething "Split Assembly File"
605          (unwords [ splitter
606                   , input_fn
607                   , split_s_prefix
608                   , n_files ]
609          )
610
611         -- save the number of split files for future references
612         s <- readFile n_files
613         let n = read s :: Int
614         writeIORef v_N_split_files n
615         return True
616
617 -----------------------------------------------------------------------------
618 -- As phase
619
620 run_phase As _basename _suff input_fn output_fn
621   = do  as <- readIORef v_Pgm_a
622         as_opts <- getOpts opt_a
623
624         cmdline_include_paths <- readIORef v_Include_paths
625         let cmdline_include_flags = map (\p -> "-I"++p) cmdline_include_paths
626         runSomething "Assembler"
627            (unwords (as : as_opts
628                        ++ cmdline_include_flags
629                        ++ [ "-c", input_fn, "-o",  output_fn ]
630                     ))
631         return True
632
633 run_phase SplitAs basename _suff _input_fn _output_fn
634   = do  as <- readIORef v_Pgm_a
635         as_opts <- getOpts opt_a
636
637         split_s_prefix <- readIORef v_Split_prefix
638         n <- readIORef v_N_split_files
639
640         odir <- readIORef v_Output_dir
641         let real_odir = case odir of
642                                 Nothing -> basename
643                                 Just d  -> d
644
645         let assemble_file n = do
646                     let input_s  = split_s_prefix ++ "__" ++ show n ++ ".s"
647                     let output_o = newdir real_odir 
648                                         (basename ++ "__" ++ show n ++ ".o")
649                     real_o <- osuf_ify output_o
650                     runSomething "Assembler" 
651                             (unwords (as : as_opts
652                                       ++ [ "-c", "-o", real_o, input_s ]
653                             ))
654         
655         mapM_ assemble_file [1..n]
656         return True
657
658 -----------------------------------------------------------------------------
659 -- Linking
660
661 doLink :: [String] -> IO ()
662 doLink o_files = do
663     ln <- readIORef v_Pgm_l
664     verb <- getVerbFlag
665     static <- readIORef v_Static
666     let imp = if static then "" else "_imp"
667     no_hs_main <- readIORef v_NoHsMain
668
669     o_file <- readIORef v_Output_file
670     let output_fn = case o_file of { Just s -> s; Nothing -> "a.out"; }
671
672     pkg_lib_paths <- getPackageLibraryPath
673     let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths
674
675     lib_paths <- readIORef v_Library_paths
676     let lib_path_opts = map ("-L"++) lib_paths
677
678     pkg_libs <- getPackageLibraries
679     let pkg_lib_opts = map (\lib -> "-l" ++ lib ++ imp) pkg_libs
680
681     libs <- readIORef v_Cmdline_libraries
682     let lib_opts = map ("-l"++) (reverse libs)
683          -- reverse because they're added in reverse order from the cmd line
684
685     pkg_extra_ld_opts <- getPackageExtraLdOpts
686
687         -- probably _stub.o files
688     extra_ld_inputs <- readIORef v_Ld_inputs
689
690         -- opts from -optl-<blah>
691     extra_ld_opts <- getStaticOpts v_Opt_l
692
693     rts_pkg <- getPackageDetails ["rts"]
694     std_pkg <- getPackageDetails ["std"]
695 #ifdef mingw32_TARGET_OS
696     let extra_os = if static || no_hs_main
697                    then []
698 --                   else [ head (lib_paths (head rts_pkg)) ++ "/Main.dll_o",
699 --                          head (lib_paths (head std_pkg)) ++ "/PrelMain.dll_o" ]
700                      else []
701 #endif
702     (md_c_flags, _) <- machdepCCOpts
703     runSomething "Linker"
704        (unwords
705          ([ ln, verb, "-o", output_fn ]
706          ++ md_c_flags
707          ++ o_files
708 #ifdef mingw32_TARGET_OS
709          ++ extra_os
710 #endif
711          ++ extra_ld_inputs
712          ++ lib_path_opts
713          ++ lib_opts
714          ++ pkg_lib_path_opts
715          ++ pkg_lib_opts
716          ++ pkg_extra_ld_opts
717          ++ extra_ld_opts
718 #ifdef mingw32_TARGET_OS
719          ++ if static then [ "-u _PrelMain_mainIO_closure" , "-u ___init_PrelMain"] else []
720 #else
721          ++ [ "-u PrelMain_mainIO_closure" , "-u __init_PrelMain"]
722 #endif
723         )
724        )
725
726 -----------------------------------------------------------------------------
727 -- Just preprocess a file, put the result in a temp. file (used by the
728 -- compilation manager during the summary phase).
729
730 preprocess :: FilePath -> IO FilePath
731 preprocess filename =
732   ASSERT(haskellish_file filename) 
733   do init_driver_state <- readIORef v_InitDriverState
734      writeIORef v_Driver_state init_driver_state
735
736      pipeline <- genPipeline (StopBefore Hsc) ("preprocess") False 
737                         defaultHscLang filename
738      runPipeline pipeline filename False{-no linking-} False{-no -o flag-}
739
740
741 -----------------------------------------------------------------------------
742 -- Compile a single module, under the control of the compilation manager.
743 --
744 -- This is the interface between the compilation manager and the
745 -- compiler proper (hsc), where we deal with tedious details like
746 -- reading the OPTIONS pragma from the source file, and passing the
747 -- output of hsc through the C compiler.
748
749 -- The driver sits between 'compile' and 'hscMain', translating calls
750 -- to the former into calls to the latter, and results from the latter
751 -- into results from the former.  It does things like preprocessing
752 -- the .hs file if necessary, and compiling up the .stub_c files to
753 -- generate Linkables.
754
755 -- NB.  No old interface can also mean that the source has changed.
756
757 compile :: GhciMode                -- distinguish batch from interactive
758         -> ModSummary              -- summary, including source
759         -> Bool                    -- source unchanged?
760         -> Maybe ModIface          -- old interface, if available
761         -> HomeSymbolTable         -- for home module ModDetails
762         -> HomeIfaceTable          -- for home module Ifaces
763         -> PersistentCompilerState -- persistent compiler state
764         -> IO CompResult
765
766 data CompResult
767    = CompOK   PersistentCompilerState   -- updated PCS
768               ModDetails  -- new details (HST additions)
769               ModIface    -- new iface   (HIT additions)
770               (Maybe Linkable)
771                        -- new code; Nothing => compilation was not reqd
772                        -- (old code is still valid)
773
774    | CompErrs PersistentCompilerState   -- updated PCS
775
776
777 compile ghci_mode summary source_unchanged old_iface hst hit pcs = do 
778    init_dyn_flags <- readIORef v_InitDynFlags
779    writeIORef v_DynFlags init_dyn_flags
780    init_driver_state <- readIORef v_InitDriverState
781    writeIORef v_Driver_state init_driver_state
782
783    showPass init_dyn_flags 
784         (showSDoc (text "Compiling" <+> ppr (name_of_summary summary)))
785
786    let verb = verbosity init_dyn_flags
787    let location   = ms_location summary
788    let input_fn   = unJust "compile:hs" (ml_hs_file location) 
789    let input_fnpp = unJust "compile:hspp" (ml_hspp_file location)
790
791    when (verb >= 2) (hPutStrLn stderr ("compile: input file " ++ input_fnpp))
792
793    opts <- getOptionsFromSource input_fnpp
794    processArgs dynamic_flags opts []
795    dyn_flags <- readIORef v_DynFlags
796
797    let hsc_lang = hscLang dyn_flags
798    output_fn <- case hsc_lang of
799                     HscAsm         -> newTempName (phaseInputExt As)
800                     HscC           -> newTempName (phaseInputExt HCc)
801                     HscJava        -> newTempName "java" -- ToDo
802                     HscInterpreted -> return (error "no output file")
803
804    -- run the compiler
805    hsc_result <- hscMain ghci_mode dyn_flags{ hscOutName = output_fn } 
806                          source_unchanged
807                          location old_iface hst hit pcs
808
809    case hsc_result of
810       HscFail pcs -> return (CompErrs pcs)
811
812       HscNoRecomp pcs details iface -> return (CompOK pcs details iface Nothing)
813
814       HscRecomp pcs details iface
815         maybe_stub_h maybe_stub_c maybe_interpreted_code -> do
816            
817            let (basename, _) = splitFilename input_fn
818            maybe_stub_o <- dealWithStubs basename maybe_stub_h maybe_stub_c
819            let stub_unlinked = case maybe_stub_o of
820                                   Nothing -> []
821                                   Just stub_o -> [ DotO stub_o ]
822
823            (hs_unlinked, unlinked_time) <-
824              case hsc_lang of
825
826                 -- in interpreted mode, just return the compiled code
827                 -- as our "unlinked" object.
828                 HscInterpreted -> 
829                     case maybe_interpreted_code of
830                        Just (code,itbl_env) -> do tm <- getClockTime 
831                                                   return ([Trees code itbl_env], tm)
832                        Nothing -> panic "compile: no interpreted code"
833
834                 -- we're in batch mode: finish the compilation pipeline.
835                 _other -> do pipe <- genPipeline (StopBefore Ln) "" True 
836                                         hsc_lang output_fn
837                              -- runPipeline takes input_fn so it can split off 
838                              -- the base name and use it as the base of 
839                              -- the output object file.
840                              let (basename, suffix) = splitFilename input_fn
841                              o_file <- pipeLoop pipe output_fn False False 
842                                                 basename suffix
843                              o_time <- getModificationTime o_file
844                              return ([DotO o_file], o_time)
845
846            let linkable = LM unlinked_time (moduleName (ms_mod summary)) 
847                              (hs_unlinked ++ stub_unlinked)
848
849            return (CompOK pcs details iface (Just linkable))
850
851
852 -----------------------------------------------------------------------------
853 -- stub .h and .c files (for foreign export support)
854
855 dealWithStubs basename maybe_stub_h maybe_stub_c
856
857  = do   let stub_h = basename ++ "_stub.h"
858         let stub_c = basename ++ "_stub.c"
859
860   -- copy the .stub_h file into the current dir if necessary
861         case maybe_stub_h of
862            Nothing -> return ()
863            Just tmp_stub_h -> do
864                 runSomething "Copy stub .h file"
865                                 ("cp " ++ tmp_stub_h ++ ' ':stub_h)
866         
867                         -- #include <..._stub.h> in .hc file
868                 addCmdlineHCInclude tmp_stub_h  -- hack
869
870   -- copy the .stub_c file into the current dir, and compile it, if necessary
871         case maybe_stub_c of
872            Nothing -> return Nothing
873            Just tmp_stub_c -> do  -- copy the _stub.c file into the current dir
874                 runSomething "Copy stub .c file" 
875                     (unwords [ 
876                         "rm -f", stub_c, "&&",
877                         "echo \'#include \"Stg.h\"\n#include \""++stub_h++"\"\' >"++stub_c, " &&",
878                         "cat", tmp_stub_c, ">> ", stub_c
879                         ])
880
881                         -- compile the _stub.c file w/ gcc
882                 pipeline <- genPipeline (StopBefore Ln) "" True 
883                                 defaultHscLang stub_c
884                 stub_o <- runPipeline pipeline stub_c False{-no linking-} 
885                                 False{-no -o option-}
886
887                 return (Just stub_o)