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