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