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