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