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