[project @ 2001-06-14 15:42:35 by simonpj]
[ghc-hetmet.git] / ghc / compiler / main / Main.hs
1 {-# OPTIONS -fno-warn-incomplete-patterns #-}
2 -----------------------------------------------------------------------------
3 -- $Id: Main.hs,v 1.71 2001/06/14 15:42:35 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 CmStaticInfo     ( GhciMode(..), PackageConfig(..) )
27 import Config           ( cBooterVersion, cGhcUnregisterised, cProjectVersion )
28 import SysTools         ( packageConfigPath, initSysTools, cleanTempFiles )
29 import ParsePkgConf     ( parsePkgConf )
30
31 import DriverPipeline   ( GhcMode(..), doLink, doMkDLL, genPipeline,
32                           getGhcMode, pipeLoop, v_GhcMode
33                         )
34 import DriverState      ( buildCoreToDo, buildStgToDo, defaultHscLang,
35                           findBuildTag, getPackageInfo, unregFlags, v_Cmdline_libraries,
36                           v_Keep_tmp_files, v_Ld_inputs, v_OptLevel, v_Output_file,
37                           v_Output_hi, v_Package_details, v_Ways
38                         )
39 import DriverFlags      ( dynFlag, buildStaticHscOpts, dynamic_flags, processArgs, static_flags)
40
41 import DriverMkDepend   ( beginMkDependHS, endMkDependHS )
42 import DriverPhases     ( Phase(Hsc, HCc), haskellish_src_file, objish_file )
43
44 import DriverUtil       ( add, handle, handleDyn, later, splitFilename, unknownFlagErr, my_prefix_match )
45 import CmdLineOpts      ( dynFlag,
46                           DynFlags(verbosity, stgToDo, hscOutName, hscLang, coreToDo),
47                           HscLang(HscInterpreted, HscC), 
48                           defaultDynFlags, restoreDynFlags, saveDynFlags, setDynFlags, 
49                           v_Static_hsc_opts
50                         )
51
52 import Outputable
53 import Util
54 import Panic            ( GhcException(..), panic )
55
56 -- Standard Haskell libraries
57 import IO
58 import Directory        ( doesFileExist )
59 import IOExts           ( readIORef, writeIORef )
60 import Exception        ( throwDyn, Exception(DynException) )
61 import System           ( getArgs, exitWith, ExitCode(..) )
62
63 #ifndef mingw32_TARGET_OS
64 import Concurrent       ( myThreadId, throwTo )
65 import Posix            ( Handler(Catch), installHandler, sigINT, sigQUIT )
66 import Dynamic          ( toDyn )
67 #endif
68
69 import Monad
70 import List
71 import Maybe
72
73
74 -----------------------------------------------------------------------------
75 -- Changes:
76
77 -- * -fglasgow-exts NO LONGER IMPLIES -package lang!!!  (-fglasgow-exts is a
78 --   dynamic flag whereas -package is a static flag.)
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 -- removed -noC
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 hPutStr stderr (show (Panic (show exception)))
107                            exitWith (ExitFailure 1)
108          ) $ do
109
110   -- all error messages are propagated as exceptions
111   handleDyn (\dyn -> case dyn of
112                           PhaseFailed _phase code -> exitWith code
113                           Interrupted -> exitWith (ExitFailure 1)
114                           _ -> do hPutStrLn stderr (show (dyn :: GhcException))
115                                   exitWith (ExitFailure 1)
116             ) $ do
117
118    -- make sure we clean up after ourselves
119    later (do  forget_it <- readIORef v_Keep_tmp_files
120               unless forget_it $ do
121               verb <- dynFlag verbosity
122               cleanTempFiles verb
123      ) $ do
124         -- exceptions will be blocked while we clean the temporary files,
125         -- so there shouldn't be any difficulty if we receive further
126         -- signals.
127
128         -- install signal handlers
129 #ifndef mingw32_TARGET_OS
130    main_thread <- myThreadId
131    let sig_handler = Catch (throwTo main_thread 
132                                 (DynException (toDyn Interrupted)))
133    installHandler sigQUIT sig_handler Nothing 
134    installHandler sigINT  sig_handler Nothing
135 #endif
136
137    argv <- getArgs
138    let (minusB_args, argv') = partition (prefixMatch "-B") argv
139    top_dir <- initSysTools minusB_args
140
141         -- read the package configuration
142    conf_file <- packageConfigPath
143    r         <- parsePkgConf conf_file
144    case r of {
145         Left err -> throwDyn (InstallationError (showSDoc err));
146         Right pkg_details -> do
147
148    writeIORef v_Package_details (mungePackagePaths top_dir pkg_details)
149
150         -- find the phase to stop after (i.e. -E, -C, -c, -S flags)
151    (flags2, mode, stop_flag) <- getGhcMode argv'
152    writeIORef v_GhcMode mode
153
154         -- Show the GHCi banner?
155 #  ifdef GHCI
156    when (mode == DoInteractive) $
157       hPutStrLn stdout ghciWelcomeMsg
158 #  endif
159
160         -- process all the other arguments, and get the source files
161    non_static <- processArgs static_flags flags2 []
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 (not (null 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    way_non_static <- processArgs static_flags (unreg_opts ++ way_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    opt_level  <- readIORef v_OptLevel
196
197
198    let lang = case mode of 
199                  StopBefore HCc -> HscC
200                  DoInteractive  -> HscInterpreted
201                  _other        | opt_level >= 1  -> HscC  -- -O implies -fvia-C 
202                                | otherwise       -> defaultHscLang
203
204    setDynFlags (defaultDynFlags{ coreToDo = core_todo,
205                                  stgToDo  = stg_todo,
206                                  hscLang  = lang,
207                                  -- leave out hscOutName for now
208                                  hscOutName = panic "Main.main:hscOutName not set",
209
210                                  verbosity = case mode of
211                                                 DoInteractive -> 1
212                                                 DoMake        -> 1
213                                                 _other        -> 0,
214                                 })
215
216         -- the rest of the arguments are "dynamic"
217    srcs <- processArgs dynamic_flags (way_non_static ++ non_static) []
218
219         -- save the "initial DynFlags" away
220    saveDynFlags
221
222         -- complain about any unknown flags
223    mapM unknownFlagErr [ f | f@('-':_) <- srcs ]
224
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         -- initialise the finder
240    pkg_avails <- getPackageInfo
241    initFinder pkg_avails
242
243         -- mkdependHS is special
244    when (mode == DoMkDependHS) beginMkDependHS
245
246         -- -ohi sanity checking
247    ohi    <- readIORef v_Output_hi
248    if (isJust ohi && 
249         (mode == DoMake || mode == DoInteractive || length srcs > 1))
250         then throwDyn (UsageError "-ohi can only be used when compiling a single source file")
251         else do
252
253         -- make/interactive require invoking the compilation manager
254    if (mode == DoMake)        then beginMake srcs        else do
255    if (mode == DoInteractive) then beginInteractive srcs else do
256
257         -- -o sanity checking
258    o_file <- readIORef v_Output_file
259    if (length srcs > 1 && isJust o_file && mode /= DoLink && mode /= DoMkDLL)
260         then throwDyn (UsageError "can't apply -o to multiple source files")
261         else do
262
263    if null srcs then throwDyn (UsageError "no input files") else do
264
265    let compileFile src = do
266           restoreDynFlags
267
268           exists <- doesFileExist src
269           when (not exists) $ 
270                 throwDyn (CmdLineError ("file `" ++ src ++ "' does not exist"))
271
272           -- We compile in two stages, because the file may have an
273           -- OPTIONS pragma that affects the compilation pipeline (eg. -fvia-C)
274           let (basename, suffix) = splitFilename src
275
276           -- just preprocess (Haskell source only)
277           pp <- if not (haskellish_src_file src) || mode == StopBefore Hsc
278                         then return src else do
279                 phases <- genPipeline (StopBefore Hsc) stop_flag
280                             False{-not persistent-} defaultHscLang src
281                 pipeLoop phases src 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) True{-use -o flag-}
288                         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 -- replace the string "$libdir" at the beginning of a path with the
300 -- current libdir (obtained from the -B option).
301 mungePackagePaths top_dir ps = map munge_pkg ps
302  where 
303   munge_pkg p = p{ import_dirs  = munge_paths (import_dirs p),
304                    include_dirs = munge_paths (include_dirs p),
305                    library_dirs = munge_paths (library_dirs p) }
306
307   munge_paths = map munge_path
308
309   munge_path p 
310           | Just p' <- my_prefix_match "$libdir" p = top_dir ++ p'
311           | otherwise = trace ("not: " ++ p) p
312
313
314 beginMake :: [String] -> IO ()
315 beginMake fileish_args
316   = do let (objs, mods) = partition objish_file fileish_args
317        mapM (add v_Ld_inputs) objs
318
319        case mods of
320          []    -> throwDyn (UsageError "no input files")
321          [mod] -> do state <- cmInit Batch
322                      cmLoadModule state mod
323                      return ()
324          _     -> throwDyn (UsageError "only one module allowed with --make")
325
326
327 beginInteractive :: [String] -> IO ()
328 #ifndef GHCI
329 beginInteractive = throwDyn (CmdLineError "not built for interactive use")
330 #else
331 beginInteractive fileish_args
332   = do minus_ls <- readIORef v_Cmdline_libraries
333
334        let (objs, mods) = partition objish_file fileish_args
335            libs = map Left objs ++ map Right minus_ls
336
337        state <- cmInit Interactive
338        case mods of
339           []    -> interactiveUI state Nothing    libs
340           [mod] -> interactiveUI state (Just mod) libs
341           _     -> throwDyn (UsageError 
342                              "only one module allowed with --interactive")
343 #endif