[project @ 2003-09-04 11:08:46 by simonmar]
[ghc-hetmet.git] / ghc / compiler / main / Main.hs
1 {-# OPTIONS -fno-warn-incomplete-patterns -optc-DNON_POSIX_SOURCE #-}
2
3 -----------------------------------------------------------------------------
4 -- $Id: Main.hs,v 1.132 2003/09/04 11:08:47 simonmar Exp $
5 --
6 -- GHC Driver program
7 --
8 -- (c) The University of Glasgow 2002
9 --
10 -----------------------------------------------------------------------------
11
12 -- with path so that ghc -M can find config.h
13 #include "../includes/config.h"
14
15 module Main (main) where
16
17 #include "HsVersions.h"
18
19
20 #ifdef GHCI
21 import InteractiveUI( ghciWelcomeMsg, interactiveUI )
22 #endif
23
24
25 import CompManager      ( cmInit, cmLoadModules, cmDepAnal )
26 import HscTypes         ( GhciMode(..) )
27 import Config           ( cBooterVersion, cGhcUnregisterised, cProjectVersion )
28 import SysTools         ( getPackageConfigPath, initSysTools, cleanTempFiles,
29                           normalisePath )
30 import Packages         ( showPackages, getPackageConfigMap, basePackage,
31                           haskell98Package
32                         )
33 import DriverPipeline   ( staticLink, doMkDLL, runPipeline )
34 import DriverState      ( buildCoreToDo, buildStgToDo,
35                           findBuildTag, 
36                           getPackageExtraGhcOpts, unregFlags, 
37                           v_GhcMode, v_GhcModeFlag, GhcMode(..),
38                           v_Keep_tmp_files, v_Ld_inputs, v_Ways, 
39                           v_OptLevel, v_Output_file, v_Output_hi, 
40                           readPackageConf, verifyOutputFiles, v_NoLink,
41                           v_Build_tag
42                         )
43 import DriverFlags      ( buildStaticHscOpts,
44                           dynamic_flags, processArgs, static_flags)
45
46 import DriverMkDepend   ( beginMkDependHS, endMkDependHS )
47 import DriverPhases     ( isSourceFile )
48
49 import DriverUtil       ( add, handle, handleDyn, later, unknownFlagsErr )
50 import CmdLineOpts      ( dynFlag, restoreDynFlags,
51                           saveDynFlags, setDynFlags, getDynFlags, dynFlag,
52                           DynFlags(..), HscLang(..), v_Static_hsc_opts
53                         )
54 import BasicTypes       ( failed )
55 import Outputable
56 import Util
57 import Panic            ( GhcException(..), panic, installSignalHandlers )
58
59 import DATA_IOREF       ( readIORef, writeIORef )
60 import EXCEPTION        ( throwDyn, Exception(..), 
61                           AsyncException(StackOverflow) )
62
63 -- Standard Haskell libraries
64 import IO
65 import Directory        ( doesFileExist )
66 import System           ( getArgs, exitWith, ExitCode(..) )
67 import Monad
68 import List
69 import Maybe
70
71 -----------------------------------------------------------------------------
72 -- ToDo:
73
74 -- new mkdependHS doesn't support all the options that the old one did (-X et al.)
75 -- time commands when run with -v
76 -- split marker
77 -- java generation
78 -- user ways
79 -- Win32 support: proper signal handling
80 -- make sure OPTIONS in .hs file propogate to .hc file if -C or -keep-hc-file-too
81 -- reading the package configuration file is too slow
82 -- -K<size>
83
84 -----------------------------------------------------------------------------
85 -- Differences vs. old driver:
86
87 -- No more "Enter your Haskell program, end with ^D (on a line of its own):"
88 -- consistency checking removed (may do this properly later)
89 -- no -Ofile
90
91 -----------------------------------------------------------------------------
92 -- Main loop
93
94 main =
95   -- top-level exception handler: any unrecognised exception is a compiler bug.
96   handle (\exception -> do
97            hFlush stdout
98            case exception of
99                 -- an IO exception probably isn't our fault, so don't panic
100                 IOException _ ->  hPutStrLn stderr (show exception)
101                 AsyncException StackOverflow ->
102                         hPutStrLn stderr "stack overflow: use +RTS -K<size> \ 
103                                          \to increase it"
104                 _other ->  hPutStr stderr (show (Panic (show exception)))
105            exitWith (ExitFailure 1)
106          ) $ do
107
108   -- all error messages are propagated as exceptions
109   handleDyn (\dyn -> do
110                 hFlush stdout
111                 case dyn of
112                      PhaseFailed _ code -> exitWith code
113                      Interrupted -> exitWith (ExitFailure 1)
114                      _ -> do hPutStrLn stderr (show (dyn :: GhcException))
115                              exitWith (ExitFailure 1)
116             ) $ do
117
118    -- make sure we clean up after ourselves
119    later (do  forget_it <- readIORef v_Keep_tmp_files
120               unless forget_it $ do
121               verb <- dynFlag verbosity
122               cleanTempFiles verb
123      ) $ do
124         -- exceptions will be blocked while we clean the temporary files,
125         -- so there shouldn't be any difficulty if we receive further
126         -- signals.
127
128    installSignalHandlers
129
130    argv <- getArgs
131    let (minusB_args, argv') = partition (prefixMatch "-B") argv
132    top_dir <- initSysTools minusB_args
133
134         -- Read the package configuration
135    conf_file <- getPackageConfigPath
136    readPackageConf conf_file
137
138         -- Process all the other arguments, and get the source files
139    non_static <- processArgs static_flags argv' []
140    mode <- readIORef v_GhcMode
141
142         -- -O and --interactive are not a good combination
143         -- ditto with any kind of way selection
144    orig_opt_level <- readIORef v_OptLevel
145    when (orig_opt_level > 0 && isInteractive mode) $
146       do putStr "warning: -O conflicts with --interactive; -O turned off.\n"
147          writeIORef v_OptLevel 0
148    orig_ways <- readIORef v_Ways
149    when (notNull orig_ways && isInteractive mode) $
150       do throwDyn (UsageError 
151                    "--interactive can't be used with -prof, -ticky, -unreg or -smp.")
152
153         -- Find the build tag, and re-process the build-specific options.
154         -- Also add in flags for unregisterised compilation, if 
155         -- GhcUnregisterised=YES.
156    way_opts <- findBuildTag
157    let unreg_opts | cGhcUnregisterised == "YES" = unregFlags
158                   | otherwise = []
159    pkg_extra_opts <- getPackageExtraGhcOpts
160    extra_non_static <- processArgs static_flags 
161                            (unreg_opts ++ way_opts ++ pkg_extra_opts) []
162
163         -- Give the static flags to hsc
164    static_opts <- buildStaticHscOpts
165    writeIORef v_Static_hsc_opts static_opts
166
167    -- build the default DynFlags (these may be adjusted on a per
168    -- module basis by OPTIONS pragmas and settings in the interpreter).
169
170    core_todo <- buildCoreToDo
171    stg_todo  <- buildStgToDo
172
173    -- set the "global" HscLang.  The HscLang can be further adjusted on a module
174    -- by module basis, using only the -fvia-C and -fasm flags.  If the global
175    -- HscLang is not HscC or HscAsm, -fvia-C and -fasm have no effect.
176    dyn_flags <- getDynFlags
177    build_tag <- readIORef v_Build_tag
178    let lang = case mode of 
179                  DoInteractive  -> HscInterpreted
180                  DoEval _       -> HscInterpreted
181                  _other | build_tag /= "" -> HscC
182                         | otherwise       -> hscLang dyn_flags
183                 -- for ways other that the normal way, we must 
184                 -- compile via C.
185
186    setDynFlags (dyn_flags{ coreToDo = core_todo,
187                            stgToDo  = stg_todo,
188                            hscLang  = lang,
189                            -- leave out hscOutName for now
190                            hscOutName = panic "Main.main:hscOutName not set",
191                            verbosity = case mode of
192                                          DoEval _ -> 0
193                                          _other   -> 1
194                         })
195
196         -- The rest of the arguments are "dynamic"
197         -- Leftover ones are presumably files
198    fileish_args <- processArgs dynamic_flags (extra_non_static ++ non_static) []
199
200         -- save the "initial DynFlags" away
201    saveDynFlags
202
203    let
204     {-
205       We split out the object files (.o, .dll) and add them
206       to v_Ld_inputs for use by the linker.
207
208       The following things should be considered compilation manager inputs:
209
210        - haskell source files (strings ending in .hs, .lhs or other 
211          haskellish extension),
212
213        - module names (not forgetting hierarchical module names),
214
215        - and finally we consider everything not containing a '.' to be
216          a comp manager input, as shorthand for a .hs or .lhs filename.
217
218       Everything else is considered to be a linker object, and passed
219       straight through to the linker.
220     -}
221     looks_like_an_input m =  isSourceFile m 
222                           || looksLikeModuleName m
223                           || '.' `notElem` m
224
225      -- To simplify the handling of filepaths, we normalise all filepaths right 
226      -- away - e.g., for win32 platforms, backslashes are converted
227      -- into forward slashes.
228     normal_fileish_paths = map normalisePath fileish_args
229     (srcs, objs)         = partition looks_like_an_input normal_fileish_paths
230
231    mapM_ (add v_Ld_inputs) objs
232
233         ---------------- Display banners and configuration -----------
234    showBanners mode conf_file static_opts
235
236         ---------------- Final sanity checking -----------
237    checkOptions mode srcs objs
238
239     -- We always link in the base package in
240     -- one-shot linking.  Any other packages
241     -- required must be given using -package
242     -- options on the command-line.
243    let def_hs_pkgs = [basePackage, haskell98Package]
244
245         ---------------- Do the business -----------
246    case mode of
247         DoMake         -> doMake srcs
248                                
249         DoMkDependHS   -> do { beginMkDependHS ; 
250                                compileFiles mode srcs; 
251                                endMkDependHS }
252         StopBefore p   -> do { compileFiles mode srcs; return () }
253         DoMkDLL        -> do { o_files <- compileFiles mode srcs; 
254                                doMkDLL o_files def_hs_pkgs }
255         DoLink         -> do { o_files <- compileFiles mode srcs; 
256                                omit_linking <- readIORef v_NoLink;
257                                when (not omit_linking)
258                                     (staticLink o_files def_hs_pkgs) }
259
260 #ifndef GHCI
261         DoInteractive -> noInteractiveError
262         DoEval _      -> noInteractiveError
263      where
264        noInteractiveError = throwDyn (CmdLineError "not built for interactive use")
265 #else
266         DoInteractive -> interactiveUI srcs Nothing
267         DoEval expr   -> interactiveUI srcs (Just expr)
268 #endif
269
270 -- -----------------------------------------------------------------------------
271 -- Option sanity checks
272
273 checkOptions :: GhcMode -> [String] -> [String] -> IO ()
274      -- Final sanity checking before kicking off a compilation (pipeline).
275 checkOptions mode srcs objs = do
276      -- Complain about any unknown flags
277    let unknown_opts = [ f | f@('-':_) <- srcs ]
278    when (notNull unknown_opts) (unknownFlagsErr unknown_opts)
279
280         -- -ohi sanity check
281    ohi <- readIORef v_Output_hi
282    if (isJust ohi && 
283       (mode == DoMake || isInteractive mode || srcs `lengthExceeds` 1))
284         then throwDyn (UsageError "-ohi can only be used when compiling a single source file")
285         else do
286
287         -- -o sanity checking
288    o_file <- readIORef v_Output_file
289    if (srcs `lengthExceeds` 1 && isJust o_file && mode /= DoLink && mode /= DoMkDLL)
290         then throwDyn (UsageError "can't apply -o to multiple source files")
291         else do
292
293         -- Check that there are some input files (except in the interactive 
294         -- case)
295    if null srcs && null objs && not (isInteractive mode)
296         then throwDyn (UsageError "no input files")
297         else do
298
299      -- Verify that output files point somewhere sensible.
300    verifyOutputFiles
301
302 isInteractive DoInteractive = True
303 isInteractive (DoEval _)    = True
304 isInteractive _             = False
305
306 -- -----------------------------------------------------------------------------
307 -- Compile files in one-shot mode.
308
309 compileFiles :: GhcMode 
310              -> [String]        -- Source files
311              -> IO [String]     -- Object files
312 compileFiles mode srcs = do
313    stop_flag <- readIORef v_GhcModeFlag
314    mapM (compileFile mode stop_flag) srcs
315
316
317 compileFile mode stop_flag src = do
318    restoreDynFlags
319    
320    exists <- doesFileExist src
321    when (not exists) $ 
322         throwDyn (CmdLineError ("file `" ++ src ++ "' does not exist"))
323    
324    o_file   <- readIORef v_Output_file
325         -- when linking, the -o argument refers to the linker's output. 
326         -- otherwise, we use it as the name for the pipeline's output.
327    let maybe_o_file
328           | mode==DoLink || mode==DoMkDLL  = Nothing
329           | otherwise                      = o_file
330
331    runPipeline mode stop_flag True maybe_o_file src Nothing{-no ModLocation-}
332
333
334 -- ----------------------------------------------------------------------------
335 -- Run --make mode
336
337 doMake :: [String] -> IO ()
338 doMake []    = throwDyn (UsageError "no input files")
339 doMake srcs  = do 
340     dflags <- getDynFlags 
341     state  <- cmInit Batch
342     graph  <- cmDepAnal state dflags srcs
343     (_, ok_flag, _) <- cmLoadModules state dflags graph
344     when (failed ok_flag) (exitWith (ExitFailure 1))
345     return ()
346
347 -- ---------------------------------------------------------------------------
348 -- Various banners and verbosity output.
349
350 showBanners :: GhcMode -> FilePath -> [String] -> IO ()
351 showBanners mode conf_file static_opts = do
352    verb <- dynFlag verbosity
353
354         -- Show the GHCi banner
355 #  ifdef GHCI
356    when (mode == DoInteractive && verb >= 1) $
357       hPutStrLn stdout ghciWelcomeMsg
358 #  endif
359
360         -- Display details of the configuration in verbose mode
361    when (verb >= 2) 
362         (do hPutStr stderr "Glasgow Haskell Compiler, Version "
363             hPutStr stderr cProjectVersion
364             hPutStr stderr ", for Haskell 98, compiled by GHC version "
365             hPutStrLn stderr cBooterVersion)
366
367    when (verb >= 2) 
368         (hPutStrLn stderr ("Using package config file: " ++ conf_file))
369
370    pkg_details <- getPackageConfigMap
371    showPackages pkg_details
372
373    when (verb >= 3) 
374         (hPutStrLn stderr ("Hsc static flags: " ++ unwords static_opts))