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