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