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