Allow flags to be marked as deprecated
[ghc-hetmet.git] / compiler / main / Main.hs
1 {-# OPTIONS -fno-warn-incomplete-patterns -optc-DNON_POSIX_SOURCE #-}
2
3 -----------------------------------------------------------------------------
4 --
5 -- GHC Driver program
6 --
7 -- (c) The University of Glasgow 2005
8 --
9 -----------------------------------------------------------------------------
10
11 module Main (main) where
12
13 #include "HsVersions.h"
14
15 -- The official GHC API
16 import qualified GHC
17 import GHC              ( Session, DynFlags(..), HscTarget(..), 
18                           GhcMode(..), GhcLink(..),
19                           LoadHowMuch(..), dopt, DynFlag(..) )
20 import CmdLineParser
21
22 -- Implementations of the various modes (--show-iface, mkdependHS. etc.)
23 import LoadIface        ( showIface )
24 import HscMain          ( newHscEnv )
25 import DriverPipeline   ( oneShot, compileFile )
26 import DriverMkDepend   ( doMkDependHS )
27 #ifdef GHCI
28 import InteractiveUI    ( interactiveUI, ghciWelcomeMsg )
29 #endif
30
31 -- Various other random stuff that we need
32 import Config
33 import HscTypes
34 import Packages         ( dumpPackages )
35 import DriverPhases     ( Phase(..), isSourceFilename, anyHsc,
36                           startPhase, isHaskellSrcFilename )
37 import StaticFlags
38 import DynFlags
39 import BasicTypes       ( failed )
40 import ErrUtils
41 import FastString
42 import Outputable
43 import Util
44 import Panic
45
46 -- Standard Haskell libraries
47 import Control.Exception ( throwDyn )
48 import System.IO
49 import System.Directory ( doesDirectoryExist )
50 import System.Environment
51 import System.Exit
52 import System.FilePath
53 import Control.Monad
54 import Data.List
55 import Data.Maybe
56
57 -----------------------------------------------------------------------------
58 -- ToDo:
59
60 -- time commands when run with -v
61 -- user ways
62 -- Win32 support: proper signal handling
63 -- reading the package configuration file is too slow
64 -- -K<size>
65
66 -----------------------------------------------------------------------------
67 -- GHC's command-line interface
68
69 main :: IO ()
70 main =
71   GHC.defaultErrorHandler defaultDynFlags $ do
72   
73   -- 1. extract the -B flag from the args
74   argv0 <- getArgs
75
76   let
77         (minusB_args, argv1) = partition ("-B" `isPrefixOf`) argv0
78         mbMinusB | null minusB_args = Nothing
79                  | otherwise = Just (drop 2 (last minusB_args))
80
81   (argv2, staticFlagWarnings) <- parseStaticFlags argv1
82
83   -- 2. Parse the "mode" flags (--make, --interactive etc.)
84   (cli_mode, argv3, modeFlagWarnings) <- parseModeFlags argv2
85
86   -- If all we want to do is to show the version number then do it
87   -- now, before we start a GHC session etc.
88   -- If we do it later then bootstrapping gets confused as it tries
89   -- to find out what version of GHC it's using before package.conf
90   -- exists, so starting the session fails.
91   case cli_mode of
92     ShowInfo                -> do showInfo
93                                   exitWith ExitSuccess
94     ShowSupportedLanguages  -> do showSupportedLanguages
95                                   exitWith ExitSuccess
96     ShowVersion             -> do showVersion
97                                   exitWith ExitSuccess
98     ShowNumVersion          -> do putStrLn cProjectVersion
99                                   exitWith ExitSuccess
100     _                       -> return ()
101
102   -- start our GHC session
103   session <- GHC.newSession mbMinusB
104
105   dflags0 <- GHC.getSessionDynFlags session
106
107   -- set the default GhcMode, HscTarget and GhcLink.  The HscTarget
108   -- can be further adjusted on a module by module basis, using only
109   -- the -fvia-C and -fasm flags.  If the default HscTarget is not
110   -- HscC or HscAsm, -fvia-C and -fasm have no effect.
111   let dflt_target = hscTarget dflags0
112       (mode, lang, link)
113          = case cli_mode of
114                 DoInteractive   -> (CompManager, HscInterpreted, LinkInMemory)
115                 DoEval _        -> (CompManager, HscInterpreted, LinkInMemory)
116                 DoMake          -> (CompManager, dflt_target,    LinkBinary)
117                 DoMkDependHS    -> (MkDepend,    dflt_target,    LinkBinary)
118                 _               -> (OneShot,     dflt_target,    LinkBinary)
119
120   let dflags1 = dflags0{ ghcMode   = mode,
121                          hscTarget = lang,
122                          ghcLink   = link,
123                          -- leave out hscOutName for now
124                          hscOutName = panic "Main.main:hscOutName not set",
125                          verbosity = case cli_mode of
126                                          DoEval _ -> 0
127                                          _other   -> 1
128                         }
129
130         -- The rest of the arguments are "dynamic"
131         -- Leftover ones are presumably files
132   (dflags, fileish_args, dynamicFlagWarnings) <- GHC.parseDynamicFlags dflags1 argv3
133
134   let flagWarnings = staticFlagWarnings
135                   ++ modeFlagWarnings
136                   ++ dynamicFlagWarnings
137   handleFlagWarnings dflags flagWarnings
138
139         -- make sure we clean up after ourselves
140   GHC.defaultCleanupHandler dflags $ do
141
142   showBanner cli_mode dflags
143
144   -- we've finished manipulating the DynFlags, update the session
145   GHC.setSessionDynFlags session dflags
146   dflags  <- GHC.getSessionDynFlags session
147   hsc_env <- GHC.sessionHscEnv      session
148
149   let
150      -- To simplify the handling of filepaths, we normalise all filepaths right 
151      -- away - e.g., for win32 platforms, backslashes are converted
152      -- into forward slashes.
153     normal_fileish_paths = map normalise fileish_args
154     (srcs, objs)         = partition_args normal_fileish_paths [] []
155
156   -- Note: have v_Ld_inputs maintain the order in which 'objs' occurred on 
157   --       the command-line.
158   mapM_ (consIORef v_Ld_inputs) (reverse objs)
159
160         ---------------- Display configuration -----------
161   when (verbosity dflags >= 4) $
162         dumpPackages dflags
163
164   when (verbosity dflags >= 3) $ do
165         hPutStrLn stderr ("Hsc static flags: " ++ unwords staticFlags)
166
167         ---------------- Final sanity checking -----------
168   checkOptions cli_mode dflags srcs objs
169
170   ---------------- Do the business -----------
171   let alreadyHandled = panic (show cli_mode ++
172                               " should already have been handled")
173   case cli_mode of
174     ShowUsage              -> showGhcUsage dflags cli_mode
175     PrintLibdir            -> putStrLn (topDir dflags)
176     ShowSupportedLanguages -> alreadyHandled
177     ShowVersion            -> alreadyHandled
178     ShowNumVersion         -> alreadyHandled
179     ShowInterface f        -> doShowIface dflags f
180     DoMake                 -> doMake session srcs
181     DoMkDependHS           -> doMkDependHS session (map fst srcs)
182     StopBefore p           -> oneShot hsc_env p srcs
183     DoInteractive          -> interactiveUI session srcs Nothing
184     DoEval exprs           -> interactiveUI session srcs $ Just $ reverse exprs
185
186   dumpFinalStats dflags
187   exitWith ExitSuccess
188
189 #ifndef GHCI
190 interactiveUI :: a -> b -> c -> IO ()
191 interactiveUI _ _ _ = 
192   throwDyn (CmdLineError "not built for interactive use")
193 #endif
194
195 -- -----------------------------------------------------------------------------
196 -- Splitting arguments into source files and object files.  This is where we
197 -- interpret the -x <suffix> option, and attach a (Maybe Phase) to each source
198 -- file indicating the phase specified by the -x option in force, if any.
199
200 partition_args :: [String] -> [(String, Maybe Phase)] -> [String]
201                -> ([(String, Maybe Phase)], [String])
202 partition_args [] srcs objs = (reverse srcs, reverse objs)
203 partition_args ("-x":suff:args) srcs objs
204   | "none" <- suff      = partition_args args srcs objs
205   | StopLn <- phase     = partition_args args srcs (slurp ++ objs)
206   | otherwise           = partition_args rest (these_srcs ++ srcs) objs
207         where phase = startPhase suff
208               (slurp,rest) = break (== "-x") args 
209               these_srcs = zip slurp (repeat (Just phase))
210 partition_args (arg:args) srcs objs
211   | looks_like_an_input arg = partition_args args ((arg,Nothing):srcs) objs
212   | otherwise               = partition_args args srcs (arg:objs)
213
214     {-
215       We split out the object files (.o, .dll) and add them
216       to v_Ld_inputs for use by the linker.
217
218       The following things should be considered compilation manager inputs:
219
220        - haskell source files (strings ending in .hs, .lhs or other 
221          haskellish extension),
222
223        - module names (not forgetting hierarchical module names),
224
225        - and finally we consider everything not containing a '.' to be
226          a comp manager input, as shorthand for a .hs or .lhs filename.
227
228       Everything else is considered to be a linker object, and passed
229       straight through to the linker.
230     -}
231 looks_like_an_input :: String -> Bool
232 looks_like_an_input m =  isSourceFilename m 
233                       || looksLikeModuleName m
234                       || '.' `notElem` m
235
236 -- -----------------------------------------------------------------------------
237 -- Option sanity checks
238
239 checkOptions :: CmdLineMode -> DynFlags -> [(String,Maybe Phase)] -> [String] -> IO ()
240      -- Final sanity checking before kicking off a compilation (pipeline).
241 checkOptions cli_mode dflags srcs objs = do
242      -- Complain about any unknown flags
243    let unknown_opts = [ f | (f@('-':_), _) <- srcs ]
244    when (notNull unknown_opts) (unknownFlagsErr unknown_opts)
245
246    when (notNull (filter isRTSWay (wayNames dflags))
247          && isInterpretiveMode cli_mode) $
248         putStrLn ("Warning: -debug, -threaded and -ticky are ignored by GHCi")
249
250         -- -prof and --interactive are not a good combination
251    when (notNull (filter (not . isRTSWay) (wayNames dflags))
252          && isInterpretiveMode cli_mode) $
253       do throwDyn (UsageError 
254                    "--interactive can't be used with -prof or -unreg.")
255         -- -ohi sanity check
256    if (isJust (outputHi dflags) && 
257       (isCompManagerMode cli_mode || srcs `lengthExceeds` 1))
258         then throwDyn (UsageError "-ohi can only be used when compiling a single source file")
259         else do
260
261         -- -o sanity checking
262    if (srcs `lengthExceeds` 1 && isJust (outputFile dflags)
263          && not (isLinkMode cli_mode))
264         then throwDyn (UsageError "can't apply -o to multiple source files")
265         else do
266
267         -- Check that there are some input files
268         -- (except in the interactive case)
269    if null srcs && null objs && needsInputsMode cli_mode
270         then throwDyn (UsageError "no input files")
271         else do
272
273      -- Verify that output files point somewhere sensible.
274    verifyOutputFiles dflags
275
276
277 -- Compiler output options
278
279 -- called to verify that the output files & directories
280 -- point somewhere valid. 
281 --
282 -- The assumption is that the directory portion of these output
283 -- options will have to exist by the time 'verifyOutputFiles'
284 -- is invoked.
285 -- 
286 verifyOutputFiles :: DynFlags -> IO ()
287 verifyOutputFiles dflags = do
288   let odir = objectDir dflags
289   when (isJust odir) $ do
290      let dir = fromJust odir
291      flg <- doesDirectoryExist dir
292      when (not flg) (nonExistentDir "-odir" dir)
293   let ofile = outputFile dflags
294   when (isJust ofile) $ do
295      let fn = fromJust ofile
296      flg <- doesDirNameExist fn
297      when (not flg) (nonExistentDir "-o" fn)
298   let ohi = outputHi dflags
299   when (isJust ohi) $ do
300      let hi = fromJust ohi
301      flg <- doesDirNameExist hi
302      when (not flg) (nonExistentDir "-ohi" hi)
303  where
304    nonExistentDir flg dir = 
305      throwDyn (CmdLineError ("error: directory portion of " ++ 
306                              show dir ++ " does not exist (used with " ++ 
307                              show flg ++ " option.)"))
308
309 -----------------------------------------------------------------------------
310 -- GHC modes of operation
311
312 data CmdLineMode
313   = ShowUsage               -- ghc -?
314   | PrintLibdir             -- ghc --print-libdir
315   | ShowInfo                -- ghc --info
316   | ShowSupportedLanguages  -- ghc --supported-languages
317   | ShowVersion             -- ghc -V/--version
318   | ShowNumVersion          -- ghc --numeric-version
319   | ShowInterface String    -- ghc --show-iface
320   | DoMkDependHS            -- ghc -M
321   | StopBefore Phase        -- ghc -E | -C | -S
322                             -- StopBefore StopLn is the default
323   | DoMake                  -- ghc --make
324   | DoInteractive           -- ghc --interactive
325   | DoEval [String]         -- ghc -e foo -e bar => DoEval ["bar", "foo"]
326   deriving (Show)
327
328 #ifdef GHCI
329 isInteractiveMode :: CmdLineMode -> Bool
330 isInteractiveMode DoInteractive = True
331 isInteractiveMode _             = False
332 #endif
333
334 -- isInterpretiveMode: byte-code compiler involved
335 isInterpretiveMode :: CmdLineMode -> Bool
336 isInterpretiveMode DoInteractive = True
337 isInterpretiveMode (DoEval _)    = True
338 isInterpretiveMode _             = False
339
340 needsInputsMode :: CmdLineMode -> Bool
341 needsInputsMode DoMkDependHS    = True
342 needsInputsMode (StopBefore _)  = True
343 needsInputsMode DoMake          = True
344 needsInputsMode _               = False
345
346 -- True if we are going to attempt to link in this mode.
347 -- (we might not actually link, depending on the GhcLink flag)
348 isLinkMode :: CmdLineMode -> Bool
349 isLinkMode (StopBefore StopLn) = True
350 isLinkMode DoMake              = True
351 isLinkMode _                   = False
352
353 isCompManagerMode :: CmdLineMode -> Bool
354 isCompManagerMode DoMake        = True
355 isCompManagerMode DoInteractive = True
356 isCompManagerMode (DoEval _)    = True
357 isCompManagerMode _             = False
358
359
360 -- -----------------------------------------------------------------------------
361 -- Parsing the mode flag
362
363 parseModeFlags :: [String] -> IO (CmdLineMode, [String], [String])
364 parseModeFlags args = do
365   let ((leftover, errs, warns), (mode, _, flags)) = 
366          runCmdLine (processArgs mode_flags args) (StopBefore StopLn, "", []) 
367   when (not (null errs)) $ do
368     throwDyn (UsageError (unlines errs))
369   return (mode, flags ++ leftover, warns)
370
371 type ModeM = CmdLineP (CmdLineMode, String, [String])
372   -- mode flags sometimes give rise to new DynFlags (eg. -C, see below)
373   -- so we collect the new ones and return them.
374
375 mode_flags :: [Flag ModeM]
376 mode_flags =
377   [  ------- help / version ----------------------------------------------
378     Flag "?"                    (PassFlag (setMode ShowUsage))
379          Supported
380   , Flag "-help"                (PassFlag (setMode ShowUsage))
381          Supported
382   , Flag "-print-libdir"        (PassFlag (setMode PrintLibdir))
383          Supported
384   , Flag "V"                    (PassFlag (setMode ShowVersion))
385          Supported
386   , Flag "-version"             (PassFlag (setMode ShowVersion))
387          Supported
388   , Flag "-numeric-version"     (PassFlag (setMode ShowNumVersion))
389          Supported
390   , Flag "-info"                (PassFlag (setMode ShowInfo))
391          Supported
392   , Flag "-supported-languages" (PassFlag (setMode ShowSupportedLanguages))
393          Supported
394
395       ------- interfaces ----------------------------------------------------
396   , Flag "-show-iface"  (HasArg (\f -> setMode (ShowInterface f)
397                                                "--show-iface"))
398          Supported
399
400       ------- primary modes ------------------------------------------------
401   , Flag "M"            (PassFlag (setMode DoMkDependHS))
402          Supported
403   , Flag "E"            (PassFlag (setMode (StopBefore anyHsc)))
404          Supported
405   , Flag "C"            (PassFlag (\f -> do setMode (StopBefore HCc) f
406                                             addFlag "-fvia-C"))
407          Supported
408   , Flag "S"            (PassFlag (setMode (StopBefore As)))
409          Supported
410   , Flag "-make"        (PassFlag (setMode DoMake))
411          Supported
412   , Flag "-interactive" (PassFlag (setMode DoInteractive))
413          Supported
414   , Flag "e"            (HasArg   (\s -> updateMode (updateDoEval s) "-e"))
415          Supported
416
417        -- -fno-code says to stop after Hsc but don't generate any code.
418   , Flag "fno-code"     (PassFlag (\f -> do setMode (StopBefore HCc) f
419                                             addFlag "-fno-code"
420                                             addFlag "-no-recomp"))
421          Supported
422   ]
423
424 setMode :: CmdLineMode -> String -> ModeM ()
425 setMode m flag = updateMode (\_ -> m) flag
426
427 updateDoEval :: String -> CmdLineMode -> CmdLineMode
428 updateDoEval expr (DoEval exprs) = DoEval (expr : exprs)
429 updateDoEval expr _              = DoEval [expr]
430
431 updateMode :: (CmdLineMode -> CmdLineMode) -> String -> ModeM ()
432 updateMode f flag = do
433   (old_mode, old_flag, flags) <- getCmdLineState
434   if notNull old_flag && flag /= old_flag
435       then throwDyn (UsageError
436                ("cannot use `" ++ old_flag ++ "' with `" ++ flag ++ "'"))
437       else putCmdLineState (f old_mode, flag, flags)
438
439 addFlag :: String -> ModeM ()
440 addFlag s = do
441   (m, f, flags) <- getCmdLineState
442   putCmdLineState (m, f, s:flags)
443
444
445 -- ----------------------------------------------------------------------------
446 -- Run --make mode
447
448 doMake :: Session -> [(String,Maybe Phase)] -> IO ()
449 doMake _    []    = throwDyn (UsageError "no input files")
450 doMake sess srcs  = do 
451     let (hs_srcs, non_hs_srcs) = partition haskellish srcs
452
453         haskellish (f,Nothing) = 
454           looksLikeModuleName f || isHaskellSrcFilename f || '.' `notElem` f
455         haskellish (_,Just phase) = 
456           phase `notElem` [As, Cc, CmmCpp, Cmm, StopLn]
457
458     hsc_env <- GHC.sessionHscEnv sess
459     o_files <- mapM (compileFile hsc_env StopLn) non_hs_srcs
460     mapM_ (consIORef v_Ld_inputs) (reverse o_files)
461
462     targets <- mapM (uncurry GHC.guessTarget) hs_srcs
463     GHC.setTargets sess targets
464     ok_flag <- GHC.load sess LoadAllTargets
465     when (failed ok_flag) (exitWith (ExitFailure 1))
466     return ()
467
468
469 -- ---------------------------------------------------------------------------
470 -- --show-iface mode
471
472 doShowIface :: DynFlags -> FilePath -> IO ()
473 doShowIface dflags file = do
474   hsc_env <- newHscEnv dflags
475   showIface hsc_env file
476
477 -- ---------------------------------------------------------------------------
478 -- Various banners and verbosity output.
479
480 showBanner :: CmdLineMode -> DynFlags -> IO ()
481 showBanner _cli_mode dflags = do
482    let verb = verbosity dflags
483
484 #ifdef GHCI
485    -- Show the GHCi banner
486    when (isInteractiveMode _cli_mode && verb >= 1) $ putStrLn ghciWelcomeMsg
487 #endif
488
489    -- Display details of the configuration in verbose mode
490    when (verb >= 2) $
491     do hPutStr stderr "Glasgow Haskell Compiler, Version "
492        hPutStr stderr cProjectVersion
493        hPutStr stderr ", for Haskell 98, stage "
494        hPutStr stderr cStage
495        hPutStr stderr " booted by GHC version "
496        hPutStrLn stderr cBooterVersion
497
498 -- We print out a Read-friendly string, but a prettier one than the
499 -- Show instance gives us
500 showInfo :: IO ()
501 showInfo = do
502     let sq x = " [" ++ x ++ "\n ]"
503     putStrLn $ sq $ concat $ intersperse "\n ," $ map show compilerInfo
504     exitWith ExitSuccess
505
506 showSupportedLanguages :: IO ()
507 showSupportedLanguages = do mapM_ putStrLn supportedLanguages
508                             exitWith ExitSuccess
509
510 showVersion :: IO ()
511 showVersion = do
512   putStrLn (cProjectName ++ ", version " ++ cProjectVersion)
513   exitWith ExitSuccess
514
515 showGhcUsage :: DynFlags -> CmdLineMode -> IO ()
516 showGhcUsage dflags cli_mode = do 
517   let usage_path 
518         | DoInteractive <- cli_mode = ghciUsagePath dflags
519         | otherwise                 = ghcUsagePath dflags
520   usage <- readFile usage_path
521   dump usage
522   exitWith ExitSuccess
523   where
524      dump ""          = return ()
525      dump ('$':'$':s) = putStr progName >> dump s
526      dump (c:s)       = putChar c >> dump s
527
528 dumpFinalStats :: DynFlags -> IO ()
529 dumpFinalStats dflags = 
530   when (dopt Opt_D_faststring_stats dflags) $ dumpFastStringStats dflags
531
532 dumpFastStringStats :: DynFlags -> IO ()
533 dumpFastStringStats dflags = do
534   buckets <- getFastStringTable
535   let (entries, longest, is_z, has_z) = countFS 0 0 0 0 buckets
536       msg = text "FastString stats:" $$
537             nest 4 (vcat [text "size:           " <+> int (length buckets),
538                           text "entries:        " <+> int entries,
539                           text "longest chain:  " <+> int longest,
540                           text "z-encoded:      " <+> (is_z `pcntOf` entries),
541                           text "has z-encoding: " <+> (has_z `pcntOf` entries)
542                          ])
543         -- we usually get more "has z-encoding" than "z-encoded", because
544         -- when we z-encode a string it might hash to the exact same string,
545         -- which will is not counted as "z-encoded".  Only strings whose
546         -- Z-encoding is different from the original string are counted in
547         -- the "z-encoded" total.
548   putMsg dflags msg
549   where
550    x `pcntOf` y = int ((x * 100) `quot` y) <> char '%'
551
552 countFS :: Int -> Int -> Int -> Int -> [[FastString]] -> (Int, Int, Int, Int)
553 countFS entries longest is_z has_z [] = (entries, longest, is_z, has_z)
554 countFS entries longest is_z has_z (b:bs) = 
555   let
556         len = length b
557         longest' = max len longest
558         entries' = entries + len
559         is_zs = length (filter isZEncoded b)
560         has_zs = length (filter hasZEncoding b)
561   in
562         countFS entries' longest' (is_z + is_zs) (has_z + has_zs) bs
563
564 -- -----------------------------------------------------------------------------
565 -- Util
566
567 unknownFlagsErr :: [String] -> a
568 unknownFlagsErr fs = throwDyn (UsageError ("unrecognised flags: " ++ unwords fs))