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