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