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