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