[project @ 2001-08-14 13:40:07 by sewardj]
[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.87 2001/08/14 13:40:08 sewardj Exp $
5 --
6 -- GHC Driver program
7 --
8 -- (c) Simon Marlow 2000
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 Finder           ( initFinder )
26 import CompManager      ( cmInit, cmLoadModule )
27 import HscTypes         ( GhciMode(..) )
28 import Config           ( cBooterVersion, cGhcUnregisterised, cProjectVersion )
29 import SysTools         ( getPackageConfigPath, initSysTools, cleanTempFiles )
30 import Packages         ( showPackages )
31
32 import DriverPipeline   ( GhcMode(..), doLink, doMkDLL, genPipeline,
33                           getGhcMode, pipeLoop, v_GhcMode
34                         )
35 import DriverState      ( buildCoreToDo, buildStgToDo, defaultHscLang,
36                           findBuildTag, getPackageInfo, unregFlags, 
37                           v_Cmdline_libraries, v_Keep_tmp_files, v_Ld_inputs,
38                           v_OptLevel, v_Output_file, v_Output_hi, 
39                           v_Package_details, v_Ways, getPackageExtraGhcOpts,
40                           readPackageConf
41                         )
42 import DriverFlags      ( dynFlag, buildStaticHscOpts, dynamic_flags,
43                           processArgs, static_flags)
44
45 import DriverMkDepend   ( beginMkDependHS, endMkDependHS )
46 import DriverPhases     ( Phase(Hsc, HCc), haskellish_src_file, objish_file )
47
48 import DriverUtil       ( add, handle, handleDyn, later, splitFilename,
49                           unknownFlagErr, getFileSuffix )
50 import CmdLineOpts      ( dynFlag, defaultDynFlags, restoreDynFlags,
51                           saveDynFlags, setDynFlags, 
52                           DynFlags(..), HscLang(..), v_Static_hsc_opts
53                         )
54
55 import Outputable
56 import Util
57 import Panic            ( GhcException(..), panic )
58
59 -- Standard Haskell libraries
60 import IO
61 import Directory        ( doesFileExist )
62 import IOExts           ( readIORef, writeIORef )
63 import Exception        ( throwDyn, Exception(..) )
64 import System           ( getArgs, exitWith, ExitCode(..) )
65 import Monad
66 import List
67 import Maybe
68
69 #ifndef mingw32_TARGET_OS
70 import Concurrent       ( myThreadId )
71 #if __GLASGOW_HASKELL__ < 500
72 import Exception        ( raiseInThread )
73 #define throwTo  raiseInThread
74 #else
75 import Exception        ( throwTo )
76 #endif
77
78 import Posix            ( Handler(Catch), installHandler, sigINT, sigQUIT )
79 import Dynamic          ( toDyn )
80 #endif
81
82
83 -----------------------------------------------------------------------------
84 -- Changes:
85
86 -- * -fglasgow-exts NO LONGER IMPLIES -package lang!!!  (-fglasgow-exts is a
87 --   dynamic flag whereas -package is a static flag.)
88
89 -----------------------------------------------------------------------------
90 -- ToDo:
91
92 -- new mkdependHS doesn't support all the options that the old one did (-X et al.)
93 -- time commands when run with -v
94 -- split marker
95 -- java generation
96 -- user ways
97 -- Win32 support: proper signal handling
98 -- make sure OPTIONS in .hs file propogate to .hc file if -C or -keep-hc-file-too
99 -- reading the package configuration file is too slow
100 -- -K<size>
101
102 -----------------------------------------------------------------------------
103 -- Differences vs. old driver:
104
105 -- No more "Enter your Haskell program, end with ^D (on a line of its own):"
106 -- consistency checking removed (may do this properly later)
107 -- removed -noC
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            case exception of
117                 -- an IO exception probably isn't our fault, so don't panic
118                 IOException _ ->  hPutStr stderr (show exception)
119                 _other        ->  hPutStr stderr (show (Panic (show exception)))
120            exitWith (ExitFailure 1)
121          ) $ do
122
123   -- all error messages are propagated as exceptions
124   handleDyn (\dyn -> case dyn of
125                           PhaseFailed _phase code -> exitWith code
126                           Interrupted -> exitWith (ExitFailure 1)
127                           _ -> do hPutStrLn stderr (show (dyn :: GhcException))
128                                   exitWith (ExitFailure 1)
129             ) $ do
130
131    -- make sure we clean up after ourselves
132    later (do  forget_it <- readIORef v_Keep_tmp_files
133               unless forget_it $ do
134               verb <- dynFlag verbosity
135               cleanTempFiles verb
136      ) $ do
137         -- exceptions will be blocked while we clean the temporary files,
138         -- so there shouldn't be any difficulty if we receive further
139         -- signals.
140
141         -- install signal handlers
142 #ifndef mingw32_TARGET_OS
143    main_thread <- myThreadId
144    let sig_handler = Catch (throwTo main_thread 
145                                 (DynException (toDyn Interrupted)))
146    installHandler sigQUIT sig_handler Nothing 
147    installHandler sigINT  sig_handler Nothing
148 #endif
149
150    argv <- getArgs
151    let (minusB_args, argv') = partition (prefixMatch "-B") argv
152    top_dir <- initSysTools minusB_args
153
154         -- Read the package configuration
155    conf_file <- getPackageConfigPath
156    readPackageConf conf_file
157
158         -- find the phase to stop after (i.e. -E, -C, -c, -S flags)
159    (flags2, mode, stop_flag) <- getGhcMode argv'
160    writeIORef v_GhcMode mode
161
162         -- process all the other arguments, and get the source files
163    non_static <- processArgs static_flags flags2 []
164
165         -- -O and --interactive are not a good combination
166         -- ditto with any kind of way selection
167    orig_opt_level <- readIORef v_OptLevel
168    when (orig_opt_level > 0 && mode == DoInteractive) $
169       do putStr "warning: -O conflicts with --interactive; -O turned off.\n"
170          writeIORef v_OptLevel 0
171    orig_ways <- readIORef v_Ways
172    when (not (null orig_ways) && mode == DoInteractive) $
173       do throwDyn (UsageError 
174                    "--interactive can't be used with -prof, -ticky, -unreg or -smp.")
175
176         -- Find the build tag, and re-process the build-specific options.
177         -- Also add in flags for unregisterised compilation, if 
178         -- GhcUnregisterised=YES.
179    way_opts <- findBuildTag
180    let unreg_opts | cGhcUnregisterised == "YES" = unregFlags
181                   | otherwise = []
182    pkg_extra_opts <- getPackageExtraGhcOpts
183    extra_non_static <- processArgs static_flags 
184                            (unreg_opts ++ way_opts ++ pkg_extra_opts) []
185
186         -- give the static flags to hsc
187    static_opts <- buildStaticHscOpts
188    writeIORef v_Static_hsc_opts static_opts
189
190    -- build the default DynFlags (these may be adjusted on a per
191    -- module basis by OPTIONS pragmas and settings in the interpreter).
192
193    core_todo <- buildCoreToDo
194    stg_todo  <- buildStgToDo
195
196    -- set the "global" HscLang.  The HscLang can be further adjusted on a module
197    -- by module basis, using only the -fvia-C and -fasm flags.  If the global
198    -- HscLang is not HscC or HscAsm, -fvia-C and -fasm have no effect.
199    opt_level  <- readIORef v_OptLevel
200
201
202    let lang = case mode of 
203                  StopBefore HCc -> HscC
204                  DoInteractive  -> HscInterpreted
205                  _other        | opt_level >= 1  -> HscC  -- -O implies -fvia-C 
206                                | otherwise       -> defaultHscLang
207
208    setDynFlags (defaultDynFlags{ 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
214                                  verbosity = case mode of
215                                                 DoInteractive -> 1
216                                                 DoMake        -> 1
217                                                 _other        -> 0,
218                                 })
219
220         -- the rest of the arguments are "dynamic"
221    srcs <- processArgs dynamic_flags (extra_non_static ++ non_static) []
222
223         -- save the "initial DynFlags" away
224    saveDynFlags
225
226         -- complain about any unknown flags
227    mapM unknownFlagErr [ f | f@('-':_) <- srcs ]
228
229    verb <- dynFlag verbosity
230
231         -- Show the GHCi banner
232 #  ifdef GHCI
233    when (mode == DoInteractive && verb >= 1) $
234       hPutStrLn stdout ghciWelcomeMsg
235 #  endif
236
237         -- Display details of the configuration in verbose mode
238    when (verb >= 2) 
239         (do hPutStr stderr "Glasgow Haskell Compiler, Version "
240             hPutStr stderr cProjectVersion
241             hPutStr stderr ", for Haskell 98, compiled by GHC version "
242             hPutStrLn stderr cBooterVersion)
243
244    when (verb >= 2) 
245         (hPutStrLn stderr ("Using package config file: " ++ conf_file))
246
247    pkg_details <- readIORef v_Package_details
248    showPackages pkg_details
249
250    when (verb >= 3) 
251         (hPutStrLn stderr ("Hsc static flags: " ++ unwords static_opts))
252
253         -- initialise the finder
254    pkg_avails <- getPackageInfo
255    initFinder pkg_avails
256
257         -- mkdependHS is special
258    when (mode == DoMkDependHS) beginMkDependHS
259
260         -- -ohi sanity checking
261    ohi    <- readIORef v_Output_hi
262    if (isJust ohi && 
263         (mode == DoMake || mode == DoInteractive || length srcs > 1))
264         then throwDyn (UsageError "-ohi can only be used when compiling a single source file")
265         else do
266
267         -- make/interactive require invoking the compilation manager
268    if (mode == DoMake)        then beginMake srcs        else do
269    if (mode == DoInteractive) then beginInteractive srcs else do
270
271         -- -o sanity checking
272    o_file <- readIORef v_Output_file
273    if (length srcs > 1 && isJust o_file && mode /= DoLink && mode /= DoMkDLL)
274         then throwDyn (UsageError "can't apply -o to multiple source files")
275         else do
276
277    if null srcs then throwDyn (UsageError "no input files") else do
278
279    let compileFile src = do
280           restoreDynFlags
281
282           exists <- doesFileExist src
283           when (not exists) $ 
284                 throwDyn (CmdLineError ("file `" ++ src ++ "' does not exist"))
285
286           -- We compile in two stages, because the file may have an
287           -- OPTIONS pragma that affects the compilation pipeline (eg. -fvia-C)
288           let (basename, suffix) = splitFilename src
289
290           -- just preprocess (Haskell source only)
291           let src_and_suff = (src, getFileSuffix src)
292           pp <- if not (haskellish_src_file src) || mode == StopBefore Hsc
293                         then return src_and_suff else do
294                 phases <- genPipeline (StopBefore Hsc) stop_flag
295                             False{-not persistent-} defaultHscLang
296                             src_and_suff
297                 pipeLoop phases src_and_suff False{-no linking-} False{-no -o flag-}
298                         basename suffix
299
300           -- rest of compilation
301           hsc_lang <- dynFlag hscLang
302           phases   <- genPipeline mode stop_flag True hsc_lang pp
303           (r,_)    <- pipeLoop phases pp (mode==DoLink || mode==DoMkDLL)
304                                       True{-use -o flag-} basename suffix
305           return r
306
307    o_files <- mapM compileFile srcs
308
309    when (mode == DoMkDependHS) endMkDependHS
310    when (mode == DoLink) (doLink o_files)
311    when (mode == DoMkDLL) (doMkDLL o_files)
312
313
314
315 beginMake :: [String] -> IO ()
316 beginMake fileish_args
317   = do let (objs, mods) = partition objish_file fileish_args
318        mapM (add v_Ld_inputs) objs
319
320        case mods of
321          []    -> throwDyn (UsageError "no input files")
322          mod   -> do state <- cmInit Batch
323                      (_, ok, _) <- cmLoadModule state mods
324                      when (not ok) (exitWith (ExitFailure 1))
325                      return ()
326
327
328 beginInteractive :: [String] -> IO ()
329 #ifndef GHCI
330 beginInteractive = throwDyn (CmdLineError "not built for interactive use")
331 #else
332 beginInteractive fileish_args
333   = do minus_ls <- readIORef v_Cmdline_libraries
334
335        let (objs, mods) = partition objish_file fileish_args
336            libs = map Left objs ++ map Right minus_ls
337
338        state <- cmInit Interactive
339        interactiveUI state mods libs
340 #endif