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