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