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