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