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