[project @ 2001-06-15 08:29:57 by simonpj]
[ghc-hetmet.git] / ghc / compiler / main / Main.hs
1 {-# OPTIONS -fno-warn-incomplete-patterns #-}
2 -----------------------------------------------------------------------------
3 -- $Id: Main.hs,v 1.72 2001/06/15 08:29:58 simonpj 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, v_Cmdline_libraries,
37                           v_Keep_tmp_files, v_Ld_inputs, v_OptLevel, v_Output_file,
38                           v_Output_hi, v_Package_details, v_Ways
39                         )
40 import DriverFlags      ( dynFlag, buildStaticHscOpts, dynamic_flags, processArgs, static_flags)
41
42 import DriverMkDepend   ( beginMkDependHS, endMkDependHS )
43 import DriverPhases     ( Phase(Hsc, HCc), haskellish_src_file, objish_file )
44
45 import DriverUtil       ( add, handle, handleDyn, later, splitFilename, unknownFlagErr, my_prefix_match )
46 import CmdLineOpts      ( dynFlag,
47                           DynFlags(verbosity, stgToDo, hscOutName, hscLang, coreToDo),
48                           HscLang(HscInterpreted, HscC), 
49                           defaultDynFlags, restoreDynFlags, saveDynFlags, setDynFlags, 
50                           v_Static_hsc_opts
51                         )
52
53 import Outputable
54 import ErrUtils         ( dumpIfSet )
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(DynException) )
63 import System           ( getArgs, exitWith, ExitCode(..) )
64
65 #ifndef mingw32_TARGET_OS
66 import Concurrent       ( myThreadId, throwTo )
67 import Posix            ( Handler(Catch), installHandler, sigINT, sigQUIT )
68 import Dynamic          ( toDyn )
69 #endif
70
71 import Monad
72 import List
73 import Maybe
74
75
76 -----------------------------------------------------------------------------
77 -- Changes:
78
79 -- * -fglasgow-exts NO LONGER IMPLIES -package lang!!!  (-fglasgow-exts is a
80 --   dynamic flag whereas -package is a static flag.)
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 -- removed -noC
101 -- no -Ofile
102
103 -----------------------------------------------------------------------------
104 -- Main loop
105
106 main =
107   -- top-level exception handler: any unrecognised exception is a compiler bug.
108   handle (\exception -> do hPutStr stderr (show (Panic (show exception)))
109                            exitWith (ExitFailure 1)
110          ) $ do
111
112   -- all error messages are propagated as exceptions
113   handleDyn (\dyn -> case dyn of
114                           PhaseFailed _phase code -> exitWith code
115                           Interrupted -> exitWith (ExitFailure 1)
116                           _ -> do hPutStrLn stderr (show (dyn :: GhcException))
117                                   exitWith (ExitFailure 1)
118             ) $ do
119
120    -- make sure we clean up after ourselves
121    later (do  forget_it <- readIORef v_Keep_tmp_files
122               unless forget_it $ do
123               verb <- dynFlag verbosity
124               cleanTempFiles verb
125      ) $ do
126         -- exceptions will be blocked while we clean the temporary files,
127         -- so there shouldn't be any difficulty if we receive further
128         -- signals.
129
130         -- install signal handlers
131 #ifndef mingw32_TARGET_OS
132    main_thread <- myThreadId
133    let sig_handler = Catch (throwTo main_thread 
134                                 (DynException (toDyn Interrupted)))
135    installHandler sigQUIT sig_handler Nothing 
136    installHandler sigINT  sig_handler Nothing
137 #endif
138
139    argv <- getArgs
140    let (minusB_args, argv') = partition (prefixMatch "-B") argv
141    top_dir <- initSysTools minusB_args
142
143         -- Read the package configuration
144    conf_file         <- packageConfigPath
145    proto_pkg_details <- loadPackageConfig conf_file
146    let pkg_details    = mungePackagePaths top_dir proto_pkg_details
147    writeIORef v_Package_details pkg_details
148
149         -- find the phase to stop after (i.e. -E, -C, -c, -S flags)
150    (flags2, mode, stop_flag) <- getGhcMode argv'
151    writeIORef v_GhcMode mode
152
153         -- Show the GHCi banner?
154 #  ifdef GHCI
155    when (mode == DoInteractive) $
156       hPutStrLn stdout ghciWelcomeMsg
157 #  endif
158
159         -- process all the other arguments, and get the source files
160    non_static <- processArgs static_flags flags2 []
161
162         -- -O and --interactive are not a good combination
163         -- ditto with any kind of way selection
164    orig_opt_level <- readIORef v_OptLevel
165    when (orig_opt_level > 0 && mode == DoInteractive) $
166       do putStr "warning: -O conflicts with --interactive; -O turned off.\n"
167          writeIORef v_OptLevel 0
168    orig_ways <- readIORef v_Ways
169    when (not (null orig_ways) && mode == DoInteractive) $
170       do throwDyn (UsageError 
171                    "--interactive can't be used with -prof, -ticky, -unreg or -smp.")
172
173         -- Find the build tag, and re-process the build-specific options.
174         -- Also add in flags for unregisterised compilation, if 
175         -- GhcUnregisterised=YES.
176    way_opts <- findBuildTag
177    let unreg_opts | cGhcUnregisterised == "YES" = unregFlags
178                   | otherwise = []
179    way_non_static <- processArgs static_flags (unreg_opts ++ way_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    opt_level  <- readIORef v_OptLevel
195
196
197    let lang = case mode of 
198                  StopBefore HCc -> HscC
199                  DoInteractive  -> HscInterpreted
200                  _other        | opt_level >= 1  -> HscC  -- -O implies -fvia-C 
201                                | otherwise       -> defaultHscLang
202
203    setDynFlags (defaultDynFlags{ coreToDo = core_todo,
204                                  stgToDo  = stg_todo,
205                                  hscLang  = lang,
206                                  -- leave out hscOutName for now
207                                  hscOutName = panic "Main.main:hscOutName not set",
208
209                                  verbosity = case mode of
210                                                 DoInteractive -> 1
211                                                 DoMake        -> 1
212                                                 _other        -> 0,
213                                 })
214
215         -- the rest of the arguments are "dynamic"
216    srcs <- processArgs dynamic_flags (way_non_static ++ non_static) []
217
218         -- save the "initial DynFlags" away
219    saveDynFlags
220
221         -- complain about any unknown flags
222    mapM unknownFlagErr [ f | f@('-':_) <- srcs ]
223
224         -- Display details of the configuration in verbose mode
225    verb <- dynFlag verbosity
226
227    when (verb >= 2) 
228         (do hPutStr stderr "Glasgow Haskell Compiler, Version "
229             hPutStr stderr cProjectVersion
230             hPutStr stderr ", for Haskell 98, compiled by GHC version "
231             hPutStrLn stderr cBooterVersion)
232
233    when (verb >= 2) 
234         (hPutStrLn stderr ("Using package config file: " ++ conf_file))
235
236    when (verb >= 3) 
237         (hPutStrLn stderr ("Hsc static flags: " ++ unwords static_opts))
238
239    showPackages pkg_details
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 || length srcs > 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 (length srcs > 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           pp <- if not (haskellish_src_file src) || mode == StopBefore Hsc
280                         then return src else do
281                 phases <- genPipeline (StopBefore Hsc) stop_flag
282                             False{-not persistent-} defaultHscLang src
283                 pipeLoop phases src False{-no linking-} False{-no -o flag-}
284                         basename suffix
285
286           -- rest of compilation
287           hsc_lang <- dynFlag hscLang
288           phases <- genPipeline mode stop_flag True hsc_lang pp
289           r <- pipeLoop phases pp (mode==DoLink || mode==DoMkDLL) True{-use -o flag-}
290                         basename suffix
291           return r
292
293    o_files <- mapM compileFile srcs
294
295    when (mode == DoMkDependHS) endMkDependHS
296    when (mode == DoLink) (doLink o_files)
297    when (mode == DoMkDLL) (doMkDLL o_files)
298
299
300
301 beginMake :: [String] -> IO ()
302 beginMake fileish_args
303   = do let (objs, mods) = partition objish_file fileish_args
304        mapM (add v_Ld_inputs) objs
305
306        case mods of
307          []    -> throwDyn (UsageError "no input files")
308          [mod] -> do state <- cmInit Batch
309                      cmLoadModule state mod
310                      return ()
311          _     -> throwDyn (UsageError "only one module allowed with --make")
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        case mods of
326           []    -> interactiveUI state Nothing    libs
327           [mod] -> interactiveUI state (Just mod) libs
328           _     -> throwDyn (UsageError 
329                              "only one module allowed with --interactive")
330 #endif