[project @ 2004-11-26 16:19:45 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.141 2004/11/26 16:21:00 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/ghcconfig.h"
14
15 module Main (main) where
16
17 #include "HsVersions.h"
18
19
20 #ifdef GHCI
21 import InteractiveUI( ghciWelcomeMsg, interactiveUI )
22 #endif
23
24
25 import CompManager      ( cmInit, cmLoadModules, cmDepAnal )
26 import HscTypes         ( GhciMode(..) )
27 import Config           ( cBooterVersion, cGhcUnregisterised, cProjectVersion )
28 import SysTools         ( initSysTools, cleanTempFiles, normalisePath )
29 import Packages         ( dumpPackages, initPackages, haskell98PackageId )
30 import DriverPipeline   ( staticLink, doMkDLL, runPipeline )
31 import DriverState      ( buildStgToDo,
32                           findBuildTag, unregFlags, 
33                           v_GhcMode, v_GhcModeFlag, GhcMode(..),
34                           v_Keep_tmp_files, v_Ld_inputs, v_Ways, 
35                           v_Output_file, v_Output_hi, 
36                           verifyOutputFiles, v_NoLink
37                         )
38 import DriverFlags
39
40 import DriverMkDepend   ( beginMkDependHS, endMkDependHS )
41 import DriverPhases     ( isSourceFilename )
42
43 import DriverUtil       ( add, handle, handleDyn, later, unknownFlagsErr )
44 import CmdLineOpts      ( DynFlags(..), HscLang(..), v_Static_hsc_opts,
45                           defaultDynFlags )
46 import BasicTypes       ( failed )
47 import Outputable
48 import Util
49 import Panic            ( GhcException(..), panic, installSignalHandlers )
50
51 import DATA_IOREF       ( readIORef, writeIORef )
52 import EXCEPTION        ( throwDyn, Exception(..), 
53                           AsyncException(StackOverflow) )
54
55 -- Standard Haskell libraries
56 import IO
57 import Directory        ( doesFileExist )
58 import System           ( getArgs, exitWith, ExitCode(..) )
59 import Monad
60 import List
61 import Maybe
62
63 -----------------------------------------------------------------------------
64 -- ToDo:
65
66 -- new mkdependHS doesn't support all the options that the old one did (-X et al.)
67 -- time commands when run with -v
68 -- split marker
69 -- java generation
70 -- user ways
71 -- Win32 support: proper signal handling
72 -- make sure OPTIONS in .hs file propogate to .hc file if -C or -keep-hc-file-too
73 -- reading the package configuration file is too slow
74 -- -K<size>
75
76 -----------------------------------------------------------------------------
77 -- Differences vs. old driver:
78
79 -- No more "Enter your Haskell program, end with ^D (on a line of its own):"
80 -- consistency checking removed (may do this properly later)
81 -- no -Ofile
82
83 -----------------------------------------------------------------------------
84 -- Main loop
85
86 main =
87   -- top-level exception handler: any unrecognised exception is a compiler bug.
88   handle (\exception -> do
89            hFlush stdout
90            case exception of
91                 -- an IO exception probably isn't our fault, so don't panic
92                 IOException _ ->  hPutStrLn stderr (show exception)
93                 AsyncException StackOverflow ->
94                         hPutStrLn stderr "stack overflow: use +RTS -K<size> to increase it"
95                 _other ->  hPutStr stderr (show (Panic (show exception)))
96            exitWith (ExitFailure 1)
97          ) $ do
98
99   -- all error messages are propagated as exceptions
100   handleDyn (\dyn -> do
101                 hFlush stdout
102                 case dyn of
103                      PhaseFailed _ code -> exitWith code
104                      Interrupted -> exitWith (ExitFailure 1)
105                      _ -> do hPutStrLn stderr (show (dyn :: GhcException))
106                              exitWith (ExitFailure 1)
107             ) $ do
108
109    installSignalHandlers
110
111    argv <- getArgs
112    let (minusB_args, argv') = partition (prefixMatch "-B") argv
113    top_dir <- initSysTools minusB_args
114
115         -- Process all the other arguments, and get the source files
116    non_static <- processStaticFlags argv'
117    mode <- readIORef v_GhcMode
118
119         -- -O and --interactive are not a good combination
120         -- ditto with any kind of way selection
121    orig_ways <- readIORef v_Ways
122    when (notNull orig_ways && isInteractive mode) $
123       do throwDyn (UsageError 
124                    "--interactive can't be used with -prof, -ticky, -unreg or -smp.")
125
126         -- Find the build tag, and re-process the build-specific options.
127         -- Also add in flags for unregisterised compilation, if 
128         -- GhcUnregisterised=YES.
129    way_opts <- findBuildTag
130    let unreg_opts | cGhcUnregisterised == "YES" = unregFlags
131                   | otherwise = []
132    extra_non_static <- processStaticFlags (unreg_opts ++ way_opts)
133
134         -- Give the static flags to hsc
135    static_opts <- buildStaticHscOpts
136    writeIORef v_Static_hsc_opts static_opts
137
138    -- build the default DynFlags (these may be adjusted on a per
139    -- module basis by OPTIONS pragmas and settings in the interpreter).
140
141    stg_todo  <- buildStgToDo
142
143    -- set the "global" HscLang.  The HscLang can be further adjusted on a module
144    -- by module basis, using only the -fvia-C and -fasm flags.  If the global
145    -- HscLang is not HscC or HscAsm, -fvia-C and -fasm have no effect.
146    let dflags0 = defaultDynFlags
147    let lang = case mode of 
148                  DoInteractive  -> HscInterpreted
149                  DoEval _       -> HscInterpreted
150                  _other         -> hscLang dflags0
151
152    let dflags1 = dflags0{ stgToDo  = stg_todo,
153                           hscLang  = lang,
154                           -- leave out hscOutName for now
155                           hscOutName = panic "Main.main:hscOutName not set",
156                           verbosity = case mode of
157                                          DoEval _ -> 0
158                                          _other   -> 1
159                         }
160
161         -- The rest of the arguments are "dynamic"
162         -- Leftover ones are presumably files
163    (dflags2, fileish_args) <- processDynamicFlags 
164                                 (extra_non_static ++ non_static) dflags1
165
166         -- make sure we clean up after ourselves
167    later (do  forget_it <- readIORef v_Keep_tmp_files
168               unless forget_it $ do
169               cleanTempFiles dflags2
170      ) $ do
171         -- exceptions will be blocked while we clean the temporary files,
172         -- so there shouldn't be any difficulty if we receive further
173         -- signals.
174
175         -- Read the package config(s), and process the package-related
176         -- command-line flags
177    dflags <- initPackages dflags2
178
179    let
180     {-
181       We split out the object files (.o, .dll) and add them
182       to v_Ld_inputs for use by the linker.
183
184       The following things should be considered compilation manager inputs:
185
186        - haskell source files (strings ending in .hs, .lhs or other 
187          haskellish extension),
188
189        - module names (not forgetting hierarchical module names),
190
191        - and finally we consider everything not containing a '.' to be
192          a comp manager input, as shorthand for a .hs or .lhs filename.
193
194       Everything else is considered to be a linker object, and passed
195       straight through to the linker.
196     -}
197     looks_like_an_input m =  isSourceFilename m 
198                           || looksLikeModuleName m
199                           || '.' `notElem` m
200
201      -- To simplify the handling of filepaths, we normalise all filepaths right 
202      -- away - e.g., for win32 platforms, backslashes are converted
203      -- into forward slashes.
204     normal_fileish_paths = map normalisePath fileish_args
205     (srcs, objs)         = partition looks_like_an_input normal_fileish_paths
206
207     -- Note: have v_Ld_inputs maintain the order in which 'objs' occurred on 
208     --       the command-line.
209    mapM_ (add v_Ld_inputs) (reverse objs)
210
211         ---------------- Display banners and configuration -----------
212    showBanners mode dflags static_opts
213
214         ---------------- Final sanity checking -----------
215    checkOptions mode srcs objs
216
217         ---------------- Do the business -----------
218
219    -- Always link in the haskell98 package for static linking.  Other
220    -- packages have to be specified via the -package flag.
221    let link_pkgs
222           | Just h98_id <- haskell98PackageId (pkgState dflags) = [h98_id]
223           | otherwise = []
224
225    case mode of
226         DoMake         -> doMake dflags srcs
227                                
228         DoMkDependHS   -> do { beginMkDependHS ; 
229                                compileFiles mode dflags srcs; 
230                                endMkDependHS dflags }
231         StopBefore p   -> do { compileFiles mode dflags srcs; return () }
232         DoMkDLL        -> do { o_files <- compileFiles mode dflags srcs; 
233                                doMkDLL dflags o_files link_pkgs }
234         DoLink         -> do { o_files <- compileFiles mode dflags srcs; 
235                                omit_linking <- readIORef v_NoLink;
236                                when (not omit_linking)
237                                     (staticLink dflags o_files link_pkgs) }
238
239 #ifndef GHCI
240         DoInteractive -> noInteractiveError
241         DoEval _      -> noInteractiveError
242      where
243        noInteractiveError = throwDyn (CmdLineError "not built for interactive use")
244 #else
245         DoInteractive -> interactiveUI dflags srcs Nothing
246         DoEval expr   -> interactiveUI dflags srcs (Just expr)
247 #endif
248
249 -- -----------------------------------------------------------------------------
250 -- Option sanity checks
251
252 checkOptions :: GhcMode -> [String] -> [String] -> IO ()
253      -- Final sanity checking before kicking off a compilation (pipeline).
254 checkOptions mode srcs objs = do
255      -- Complain about any unknown flags
256    let unknown_opts = [ f | f@('-':_) <- srcs ]
257    when (notNull unknown_opts) (unknownFlagsErr unknown_opts)
258
259         -- -ohi sanity check
260    ohi <- readIORef v_Output_hi
261    if (isJust ohi && 
262       (mode == DoMake || isInteractive mode || srcs `lengthExceeds` 1))
263         then throwDyn (UsageError "-ohi can only be used when compiling a single source file")
264         else do
265
266         -- -o sanity checking
267    o_file <- readIORef v_Output_file
268    if (srcs `lengthExceeds` 1 && isJust o_file && mode /= DoLink && mode /= DoMkDLL)
269         then throwDyn (UsageError "can't apply -o to multiple source files")
270         else do
271
272         -- Check that there are some input files (except in the interactive 
273         -- case)
274    if null srcs && null objs && not (isInteractive mode)
275         then throwDyn (UsageError "no input files")
276         else do
277
278      -- Verify that output files point somewhere sensible.
279    verifyOutputFiles
280
281 isInteractive DoInteractive = True
282 isInteractive (DoEval _)    = True
283 isInteractive _             = False
284
285 -- -----------------------------------------------------------------------------
286 -- Compile files in one-shot mode.
287
288 compileFiles :: GhcMode
289              -> DynFlags
290              -> [String]        -- Source files
291              -> IO [String]     -- Object files
292 compileFiles mode dflags srcs = do
293    stop_flag <- readIORef v_GhcModeFlag
294    mapM (compileFile mode dflags stop_flag) srcs
295
296
297 compileFile mode dflags stop_flag src = do
298    exists <- doesFileExist src
299    when (not exists) $ 
300         throwDyn (CmdLineError ("file `" ++ src ++ "' does not exist"))
301    
302    o_file   <- readIORef v_Output_file
303         -- when linking, the -o argument refers to the linker's output. 
304         -- otherwise, we use it as the name for the pipeline's output.
305    let maybe_o_file
306           | mode==DoLink || mode==DoMkDLL  = Nothing
307           | otherwise                      = o_file
308
309    runPipeline mode dflags stop_flag True maybe_o_file src 
310                 Nothing{-no ModLocation-}
311
312
313 -- ----------------------------------------------------------------------------
314 -- Run --make mode
315
316 doMake :: DynFlags -> [String] -> IO ()
317 doMake dflags []    = throwDyn (UsageError "no input files")
318 doMake dflags srcs  = do 
319     state  <- cmInit Batch dflags
320     graph  <- cmDepAnal state srcs
321     (_, ok_flag, _) <- cmLoadModules state graph
322     when (failed ok_flag) (exitWith (ExitFailure 1))
323     return ()
324
325 -- ---------------------------------------------------------------------------
326 -- Various banners and verbosity output.
327
328 showBanners :: GhcMode -> DynFlags -> [String] -> IO ()
329 showBanners mode dflags static_opts = do
330    let verb = verbosity dflags
331
332         -- Show the GHCi banner
333 #  ifdef GHCI
334    when (mode == DoInteractive && verb >= 1) $
335       hPutStrLn stdout ghciWelcomeMsg
336 #  endif
337
338         -- Display details of the configuration in verbose mode
339    when (verb >= 2) $
340         do hPutStr stderr "Glasgow Haskell Compiler, Version "
341            hPutStr stderr cProjectVersion
342            hPutStr stderr ", for Haskell 98, compiled by GHC version "
343            hPutStrLn stderr cBooterVersion
344
345    when (verb >= 3) $
346         dumpPackages dflags
347
348    when (verb >= 3) $
349         hPutStrLn stderr ("Hsc static flags: " ++ unwords static_opts)