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