[project @ 2005-01-18 12:18:11 by simonpj]
[ghc-hetmet.git] / ghc / compiler / main / DriverPipeline.hs
1 -----------------------------------------------------------------------------
2 --
3 -- GHC Driver
4 --
5 -- (c) The University of Glasgow 2002
6 --
7 -----------------------------------------------------------------------------
8
9 #include "../includes/ghcconfig.h"
10
11 module DriverPipeline (
12
13         -- Interfaces for the batch-mode driver
14    runPipeline, staticLink,
15
16         -- Interfaces for the compilation manager (interpreted/batch-mode)
17    preprocess, 
18    compile, CompResult(..), 
19    link, 
20
21         -- DLL building
22    doMkDLL
23   ) where
24
25 #include "HsVersions.h"
26
27 import Packages
28 import GetImports
29 import DriverState
30 import DriverUtil
31 import DriverMkDepend
32 import DriverPhases
33 import DriverFlags
34 import SysTools         ( newTempName, addFilesToClean, getSysMan, copy )
35 import qualified SysTools       
36 import HscMain
37 import Finder
38 import HscTypes
39 import Outputable
40 import Module
41 import ErrUtils
42 import CmdLineOpts
43 import Config
44 import RdrName          ( GlobalRdrEnv )
45 import Panic
46 import Util
47 import StringBuffer     ( hGetStringBuffer )
48 import BasicTypes       ( SuccessFlag(..) )
49 import Maybes           ( expectJust )
50
51 import ParserCoreUtils ( getCoreModuleName )
52
53 import EXCEPTION
54 import DATA_IOREF       ( readIORef, writeIORef )
55
56 import Time             ( ClockTime )
57 import Directory
58 import System
59 import IO
60 import Monad
61 import Maybe
62
63
64 -- ---------------------------------------------------------------------------
65 -- Pre-process
66
67 -- Just preprocess a file, put the result in a temp. file (used by the
68 -- compilation manager during the summary phase).
69
70 preprocess :: DynFlags -> FilePath -> IO FilePath
71 preprocess dflags filename =
72   ASSERT2(isHaskellSrcFilename filename, text filename) 
73   do runPipeline (StopBefore Hsc) dflags ("preprocess") 
74         False{-temporary output file-}
75         Nothing{-no specific output file-}
76         filename
77         Nothing{-no ModLocation-}
78
79 -- ---------------------------------------------------------------------------
80 -- Compile
81
82 -- Compile a single module, under the control of the compilation manager.
83 --
84 -- This is the interface between the compilation manager and the
85 -- compiler proper (hsc), where we deal with tedious details like
86 -- reading the OPTIONS pragma from the source file, and passing the
87 -- output of hsc through the C compiler.
88
89 -- The driver sits between 'compile' and 'hscMain', translating calls
90 -- to the former into calls to the latter, and results from the latter
91 -- into results from the former.  It does things like preprocessing
92 -- the .hs file if necessary, and compiling up the .stub_c files to
93 -- generate Linkables.
94
95 -- NB.  No old interface can also mean that the source has changed.
96
97 compile :: HscEnv
98         -> Module
99         -> ModLocation
100         -> ClockTime               -- timestamp of original source file
101         -> Bool                    -- True <=> source unchanged
102         -> Bool                    -- True <=> have object
103         -> Maybe ModIface          -- old interface, if available
104         -> IO CompResult
105
106 data CompResult
107    = CompOK   ModDetails                -- New details
108               (Maybe GlobalRdrEnv)      -- Lexical environment for the module
109                                         -- (Maybe because we may have loaded it from
110                                         --  its precompiled interface)
111               ModIface                  -- New iface
112               (Maybe Linkable)  -- New code; Nothing => compilation was not reqd
113                                 --                      (old code is still valid)
114
115    | CompErrs 
116
117
118 compile hsc_env this_mod location src_timestamp
119         source_unchanged have_object 
120         old_iface = do 
121
122    let dyn_flags = hsc_dflags hsc_env
123
124    showPass dyn_flags
125         (showSDoc (text "Compiling" <+> ppr this_mod))
126
127    let verb       = verbosity dyn_flags
128    let input_fn   = expectJust "compile:hs" (ml_hs_file location) 
129    let input_fnpp = expectJust "compile:hspp" (ml_hspp_file location)
130
131    when (verb >= 2) (hPutStrLn stderr ("compile: input file " ++ input_fnpp))
132
133    -- add in the OPTIONS from the source file
134    opts <- getOptionsFromSource input_fnpp
135    (dyn_flags,unhandled_flags) <- processDynamicFlags opts dyn_flags
136    checkProcessArgsResult unhandled_flags input_fn
137
138    let (basename, _) = splitFilename input_fn
139
140   -- We add the directory in which the .hs files resides) to the import path.
141   -- This is needed when we try to compile the .hc file later, if it
142   -- imports a _stub.h file that we created here.
143    let current_dir = directoryOf basename
144    old_paths <- readIORef v_Include_paths
145    writeIORef v_Include_paths (current_dir : old_paths)
146    -- put back the old include paths afterward.
147    later (writeIORef v_Include_paths old_paths) $ do
148
149    -- figure out what lang we're generating
150    hsc_lang <- hscMaybeAdjustLang (hscLang dyn_flags)
151    -- figure out what the next phase should be
152    next_phase <- hscNextPhase hsc_lang
153    -- figure out what file to generate the output into
154    get_output_fn <- genOutputFilenameFunc False Nothing next_phase basename
155    output_fn <- get_output_fn next_phase (Just location)
156
157    let dyn_flags' = dyn_flags { hscLang = hsc_lang,
158                                 hscOutName = output_fn,
159                                 hscStubCOutName = basename ++ "_stub.c",
160                                 hscStubHOutName = basename ++ "_stub.h",
161                                 extCoreName = basename ++ ".hcr" }
162
163    -- -no-recomp should also work with --make
164    do_recomp <- readIORef v_Recomp
165    let source_unchanged' = source_unchanged && do_recomp
166        hsc_env' = hsc_env { hsc_dflags = dyn_flags' }
167
168    -- run the compiler
169    hsc_result <- hscMain hsc_env' printErrorsAndWarnings this_mod location
170                          source_unchanged' have_object old_iface
171
172    case hsc_result of
173       HscFail -> return CompErrs
174
175       HscNoRecomp details iface -> return (CompOK details Nothing iface Nothing)
176
177       HscRecomp details rdr_env iface
178         stub_h_exists stub_c_exists maybe_interpreted_code -> do
179            let 
180            maybe_stub_o <- compileStub dyn_flags' stub_c_exists
181            let stub_unlinked = case maybe_stub_o of
182                                   Nothing -> []
183                                   Just stub_o -> [ DotO stub_o ]
184
185            (hs_unlinked, unlinked_time) <-
186              case hsc_lang of
187
188                 -- in interpreted mode, just return the compiled code
189                 -- as our "unlinked" object.
190                 HscInterpreted -> 
191                     case maybe_interpreted_code of
192 #ifdef GHCI
193                        Just comp_bc -> return ([BCOs comp_bc], src_timestamp)
194                         -- Why do we use the timestamp of the source file here,
195                         -- rather than the current time?  This works better in
196                         -- the case where the local clock is out of sync
197                         -- with the filesystem's clock.  It's just as accurate:
198                         -- if the source is modified, then the linkable will
199                         -- be out of date.
200 #endif
201                        Nothing -> panic "compile: no interpreted code"
202
203                 -- we're in batch mode: finish the compilation pipeline.
204                 _other -> do
205                    let object_filename = ml_obj_file location
206
207                    runPipeline (StopBefore Ln) dyn_flags ""
208                         True Nothing output_fn (Just location)
209                         -- the object filename comes from the ModLocation
210
211                    o_time <- getModificationTime object_filename
212                    return ([DotO object_filename], o_time)
213
214            let linkable = LM unlinked_time this_mod
215                              (hs_unlinked ++ stub_unlinked)
216
217            return (CompOK details rdr_env iface (Just linkable))
218
219 -----------------------------------------------------------------------------
220 -- stub .h and .c files (for foreign export support)
221
222 compileStub dflags stub_c_exists
223   | not stub_c_exists = return Nothing
224   | stub_c_exists = do
225         -- compile the _stub.c file w/ gcc
226         let stub_c = hscStubCOutName dflags
227         stub_o <- runPipeline (StopBefore Ln) dflags "stub-compile"
228                         True{-persistent output-} 
229                         Nothing{-no specific output file-}
230                         stub_c
231                         Nothing{-no ModLocation-}
232         return (Just stub_o)
233
234
235 -- ---------------------------------------------------------------------------
236 -- Link
237
238 link :: GhciMode                -- interactive or batch
239      -> DynFlags                -- dynamic flags
240      -> Bool                    -- attempt linking in batch mode?
241      -> HomePackageTable        -- what to link
242      -> IO SuccessFlag
243
244 -- For the moment, in the batch linker, we don't bother to tell doLink
245 -- which packages to link -- it just tries all that are available.
246 -- batch_attempt_linking should only be *looked at* in batch mode.  It
247 -- should only be True if the upsweep was successful and someone
248 -- exports main, i.e., we have good reason to believe that linking
249 -- will succeed.
250
251 #ifdef GHCI
252 link Interactive dflags batch_attempt_linking hpt
253     = do -- Not Linking...(demand linker will do the job)
254          return Succeeded
255 #endif
256
257 link Batch dflags batch_attempt_linking hpt
258    | batch_attempt_linking
259    = do 
260         let 
261             home_mod_infos = moduleEnvElts hpt
262
263             -- the packages we depend on
264             pkg_deps  = concatMap (dep_pkgs . mi_deps . hm_iface) home_mod_infos
265
266             -- the linkables to link
267             linkables = map hm_linkable home_mod_infos
268
269         when (verb >= 3) $ do
270              hPutStrLn stderr "link: linkables are ..."
271              hPutStrLn stderr (showSDoc (vcat (map ppr linkables)))
272
273         -- check for the -no-link flag
274         omit_linking <- readIORef v_NoLink
275         if omit_linking 
276           then do when (verb >= 3) $
277                     hPutStrLn stderr "link(batch): linking omitted (-no-link flag given)."
278                   return Succeeded
279           else do
280
281         when (verb >= 1) $
282              hPutStrLn stderr "Linking ..."
283
284         let getOfiles (LM _ _ us) = map nameOfObject (filter isObject us)
285             obj_files = concatMap getOfiles linkables
286
287         -- Don't showPass in Batch mode; doLink will do that for us.
288         staticLink dflags obj_files pkg_deps
289
290         when (verb >= 3) (hPutStrLn stderr "link: done")
291
292         -- staticLink only returns if it succeeds
293         return Succeeded
294
295    | otherwise
296    = do when (verb >= 3) $ do
297             hPutStrLn stderr "link(batch): upsweep (partially) failed OR"
298             hPutStrLn stderr "   Main.main not exported; not linking."
299         return Succeeded
300    where
301       verb = verbosity dflags
302       
303 -- ---------------------------------------------------------------------------
304 -- Run a compilation pipeline, consisting of multiple phases.
305
306 -- The DynFlags can be modified by phases in the pipeline (eg. by
307 -- OPTIONS pragmas), and the changes affect later phases in the
308 -- pipeline, but we throw away the resulting DynFlags at the end.
309
310 runPipeline
311   :: GhcMode            -- when to stop
312   -> DynFlags           -- dynamic flags
313   -> String             -- "stop after" flag
314   -> Bool               -- final output is persistent?
315   -> Maybe FilePath     -- where to put the output, optionally
316   -> FilePath           -- input filename
317   -> Maybe ModLocation  -- a ModLocation for this module, if we have one
318   -> IO FilePath        -- output filename
319
320 runPipeline todo dflags stop_flag keep_output 
321   maybe_output_filename input_fn maybe_loc
322   = do
323   split <- readIORef v_Split_object_files
324   let (basename, suffix) = splitFilename input_fn
325       start_phase = startPhase suffix
326
327       stop_phase = case todo of 
328                         StopBefore As | split -> SplitAs
329                         StopBefore phase      -> phase
330                         DoMkDependHS          -> Ln
331                         DoLink                -> Ln
332                         DoMkDLL               -> Ln
333
334   -- We want to catch cases of "you can't get there from here" before
335   -- we start the pipeline, because otherwise it will just run off the
336   -- end.
337   --
338   -- There is a partial ordering on phases, where A < B iff A occurs
339   -- before B in a normal compilation pipeline.
340   --
341   when (not (start_phase `happensBefore` stop_phase)) $
342         throwDyn (UsageError 
343                     ("flag `" ++ stop_flag
344                      ++ "' is incompatible with source file `"
345                      ++ input_fn ++ "'"))
346
347   -- generate a function which will be used to calculate output file names
348   -- as we go along.
349   get_output_fn <- genOutputFilenameFunc keep_output maybe_output_filename
350                         stop_phase basename
351
352   -- and execute the pipeline...
353   (output_fn, maybe_loc) <- 
354         pipeLoop dflags start_phase stop_phase input_fn basename suffix 
355                  get_output_fn maybe_loc
356
357   -- sometimes, a compilation phase doesn't actually generate any output
358   -- (eg. the CPP phase when -fcpp is not turned on).  If we end on this
359   -- stage, but we wanted to keep the output, then we have to explicitly
360   -- copy the file.
361   if keep_output
362         then do final_fn <- get_output_fn stop_phase maybe_loc
363                 when (final_fn /= output_fn) $
364                   copy dflags ("Copying `" ++ output_fn ++ "' to `" ++ final_fn
365                         ++ "'") output_fn final_fn
366                 return final_fn
367         else
368              return output_fn
369
370
371 pipeLoop :: DynFlags -> Phase -> Phase -> FilePath -> String -> Suffix
372   -> (Phase -> Maybe ModLocation -> IO FilePath)
373   -> Maybe ModLocation -> IO (FilePath, Maybe ModLocation)
374
375 pipeLoop dflags phase stop_phase input_fn orig_basename orig_suff 
376         get_output_fn maybe_loc
377
378   | phase == stop_phase  =  return (input_fn, maybe_loc)  -- all done
379
380   | not (phase `happensBefore` stop_phase)  = 
381         -- Something has gone wrong.  We'll try to cover all the cases when
382         -- this could happen, so if we reach here it is a panic.
383         -- eg. it might happen if the -C flag is used on a source file that
384         -- has {-# OPTIONS -fasm #-}.
385         panic ("pipeLoop: at phase " ++ show phase ++ 
386                 " but I wanted to stop at phase " ++ show stop_phase)
387
388   | otherwise = do
389         maybe_next_phase <- runPhase phase dflags orig_basename 
390                                 orig_suff input_fn get_output_fn maybe_loc
391         case maybe_next_phase of
392           (Nothing, dflags, maybe_loc, output_fn) -> do
393                 -- we stopped early, but return the *final* filename
394                 -- (it presumably already exists)
395                 final_fn <- get_output_fn stop_phase maybe_loc
396                 return (final_fn, maybe_loc)
397           (Just next_phase, dflags', maybe_loc, output_fn) ->
398                 pipeLoop dflags' next_phase stop_phase output_fn
399                         orig_basename orig_suff get_output_fn maybe_loc
400
401   
402 genOutputFilenameFunc :: Bool -> Maybe FilePath -> Phase -> String
403   -> IO (Phase{-next phase-} -> Maybe ModLocation -> IO FilePath)
404 genOutputFilenameFunc keep_final_output maybe_output_filename 
405                 stop_phase basename
406  = do
407    hcsuf      <- readIORef v_HC_suf
408    odir       <- readIORef v_Output_dir
409    osuf       <- readIORef v_Object_suf
410    keep_hc    <- readIORef v_Keep_hc_files
411 #ifdef ILX
412    keep_il    <- readIORef v_Keep_il_files
413    keep_ilx   <- readIORef v_Keep_ilx_files
414 #endif
415    keep_raw_s <- readIORef v_Keep_raw_s_files
416    keep_s     <- readIORef v_Keep_s_files
417    let
418         myPhaseInputExt HCc | Just s <- hcsuf = s
419         myPhaseInputExt Ln    = osuf
420         myPhaseInputExt other = phaseInputExt other
421
422         func next_phase maybe_location
423                 | is_last_phase, Just f <- maybe_output_filename = return f
424                 | is_last_phase && keep_final_output = persistent_fn
425                 | keep_this_output                   = persistent_fn
426                 | otherwise                          = newTempName suffix
427
428            where
429                 is_last_phase = next_phase == stop_phase
430
431                 -- sometimes, we keep output from intermediate stages
432                 keep_this_output = 
433                      case next_phase of
434                              Ln                  -> True
435                              Mangle | keep_raw_s -> True
436                              As     | keep_s     -> True
437                              HCc    | keep_hc    -> True
438                              _other              -> False
439
440                 suffix = myPhaseInputExt next_phase
441
442                 -- persistent object files get put in odir
443                 persistent_fn 
444                    | Ln <- next_phase  = return odir_persistent
445                    | otherwise         = return persistent
446
447                 persistent = basename ++ '.':suffix
448
449                 odir_persistent
450                    | Just loc <- maybe_location = ml_obj_file loc
451                    | Just d <- odir = replaceFilenameDirectory persistent d
452                    | otherwise      = persistent
453
454    return func
455
456
457 -- -----------------------------------------------------------------------------
458 -- Each phase in the pipeline returns the next phase to execute, and the
459 -- name of the file in which the output was placed.
460 --
461 -- We must do things dynamically this way, because we often don't know
462 -- what the rest of the phases will be until part-way through the
463 -- compilation: for example, an {-# OPTIONS -fasm #-} at the beginning
464 -- of a source file can change the latter stages of the pipeline from
465 -- taking the via-C route to using the native code generator.
466
467 runPhase :: Phase
468          -> DynFlags
469          -> String      -- basename of original input source
470          -> String      -- its extension
471          -> FilePath    -- name of file which contains the input to this phase.
472          -> (Phase -> Maybe ModLocation -> IO FilePath)
473                         -- how to calculate the output filename
474          -> Maybe ModLocation           -- the ModLocation, if we have one
475          -> IO (Maybe Phase,            -- next phase
476                 DynFlags,               -- new dynamic flags
477                 Maybe ModLocation,      -- the ModLocation, if we have one
478                 FilePath)               -- output filename
479
480 -------------------------------------------------------------------------------
481 -- Unlit phase 
482
483 runPhase Unlit dflags _basename _suff input_fn get_output_fn maybe_loc
484   = do let unlit_flags = getOpts dflags opt_L
485        -- The -h option passes the file name for unlit to put in a #line directive
486        output_fn <- get_output_fn Cpp maybe_loc
487
488        SysTools.runUnlit dflags 
489                 (map SysTools.Option unlit_flags ++
490                           [ SysTools.Option     "-h"
491                           , SysTools.Option     input_fn
492                           , SysTools.FileOption "" input_fn
493                           , SysTools.FileOption "" output_fn
494                           ])
495
496        return (Just Cpp, dflags, maybe_loc, output_fn)
497
498 -------------------------------------------------------------------------------
499 -- Cpp phase 
500
501 runPhase Cpp dflags basename suff input_fn get_output_fn maybe_loc
502   = do src_opts <- getOptionsFromSource input_fn
503        (dflags,unhandled_flags) <- processDynamicFlags src_opts dflags
504        checkProcessArgsResult unhandled_flags (basename++'.':suff)
505
506        if not (cppFlag dflags) then
507            -- no need to preprocess CPP, just pass input file along
508            -- to the next phase of the pipeline.
509           return (Just HsPp, dflags, maybe_loc, input_fn)
510         else do
511             output_fn <- get_output_fn HsPp maybe_loc
512             doCpp dflags True{-raw-} False{-no CC opts-} input_fn output_fn
513             return (Just HsPp, dflags, maybe_loc, output_fn)
514
515 -------------------------------------------------------------------------------
516 -- HsPp phase 
517
518 runPhase HsPp dflags basename suff input_fn get_output_fn maybe_loc
519   = do if not (ppFlag dflags) then
520            -- no need to preprocess, just pass input file along
521            -- to the next phase of the pipeline.
522           return (Just Hsc, dflags, maybe_loc, input_fn)
523         else do
524             let hspp_opts = getOpts dflags opt_F
525             hs_src_pp_opts <- readIORef v_Hs_source_pp_opts
526             let orig_fn = basename ++ '.':suff
527             output_fn <- get_output_fn Hsc maybe_loc
528             SysTools.runPp dflags
529                            ( [ SysTools.Option     orig_fn
530                              , SysTools.Option     input_fn
531                              , SysTools.FileOption "" output_fn
532                              ] ++
533                              map SysTools.Option hs_src_pp_opts ++
534                              map SysTools.Option hspp_opts
535                            )
536             return (Just Hsc, dflags, maybe_loc, output_fn)
537
538 -----------------------------------------------------------------------------
539 -- Hsc phase
540
541 -- Compilation of a single module, in "legacy" mode (_not_ under
542 -- the direction of the compilation manager).
543 runPhase Hsc dflags basename suff input_fn get_output_fn _maybe_loc = do
544   todo <- readIORef v_GhcMode
545   if todo == DoMkDependHS then do
546        locn <- doMkDependHSPhase dflags basename suff input_fn
547        return (Nothing, dflags, Just locn, input_fn)  -- Ln is a dummy stop phase 
548
549    else do
550       -- normal Hsc mode, not mkdependHS
551
552   -- we add the current directory (i.e. the directory in which
553   -- the .hs files resides) to the import path, since this is
554   -- what gcc does, and it's probably what you want.
555         let current_dir = directoryOf basename
556         
557         paths <- readIORef v_Include_paths
558         writeIORef v_Include_paths (current_dir : paths)
559         
560   -- gather the imports and module name
561         (hspp_buf,mod_name) <- 
562             if isExtCoreFilename ('.':suff)
563              then do
564                -- no explicit imports in ExtCore input.
565                m <- getCoreModuleName input_fn
566                return (Nothing, mkModule m)
567              else do
568                buf <- hGetStringBuffer input_fn
569                (_,_,mod_name) <- getImports dflags buf input_fn
570                return (Just buf, mod_name)
571
572   -- build a ModLocation to pass to hscMain.
573         location' <- mkHomeModLocation mod_name (basename ++ '.':suff)
574
575   -- take -ohi into account if present
576         ohi <- readIORef v_Output_hi
577         let location | Just fn <- ohi = location'{ ml_hi_file = fn }
578                      | otherwise      = location'
579
580   -- figure out if the source has changed, for recompilation avoidance.
581   -- only do this if we're eventually going to generate a .o file.
582   -- (ToDo: do when generating .hc files too?)
583   --
584   -- Setting source_unchanged to True means that M.o seems
585   -- to be up to date wrt M.hs; so no need to recompile unless imports have
586   -- changed (which the compiler itself figures out).
587   -- Setting source_unchanged to False tells the compiler that M.o is out of
588   -- date wrt M.hs (or M.o doesn't exist) so we must recompile regardless.
589         do_recomp   <- readIORef v_Recomp
590         expl_o_file <- readIORef v_Output_file
591
592         let o_file -- if the -o option is given and IT IS THE OBJECT FILE FOR
593                    -- THIS COMPILATION, then use that to determine if the 
594                    -- source is unchanged.
595                 | Just x <- expl_o_file, todo == StopBefore Ln  =  x
596                 | otherwise = ml_obj_file location
597
598         source_unchanged <- 
599           if not (do_recomp && ( todo == DoLink || todo == StopBefore Ln ))
600              then return False
601              else do t1 <- getModificationTime (basename ++ '.':suff)
602                      o_file_exists <- doesFileExist o_file
603                      if not o_file_exists
604                         then return False       -- Need to recompile
605                         else do t2 <- getModificationTime o_file
606                                 if t2 > t1
607                                   then return True
608                                   else return False
609
610   -- get the DynFlags
611         hsc_lang <- hscMaybeAdjustLang (hscLang dflags)
612         next_phase <- hscNextPhase hsc_lang
613         output_fn <- get_output_fn next_phase (Just location)
614
615         let dflags' = dflags { hscLang = hsc_lang,
616                                hscOutName = output_fn,
617                                hscStubCOutName = basename ++ "_stub.c",
618                                hscStubHOutName = basename ++ "_stub.h",
619                                extCoreName = basename ++ ".hcr" }
620         hsc_env <- newHscEnv OneShot dflags'
621
622   -- run the compiler!
623         result <- hscMain hsc_env printErrorsAndWarnings mod_name
624                           location{ ml_hspp_file = Just input_fn,
625                                     ml_hspp_buf  = hspp_buf }
626                           source_unchanged
627                           False
628                           Nothing        -- no iface
629
630         case result of
631
632             HscFail -> throwDyn (PhaseFailed "hsc" (ExitFailure 1))
633
634             HscNoRecomp details iface -> do
635                 SysTools.touch dflags' "Touching object file" o_file
636                 return (Nothing, dflags', Just location, output_fn)
637
638             HscRecomp _details _rdr_env _iface 
639                       stub_h_exists stub_c_exists
640                       _maybe_interpreted_code -> do
641
642                 -- deal with stubs
643                 maybe_stub_o <- compileStub dflags' stub_c_exists
644                 case maybe_stub_o of
645                       Nothing -> return ()
646                       Just stub_o -> add v_Ld_inputs stub_o
647                 case hscLang dflags' of
648                       HscNothing -> return (Nothing, dflags', Just location, output_fn)
649                       _ -> return (Just next_phase, dflags', Just location, output_fn)
650
651 -----------------------------------------------------------------------------
652 -- Cmm phase
653
654 runPhase CmmCpp dflags basename suff input_fn get_output_fn maybe_loc
655   = do
656        output_fn <- get_output_fn Cmm maybe_loc
657        doCpp dflags False{-not raw-} True{-include CC opts-} input_fn output_fn 
658        return (Just Cmm, dflags, maybe_loc, output_fn)
659
660 runPhase Cmm dflags basename suff input_fn get_output_fn maybe_loc
661   = do
662         hsc_lang <- hscMaybeAdjustLang (hscLang dflags)
663         next_phase <- hscNextPhase hsc_lang
664         output_fn <- get_output_fn next_phase maybe_loc
665
666         let dflags' = dflags { hscLang = hsc_lang,
667                                hscOutName = output_fn,
668                                hscStubCOutName = basename ++ "_stub.c",
669                                hscStubHOutName = basename ++ "_stub.h",
670                                extCoreName = basename ++ ".hcr" }
671
672         ok <- hscCmmFile dflags' input_fn
673
674         when (not ok) $ throwDyn (PhaseFailed "cmm" (ExitFailure 1))
675
676         return (Just next_phase, dflags, maybe_loc, output_fn)
677
678 -----------------------------------------------------------------------------
679 -- Cc phase
680
681 -- we don't support preprocessing .c files (with -E) now.  Doing so introduces
682 -- way too many hacks, and I can't say I've ever used it anyway.
683
684 runPhase cc_phase dflags basename suff input_fn get_output_fn maybe_loc
685    | cc_phase == Cc || cc_phase == HCc
686    = do let cc_opts = getOpts dflags opt_c
687         cmdline_include_paths <- readIORef v_Include_paths
688
689         split  <- readIORef v_Split_object_files
690         mangle <- readIORef v_Do_asm_mangling
691
692         let hcc = cc_phase == HCc
693
694             next_phase
695                 | hcc && mangle     = Mangle
696                 | otherwise         = As
697
698         output_fn <- get_output_fn next_phase maybe_loc
699
700         -- HC files have the dependent packages stamped into them
701         pkgs <- if hcc then getHCFilePackages input_fn else return []
702
703         -- add package include paths even if we're just compiling .c
704         -- files; this is the Value Add(TM) that using ghc instead of
705         -- gcc gives you :)
706         pkg_include_dirs <- getPackageIncludePath dflags pkgs
707         let include_paths = foldr (\ x xs -> "-I" : x : xs) []
708                               (cmdline_include_paths ++ pkg_include_dirs)
709
710         mangle <- readIORef v_Do_asm_mangling
711         (md_c_flags, md_regd_c_flags) <- machdepCCOpts dflags
712
713         let verb = getVerbFlag dflags
714
715         pkg_extra_cc_opts <- getPackageExtraCcOpts dflags pkgs
716
717         split_objs <- readIORef v_Split_object_files
718         let split_opt | hcc && split_objs = [ "-DUSE_SPLIT_MARKERS" ]
719                       | otherwise         = [ ]
720
721         excessPrecision <- readIORef v_Excess_precision
722
723         -- force the C compiler to interpret this file as C when
724         -- compiling .hc files, by adding the -x c option.
725         let langopt
726                 | cc_phase == HCc = [ SysTools.Option "-x", SysTools.Option "c"]
727                 | otherwise       = [ ]
728
729         SysTools.runCc dflags (langopt ++
730                         [ SysTools.FileOption "" input_fn
731                         , SysTools.Option "-o"
732                         , SysTools.FileOption "" output_fn
733                         ]
734                        ++ map SysTools.Option (
735                           md_c_flags
736                        ++ (if cc_phase == HCc && mangle
737                              then md_regd_c_flags
738                              else [])
739                        ++ [ verb, "-S", "-Wimplicit", "-O" ]
740                        ++ [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ]
741                        ++ cc_opts
742                        ++ split_opt
743                        ++ (if excessPrecision then [] else [ "-ffloat-store" ])
744                        ++ include_paths
745                        ++ pkg_extra_cc_opts
746                        ))
747
748         return (Just next_phase, dflags, maybe_loc, output_fn)
749
750         -- ToDo: postprocess the output from gcc
751
752 -----------------------------------------------------------------------------
753 -- Mangle phase
754
755 runPhase Mangle dflags _basename _suff input_fn get_output_fn maybe_loc
756    = do let mangler_opts = getOpts dflags opt_m
757         machdep_opts <- if (prefixMatch "i386" cTARGETPLATFORM)
758                           then do let n_regs = stolen_x86_regs dflags
759                                   return [ show n_regs ]
760                           else return []
761
762         split <- readIORef v_Split_object_files
763         let next_phase
764                 | split = SplitMangle
765                 | otherwise = As
766         output_fn <- get_output_fn next_phase maybe_loc
767
768         SysTools.runMangle dflags (map SysTools.Option mangler_opts
769                           ++ [ SysTools.FileOption "" input_fn
770                              , SysTools.FileOption "" output_fn
771                              ]
772                           ++ map SysTools.Option machdep_opts)
773
774         return (Just next_phase, dflags, maybe_loc, output_fn)
775
776 -----------------------------------------------------------------------------
777 -- Splitting phase
778
779 runPhase SplitMangle dflags _basename _suff input_fn get_output_fn maybe_loc
780   = do  -- tmp_pfx is the prefix used for the split .s files
781         -- We also use it as the file to contain the no. of split .s files (sigh)
782         split_s_prefix <- SysTools.newTempName "split"
783         let n_files_fn = split_s_prefix
784
785         SysTools.runSplit dflags
786                           [ SysTools.FileOption "" input_fn
787                           , SysTools.FileOption "" split_s_prefix
788                           , SysTools.FileOption "" n_files_fn
789                           ]
790
791         -- Save the number of split files for future references
792         s <- readFile n_files_fn
793         let n_files = read s :: Int
794         writeIORef v_Split_info (split_s_prefix, n_files)
795
796         -- Remember to delete all these files
797         addFilesToClean [ split_s_prefix ++ "__" ++ show n ++ ".s"
798                         | n <- [1..n_files]]
799
800         return (Just SplitAs, dflags, maybe_loc, "**splitmangle**")
801           -- we don't use the filename
802
803 -----------------------------------------------------------------------------
804 -- As phase
805
806 runPhase As dflags _basename _suff input_fn get_output_fn maybe_loc
807   = do  let as_opts =  getOpts dflags opt_a
808         cmdline_include_paths <- readIORef v_Include_paths
809
810         output_fn <- get_output_fn Ln maybe_loc
811
812         -- we create directories for the object file, because it
813         -- might be a hierarchical module.
814         createDirectoryHierarchy (directoryOf output_fn)
815
816         SysTools.runAs dflags   
817                        (map SysTools.Option as_opts
818                        ++ [ SysTools.Option ("-I" ++ p) | p <- cmdline_include_paths ]
819                        ++ [ SysTools.Option "-c"
820                           , SysTools.FileOption "" input_fn
821                           , SysTools.Option "-o"
822                           , SysTools.FileOption "" output_fn
823                           ])
824
825         return (Just Ln, dflags, maybe_loc, output_fn)
826
827
828 runPhase SplitAs dflags basename _suff _input_fn get_output_fn maybe_loc
829   = do  let as_opts = getOpts dflags opt_a
830
831         (split_s_prefix, n) <- readIORef v_Split_info
832
833         odir <- readIORef v_Output_dir
834         let real_odir = case odir of
835                                 Nothing -> basename ++ "_split"
836                                 Just d  -> d
837
838         let assemble_file n
839               = do  let input_s  = split_s_prefix ++ "__" ++ show n ++ ".s"
840                     let output_o = replaceFilenameDirectory
841                                         (basename ++ "__" ++ show n ++ ".o")
842                                          real_odir
843                     real_o <- osuf_ify output_o
844                     SysTools.runAs dflags
845                                  (map SysTools.Option as_opts ++
846                                     [ SysTools.Option "-c"
847                                     , SysTools.Option "-o"
848                                     , SysTools.FileOption "" real_o
849                                     , SysTools.FileOption "" input_s
850                                     ])
851         
852         mapM_ assemble_file [1..n]
853
854         output_fn <- get_output_fn Ln maybe_loc
855         return (Just Ln, dflags, maybe_loc, output_fn)
856
857 #ifdef ILX
858 -----------------------------------------------------------------------------
859 -- Ilx2Il phase
860 -- Run ilx2il over the ILX output, getting an IL file
861
862 runPhase Ilx2Il dflags _basename _suff input_fn get_output_fn maybe_loc
863   = do  let ilx2il_opts = getOpts dflags opt_I
864         SysTools.runIlx2il (map SysTools.Option ilx2il_opts
865                            ++ [ SysTools.Option "--no-add-suffix-to-assembly",
866                                 SysTools.Option "mscorlib",
867                                 SysTools.Option "-o",
868                                 SysTools.FileOption "" output_fn,
869                                 SysTools.FileOption "" input_fn ])
870         return True
871
872 -----------------------------------------------------------------------------
873 -- Ilasm phase
874 -- Run ilasm over the IL, getting a DLL
875
876 runPhase Ilasm dflags _basename _suff input_fn get_output_fn maybe_loc
877   = do  let ilasm_opts = getOpts dflags opt_i
878         SysTools.runIlasm (map SysTools.Option ilasm_opts
879                            ++ [ SysTools.Option "/QUIET",
880                                 SysTools.Option "/DLL",
881                                 SysTools.FileOption "/OUT=" output_fn,
882                                 SysTools.FileOption "" input_fn ])
883         return True
884
885 #endif /* ILX */
886
887 -----------------------------------------------------------------------------
888 -- MoveBinary sort-of-phase
889 -- After having produced a binary, move it somewhere else and generate a
890 -- wrapper script calling the binary. Currently, we need this only in 
891 -- a parallel way (i.e. in GUM), because PVM expects the binary in a
892 -- central directory.
893 -- This is called from staticLink below, after linking. I haven't made it
894 -- a separate phase to minimise interfering with other modules, and
895 -- we don't need the generality of a phase (MoveBinary is always
896 -- done after linking and makes only sense in a parallel setup)   -- HWL
897
898 runPhase_MoveBinary input_fn
899   = do  
900         sysMan   <- getSysMan
901         pvm_root <- getEnv "PVM_ROOT"
902         pvm_arch <- getEnv "PVM_ARCH"
903         let 
904            pvm_executable_base = "=" ++ input_fn
905            pvm_executable = pvm_root ++ "/bin/" ++ pvm_arch ++ "/" ++ pvm_executable_base
906         -- nuke old binary; maybe use configur'ed names for cp and rm?
907         system ("rm -f " ++ pvm_executable)
908         -- move the newly created binary into PVM land
909         system ("cp -p " ++ input_fn ++ " " ++ pvm_executable)
910         -- generate a wrapper script for running a parallel prg under PVM
911         writeFile input_fn (mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan)
912         return True
913
914 -- generates a Perl skript starting a parallel prg under PVM
915 mk_pvm_wrapper_script :: String -> String -> String -> String
916 mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan = unlines $
917  [
918   "eval 'exec perl -S $0 ${1+\"$@\"}'", 
919   "  if $running_under_some_shell;",
920   "# =!=!=!=!=!=!=!=!=!=!=!",
921   "# This script is automatically generated: DO NOT EDIT!!!",
922   "# Generated by Glasgow Haskell Compiler",
923   "# ngoqvam choHbogh vaj' vIHoHnISbej !!!!",
924   "#",
925   "$pvm_executable      = '" ++ pvm_executable ++ "';",
926   "$pvm_executable_base = '" ++ pvm_executable_base ++ "';",
927   "$SysMan = '" ++ sysMan ++ "';",
928   "",
929   {- ToDo: add the magical shortcuts again iff we actually use them -- HWL
930   "# first, some magical shortcuts to run "commands" on the binary",
931   "# (which is hidden)",
932   "if ($#ARGV == 1 && $ARGV[0] eq '+RTS' && $ARGV[1] =~ /^--((size|file|strip|rm|nm).*)/ ) {",
933   "    local($cmd) = $1;",
934   "    system("$cmd $pvm_executable");",
935   "    exit(0); # all done",
936   "}", -}
937   "",
938   "# Now, run the real binary; process the args first",
939   "$ENV{'PE'} = $pvm_executable_base;", --  ++ pvm_executable_base,
940   "$debug = '';",
941   "$nprocessors = 0; # the default: as many PEs as machines in PVM config",
942   "@nonPVM_args = ();",
943   "$in_RTS_args = 0;",
944   "",
945   "args: while ($a = shift(@ARGV)) {",
946   "    if ( $a eq '+RTS' ) {",
947   "     $in_RTS_args = 1;",
948   "    } elsif ( $a eq '-RTS' ) {",
949   "     $in_RTS_args = 0;",
950   "    }",
951   "    if ( $a eq '-d' && $in_RTS_args ) {",
952   "     $debug = '-';",
953   "    } elsif ( $a =~ /^-qN(\\d+)/ && $in_RTS_args ) {",
954   "     $nprocessors = $1;",
955   "    } elsif ( $a =~ /^-qp(\\d+)/ && $in_RTS_args ) {",
956   "     $nprocessors = $1;",
957   "    } else {",
958   "     push(@nonPVM_args, $a);",
959   "    }",
960   "}",
961   "",
962   "local($return_val) = 0;",
963   "# Start the parallel execution by calling SysMan",
964   "system(\"$SysMan $debug $pvm_executable $nprocessors @nonPVM_args\");",
965   "$return_val = $?;",
966   "# ToDo: fix race condition moving files and flushing them!!",
967   "system(\"cp $ENV{'HOME'}/$pvm_executable_base.???.gr .\") if -f \"$ENV{'HOME'}/$pvm_executable_base.002.gr\";",
968   "exit($return_val);"
969  ]
970
971 -----------------------------------------------------------------------------
972 -- Complain about non-dynamic flags in OPTIONS pragmas
973
974 checkProcessArgsResult flags filename
975   = do when (notNull flags) (throwDyn (ProgramError (
976           showSDoc (hang (text filename <> char ':')
977                       4 (text "unknown flags in  {-# OPTIONS #-} pragma:" <+>
978                           hsep (map text flags)))
979         )))
980
981 -----------------------------------------------------------------------------
982 -- Look for the /* GHC_PACKAGES ... */ comment at the top of a .hc file
983
984 getHCFilePackages :: FilePath -> IO [PackageId]
985 getHCFilePackages filename =
986   EXCEPTION.bracket (openFile filename ReadMode) hClose $ \h -> do
987     l <- hGetLine h
988     case l of
989       '/':'*':' ':'G':'H':'C':'_':'P':'A':'C':'K':'A':'G':'E':'S':rest ->
990           return (map stringToPackageId (words rest))
991       _other ->
992           return []
993
994 -----------------------------------------------------------------------------
995 -- Static linking, of .o files
996
997 -- The list of packages passed to link is the list of packages on
998 -- which this program depends, as discovered by the compilation
999 -- manager.  It is combined with the list of packages that the user
1000 -- specifies on the command line with -package flags.  
1001 --
1002 -- In one-shot linking mode, we can't discover the package
1003 -- dependencies (because we haven't actually done any compilation or
1004 -- read any interface files), so the user must explicitly specify all
1005 -- the packages.
1006
1007 staticLink :: DynFlags -> [FilePath] -> [PackageId] -> IO ()
1008 staticLink dflags o_files dep_packages = do
1009     let verb = getVerbFlag dflags
1010     static     <- readIORef v_Static
1011     no_hs_main <- readIORef v_NoHsMain
1012
1013     -- get the full list of packages to link with, by combining the
1014     -- explicit packages with the auto packages and all of their
1015     -- dependencies, and eliminating duplicates.
1016
1017     o_file <- readIORef v_Output_file
1018 #if defined(mingw32_HOST_OS)
1019     let output_fn = case o_file of { Just s -> s; Nothing -> "main.exe"; }
1020 #else
1021     let output_fn = case o_file of { Just s -> s; Nothing -> "a.out"; }
1022 #endif
1023
1024     pkg_lib_paths <- getPackageLibraryPath dflags dep_packages
1025     let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths
1026
1027     lib_paths <- readIORef v_Library_paths
1028     let lib_path_opts = map ("-L"++) lib_paths
1029
1030     pkg_link_opts <- getPackageLinkOpts dflags dep_packages
1031
1032 #ifdef darwin_TARGET_OS
1033     pkg_framework_paths <- getPackageFrameworkPath dflags dep_packages
1034     let pkg_framework_path_opts = map ("-F"++) pkg_framework_paths
1035
1036     framework_paths <- readIORef v_Framework_paths
1037     let framework_path_opts = map ("-F"++) framework_paths
1038
1039     pkg_frameworks <- getPackageFrameworks dflags dep_packages
1040     let pkg_framework_opts = concat [ ["-framework", fw] | fw <- pkg_frameworks ]
1041
1042     frameworks <- readIORef v_Cmdline_frameworks
1043     let framework_opts = concat [ ["-framework", fw] | fw <- reverse frameworks ]
1044          -- reverse because they're added in reverse order from the cmd line
1045 #endif
1046
1047         -- probably _stub.o files
1048     extra_ld_inputs <- readIORef v_Ld_inputs
1049
1050         -- opts from -optl-<blah> (including -l<blah> options)
1051     extra_ld_opts <- getStaticOpts v_Opt_l
1052
1053     let pstate = pkgState dflags
1054         rts_id | ExtPackage id <- rtsPackageId pstate = id
1055                | otherwise = panic "staticLink: rts package missing"
1056         base_id | ExtPackage id <- basePackageId pstate = id
1057                 | otherwise = panic "staticLink: base package missing"
1058         rts_pkg  = getPackageDetails pstate rts_id
1059         base_pkg = getPackageDetails pstate base_id
1060
1061     ways <- readIORef v_Ways
1062
1063     -- Here are some libs that need to be linked at the *end* of
1064     -- the command line, because they contain symbols that are referred to
1065     -- by the RTS.  We can't therefore use the ordinary way opts for these.
1066     let
1067         debug_opts | WayDebug `elem` ways = [ 
1068 #if defined(HAVE_LIBBFD)
1069                         "-lbfd", "-liberty"
1070 #endif
1071                          ]
1072                    | otherwise            = []
1073
1074     let
1075         thread_opts | WayThreaded `elem` ways = [ 
1076 #if !defined(mingw32_TARGET_OS) && !defined(freebsd_TARGET_OS)
1077                         "-lpthread"
1078 #endif
1079 #if defined(osf3_TARGET_OS)
1080                         , "-lexc"
1081 #endif
1082                         ]
1083                     | otherwise               = []
1084
1085     let extra_os = if static || no_hs_main
1086                    then []
1087                    else []
1088
1089     (md_c_flags, _) <- machdepCCOpts dflags
1090     SysTools.runLink dflags ( 
1091                        [ SysTools.Option verb
1092                        , SysTools.Option "-o"
1093                        , SysTools.FileOption "" output_fn
1094                        ]
1095                       ++ map SysTools.Option (
1096                          md_c_flags
1097                       ++ o_files
1098                       ++ extra_os
1099                       ++ extra_ld_inputs
1100                       ++ lib_path_opts
1101                       ++ extra_ld_opts
1102 #ifdef darwin_TARGET_OS
1103                       ++ framework_path_opts
1104                       ++ framework_opts
1105 #endif
1106                       ++ pkg_lib_path_opts
1107                       ++ pkg_link_opts
1108 #ifdef darwin_TARGET_OS
1109                       ++ pkg_framework_path_opts
1110                       ++ pkg_framework_opts
1111 #endif
1112                       ++ debug_opts
1113                       ++ thread_opts
1114                     ))
1115
1116     -- parallel only: move binary to another dir -- HWL
1117     ways_ <- readIORef v_Ways
1118     when (WayPar `elem` ways_)
1119          (do success <- runPhase_MoveBinary output_fn
1120              if success then return ()
1121                         else throwDyn (InstallationError ("cannot move binary to PVM dir")))
1122
1123 -----------------------------------------------------------------------------
1124 -- Making a DLL (only for Win32)
1125
1126 doMkDLL :: DynFlags -> [String] -> [PackageId] -> IO ()
1127 doMkDLL dflags o_files dep_packages = do
1128     let verb = getVerbFlag dflags
1129     static     <- readIORef v_Static
1130     no_hs_main <- readIORef v_NoHsMain
1131
1132     o_file <- readIORef v_Output_file
1133     let output_fn = case o_file of { Just s -> s; Nothing -> "HSdll.dll"; }
1134
1135     pkg_lib_paths <- getPackageLibraryPath dflags dep_packages
1136     let pkg_lib_path_opts = map ("-L"++) pkg_lib_paths
1137
1138     lib_paths <- readIORef v_Library_paths
1139     let lib_path_opts = map ("-L"++) lib_paths
1140
1141     pkg_link_opts <- getPackageLinkOpts dflags dep_packages
1142
1143         -- probably _stub.o files
1144     extra_ld_inputs <- readIORef v_Ld_inputs
1145
1146         -- opts from -optdll-<blah>
1147     extra_ld_opts <- getStaticOpts v_Opt_dll
1148
1149     let pstate = pkgState dflags
1150         rts_id | ExtPackage id <- rtsPackageId pstate = id
1151                | otherwise = panic "staticLink: rts package missing"
1152         base_id | ExtPackage id <- basePackageId pstate = id
1153                 | otherwise = panic "staticLink: base package missing"
1154         rts_pkg  = getPackageDetails pstate rts_id
1155         base_pkg = getPackageDetails pstate base_id
1156
1157     let extra_os = if static || no_hs_main
1158                    then []
1159                    else [ head (libraryDirs rts_pkg) ++ "/Main.dll_o",
1160                           head (libraryDirs base_pkg) ++ "/PrelMain.dll_o" ]
1161
1162     (md_c_flags, _) <- machdepCCOpts dflags
1163     SysTools.runMkDLL dflags
1164          ([ SysTools.Option verb
1165           , SysTools.Option "-o"
1166           , SysTools.FileOption "" output_fn
1167           ]
1168          ++ map SysTools.Option (
1169             md_c_flags
1170          ++ o_files
1171          ++ extra_os
1172          ++ [ "--target=i386-mingw32" ]
1173          ++ extra_ld_inputs
1174          ++ lib_path_opts
1175          ++ extra_ld_opts
1176          ++ pkg_lib_path_opts
1177          ++ pkg_link_opts
1178          ++ (if "--def" `elem` (concatMap words extra_ld_opts)
1179                then [ "" ]
1180                else [ "--export-all" ])
1181         ))
1182
1183 -- -----------------------------------------------------------------------------
1184 -- Misc.
1185
1186 doCpp :: DynFlags -> Bool -> Bool -> FilePath -> FilePath -> IO ()
1187 doCpp dflags raw include_cc_opts input_fn output_fn = do
1188     let hscpp_opts = getOpts dflags opt_P
1189
1190     cmdline_include_paths <- readIORef v_Include_paths
1191
1192     pkg_include_dirs <- getPackageIncludePath dflags []
1193     let include_paths = foldr (\ x xs -> "-I" : x : xs) []
1194                           (cmdline_include_paths ++ pkg_include_dirs)
1195
1196     let verb = getVerbFlag dflags
1197
1198     cc_opts <- if not include_cc_opts 
1199                   then return []
1200                   else do let optc = getOpts dflags opt_c
1201                           (md_c_flags, _) <- machdepCCOpts dflags
1202                           return (optc ++ md_c_flags)
1203
1204     let cpp_prog args | raw       = SysTools.runCpp dflags args
1205                       | otherwise = SysTools.runCc dflags (SysTools.Option "-E" : args)
1206
1207     let target_defs = 
1208           [ "-D" ++ cTARGETOS   ++ "_TARGET_OS=1",
1209             "-D" ++ cTARGETARCH ++ "_TARGET_ARCH=1" ]
1210
1211     cpp_prog       ([SysTools.Option verb]
1212                     ++ map SysTools.Option include_paths
1213                     ++ map SysTools.Option hsSourceCppOpts
1214                     ++ map SysTools.Option hscpp_opts
1215                     ++ map SysTools.Option cc_opts
1216                     ++ map SysTools.Option target_defs
1217                     ++ [ SysTools.Option     "-x"
1218                        , SysTools.Option     "c"
1219                        , SysTools.Option     input_fn
1220         -- We hackily use Option instead of FileOption here, so that the file
1221         -- name is not back-slashed on Windows.  cpp is capable of
1222         -- dealing with / in filenames, so it works fine.  Furthermore
1223         -- if we put in backslashes, cpp outputs #line directives
1224         -- with *double* backslashes.   And that in turn means that
1225         -- our error messages get double backslashes in them.
1226         -- In due course we should arrange that the lexer deals
1227         -- with these \\ escapes properly.
1228                        , SysTools.Option     "-o"
1229                        , SysTools.FileOption "" output_fn
1230                        ])
1231
1232 -- -----------------------------------------------------------------------------
1233 -- Misc.
1234
1235 hscNextPhase :: HscLang -> IO Phase
1236 hscNextPhase hsc_lang = do
1237   split <- readIORef v_Split_object_files
1238   return (case hsc_lang of
1239                 HscC -> HCc
1240                 HscAsm | split -> SplitMangle
1241                        | otherwise -> As
1242                 HscNothing     -> HCc  -- dummy (no output will be generated)
1243                 HscInterpreted -> HCc  -- "" ""
1244                 _other         -> HCc  -- "" ""
1245         )
1246
1247 hscMaybeAdjustLang :: HscLang -> IO HscLang
1248 hscMaybeAdjustLang current_hsc_lang = do
1249   todo    <- readIORef v_GhcMode
1250   keep_hc <- readIORef v_Keep_hc_files
1251   let hsc_lang
1252         -- don't change the lang if we're interpreting
1253          | current_hsc_lang == HscInterpreted = current_hsc_lang
1254         -- force -fvia-C if we are being asked for a .hc file
1255          | todo == StopBefore HCc  || keep_hc = HscC
1256         -- otherwise, stick to the plan
1257          | otherwise = current_hsc_lang
1258   return hsc_lang