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