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