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