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