Cmm back end upgrades
[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         ( putMsg )
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 <- parseStaticFlags argv1
82
83   -- 2. Parse the "mode" flags (--make, --interactive etc.)
84   (cli_mode, argv3) <- 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) <- GHC.parseDynamicFlags dflags1 argv3
133
134         -- make sure we clean up after ourselves
135   GHC.defaultCleanupHandler dflags $ do
136
137   showBanner cli_mode dflags
138
139   -- we've finished manipulating the DynFlags, update the session
140   GHC.setSessionDynFlags session dflags
141   dflags  <- GHC.getSessionDynFlags session
142   hsc_env <- GHC.sessionHscEnv      session
143
144   let
145      -- To simplify the handling of filepaths, we normalise all filepaths right 
146      -- away - e.g., for win32 platforms, backslashes are converted
147      -- into forward slashes.
148     normal_fileish_paths = map normalise fileish_args
149     (srcs, objs)         = partition_args normal_fileish_paths [] []
150
151   -- Note: have v_Ld_inputs maintain the order in which 'objs' occurred on 
152   --       the command-line.
153   mapM_ (consIORef v_Ld_inputs) (reverse objs)
154
155         ---------------- Display configuration -----------
156   when (verbosity dflags >= 4) $
157         dumpPackages dflags
158
159   when (verbosity dflags >= 3) $ do
160         hPutStrLn stderr ("Hsc static flags: " ++ unwords staticFlags)
161
162         ---------------- Final sanity checking -----------
163   checkOptions cli_mode dflags srcs objs
164
165   ---------------- Do the business -----------
166   let alreadyHandled = panic (show cli_mode ++
167                               " should already have been handled")
168   case cli_mode of
169     ShowUsage              -> showGhcUsage dflags cli_mode
170     PrintLibdir            -> putStrLn (topDir dflags)
171     ShowSupportedLanguages -> alreadyHandled
172     ShowVersion            -> alreadyHandled
173     ShowNumVersion         -> alreadyHandled
174     ShowInterface f        -> doShowIface dflags f
175     DoMake                 -> doMake session srcs
176     DoMkDependHS           -> doMkDependHS session (map fst srcs)
177     StopBefore p           -> oneShot hsc_env p srcs
178     DoInteractive          -> interactiveUI session srcs Nothing
179     DoEval exprs           -> interactiveUI session srcs $ Just $ reverse exprs
180
181   dumpFinalStats dflags
182   exitWith ExitSuccess
183
184 #ifndef GHCI
185 interactiveUI :: a -> b -> c -> IO ()
186 interactiveUI _ _ _ = 
187   throwDyn (CmdLineError "not built for interactive use")
188 #endif
189
190 -- -----------------------------------------------------------------------------
191 -- Splitting arguments into source files and object files.  This is where we
192 -- interpret the -x <suffix> option, and attach a (Maybe Phase) to each source
193 -- file indicating the phase specified by the -x option in force, if any.
194
195 partition_args :: [String] -> [(String, Maybe Phase)] -> [String]
196                -> ([(String, Maybe Phase)], [String])
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 :: String -> Bool
227 looks_like_an_input m =  isSourceFilename m 
228                       || looksLikeModuleName m
229                       || '.' `notElem` m
230
231 -- -----------------------------------------------------------------------------
232 -- Option sanity checks
233
234 checkOptions :: CmdLineMode -> DynFlags -> [(String,Maybe Phase)] -> [String] -> IO ()
235      -- Final sanity checking before kicking off a compilation (pipeline).
236 checkOptions cli_mode dflags srcs objs = do
237      -- Complain about any unknown flags
238    let unknown_opts = [ f | (f@('-':_), _) <- srcs ]
239    when (notNull unknown_opts) (unknownFlagsErr unknown_opts)
240
241    when (notNull (filter isRTSWay (wayNames dflags))
242          && isInterpretiveMode cli_mode) $
243         putStrLn ("Warning: -debug, -threaded and -ticky are ignored by GHCi")
244
245         -- -prof and --interactive are not a good combination
246    when (notNull (filter (not . isRTSWay) (wayNames dflags))
247          && isInterpretiveMode cli_mode) $
248       do throwDyn (UsageError 
249                    "--interactive can't be used with -prof or -unreg.")
250         -- -ohi sanity check
251    if (isJust (outputHi dflags) && 
252       (isCompManagerMode cli_mode || srcs `lengthExceeds` 1))
253         then throwDyn (UsageError "-ohi can only be used when compiling a single source file")
254         else do
255
256         -- -o sanity checking
257    if (srcs `lengthExceeds` 1 && isJust (outputFile dflags)
258          && not (isLinkMode cli_mode))
259         then throwDyn (UsageError "can't apply -o to multiple source files")
260         else do
261
262         -- Check that there are some input files
263         -- (except in the interactive case)
264    if null srcs && null objs && needsInputsMode cli_mode
265         then throwDyn (UsageError "no input files")
266         else do
267
268      -- Verify that output files point somewhere sensible.
269    verifyOutputFiles dflags
270
271
272 -- Compiler output options
273
274 -- called to verify that the output files & directories
275 -- point somewhere valid. 
276 --
277 -- The assumption is that the directory portion of these output
278 -- options will have to exist by the time 'verifyOutputFiles'
279 -- is invoked.
280 -- 
281 verifyOutputFiles :: DynFlags -> IO ()
282 verifyOutputFiles dflags = do
283   let odir = objectDir dflags
284   when (isJust odir) $ do
285      let dir = fromJust odir
286      flg <- doesDirectoryExist dir
287      when (not flg) (nonExistentDir "-odir" dir)
288   let ofile = outputFile dflags
289   when (isJust ofile) $ do
290      let fn = fromJust ofile
291      flg <- doesDirNameExist fn
292      when (not flg) (nonExistentDir "-o" fn)
293   let ohi = outputHi dflags
294   when (isJust ohi) $ do
295      let hi = fromJust ohi
296      flg <- doesDirNameExist hi
297      when (not flg) (nonExistentDir "-ohi" hi)
298  where
299    nonExistentDir flg dir = 
300      throwDyn (CmdLineError ("error: directory portion of " ++ 
301                              show dir ++ " does not exist (used with " ++ 
302                              show flg ++ " option.)"))
303
304 -----------------------------------------------------------------------------
305 -- GHC modes of operation
306
307 data CmdLineMode
308   = ShowUsage               -- ghc -?
309   | PrintLibdir             -- ghc --print-libdir
310   | ShowInfo                -- ghc --info
311   | ShowSupportedLanguages  -- ghc --supported-languages
312   | ShowVersion             -- ghc -V/--version
313   | ShowNumVersion          -- ghc --numeric-version
314   | ShowInterface String    -- ghc --show-iface
315   | DoMkDependHS            -- ghc -M
316   | StopBefore Phase        -- ghc -E | -C | -S
317                             -- StopBefore StopLn is the default
318   | DoMake                  -- ghc --make
319   | DoInteractive           -- ghc --interactive
320   | DoEval [String]         -- ghc -e foo -e bar => DoEval ["bar", "foo"]
321   deriving (Show)
322
323 #ifdef GHCI
324 isInteractiveMode :: CmdLineMode -> Bool
325 isInteractiveMode DoInteractive = True
326 isInteractiveMode _             = False
327 #endif
328
329 -- isInterpretiveMode: byte-code compiler involved
330 isInterpretiveMode :: CmdLineMode -> Bool
331 isInterpretiveMode DoInteractive = True
332 isInterpretiveMode (DoEval _)    = True
333 isInterpretiveMode _             = False
334
335 needsInputsMode :: CmdLineMode -> Bool
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 :: CmdLineMode -> Bool
344 isLinkMode (StopBefore StopLn) = True
345 isLinkMode DoMake              = True
346 isLinkMode _                   = False
347
348 isCompManagerMode :: CmdLineMode -> Bool
349 isCompManagerMode DoMake        = True
350 isCompManagerMode DoInteractive = True
351 isCompManagerMode (DoEval _)    = True
352 isCompManagerMode _             = False
353
354
355 -- -----------------------------------------------------------------------------
356 -- Parsing the mode flag
357
358 parseModeFlags :: [String] -> IO (CmdLineMode, [String])
359 parseModeFlags args = do
360   let ((leftover, errs), (mode, _, flags)) = 
361          runCmdLine (processArgs mode_flags args) (StopBefore StopLn, "", []) 
362   when (not (null errs)) $ do
363     throwDyn (UsageError (unlines errs))
364   return (mode, flags ++ leftover)
365
366 type ModeM a = CmdLineP (CmdLineMode, String, [String]) a
367   -- mode flags sometimes give rise to new DynFlags (eg. -C, see below)
368   -- so we collect the new ones and return them.
369
370 mode_flags :: [(String, OptKind (CmdLineP (CmdLineMode, String, [String])))]
371 mode_flags =
372   [  ------- help / version ----------------------------------------------
373      ( "?"                   , PassFlag (setMode ShowUsage))
374   ,  ( "-help"               , PassFlag (setMode ShowUsage))
375   ,  ( "-print-libdir"       , PassFlag (setMode PrintLibdir))
376   ,  ( "V"                   , PassFlag (setMode ShowVersion))
377   ,  ( "-version"            , PassFlag (setMode ShowVersion))
378   ,  ( "-numeric-version"    , PassFlag (setMode ShowNumVersion))
379   ,  ( "-info"               , PassFlag (setMode ShowInfo))
380   ,  ( "-supported-languages", PassFlag (setMode ShowSupportedLanguages))
381
382       ------- interfaces ----------------------------------------------------
383   ,  ( "-show-iface"     , HasArg (\f -> setMode (ShowInterface f)
384                                                  "--show-iface"))
385
386       ------- primary modes ------------------------------------------------
387   ,  ( "M"              , PassFlag (setMode DoMkDependHS))
388   ,  ( "E"              , PassFlag (setMode (StopBefore anyHsc)))
389   ,  ( "C"              , PassFlag (\f -> do setMode (StopBefore HCc) f
390                                              addFlag "-fvia-C"))
391   ,  ( "S"              , PassFlag (setMode (StopBefore As)))
392   ,  ( "-make"          , PassFlag (setMode DoMake))
393   ,  ( "-interactive"   , PassFlag (setMode DoInteractive))
394   ,  ( "e"              , HasArg   (\s -> updateMode (updateDoEval s) "-e"))
395
396        -- -fno-code says to stop after Hsc but don't generate any code.
397   ,  ( "fno-code"       , PassFlag (\f -> do setMode (StopBefore HCc) f
398                                              addFlag "-fno-code"
399                                              addFlag "-no-recomp"))
400   ]
401
402 setMode :: CmdLineMode -> String -> ModeM ()
403 setMode m flag = updateMode (\_ -> m) flag
404
405 updateDoEval :: String -> CmdLineMode -> CmdLineMode
406 updateDoEval expr (DoEval exprs) = DoEval (expr : exprs)
407 updateDoEval expr _              = DoEval [expr]
408
409 updateMode :: (CmdLineMode -> CmdLineMode) -> String -> ModeM ()
410 updateMode f flag = do
411   (old_mode, old_flag, flags) <- getCmdLineState
412   if notNull old_flag && flag /= old_flag
413       then throwDyn (UsageError
414                ("cannot use `" ++ old_flag ++ "' with `" ++ flag ++ "'"))
415       else putCmdLineState (f old_mode, flag, flags)
416
417 addFlag :: String -> ModeM ()
418 addFlag s = do
419   (m, f, flags) <- getCmdLineState
420   putCmdLineState (m, f, s:flags)
421
422
423 -- ----------------------------------------------------------------------------
424 -- Run --make mode
425
426 doMake :: Session -> [(String,Maybe Phase)] -> IO ()
427 doMake _    []    = throwDyn (UsageError "no input files")
428 doMake sess srcs  = do 
429     let (hs_srcs, non_hs_srcs) = partition haskellish srcs
430
431         haskellish (f,Nothing) = 
432           looksLikeModuleName f || isHaskellSrcFilename f || '.' `notElem` f
433         haskellish (_,Just phase) = 
434           phase `notElem` [As, Cc, CmmCpp, Cmm, StopLn]
435
436     hsc_env <- GHC.sessionHscEnv sess
437     o_files <- mapM (compileFile hsc_env StopLn) non_hs_srcs
438     mapM_ (consIORef v_Ld_inputs) (reverse o_files)
439
440     targets <- mapM (uncurry GHC.guessTarget) hs_srcs
441     GHC.setTargets sess targets
442     ok_flag <- GHC.load sess LoadAllTargets
443     when (failed ok_flag) (exitWith (ExitFailure 1))
444     return ()
445
446
447 -- ---------------------------------------------------------------------------
448 -- --show-iface mode
449
450 doShowIface :: DynFlags -> FilePath -> IO ()
451 doShowIface dflags file = do
452   hsc_env <- newHscEnv dflags
453   showIface hsc_env file
454
455 -- ---------------------------------------------------------------------------
456 -- Various banners and verbosity output.
457
458 showBanner :: CmdLineMode -> DynFlags -> IO ()
459 showBanner _cli_mode dflags = do
460    let verb = verbosity dflags
461
462 #ifdef GHCI
463    -- Show the GHCi banner
464    when (isInteractiveMode _cli_mode && verb >= 1) $ putStrLn ghciWelcomeMsg
465 #endif
466
467    -- Display details of the configuration in verbose mode
468    when (verb >= 2) $
469     do hPutStr stderr "Glasgow Haskell Compiler, Version "
470        hPutStr stderr cProjectVersion
471        hPutStr stderr ", for Haskell 98, stage "
472        hPutStr stderr cStage
473        hPutStr stderr " booted by GHC version "
474        hPutStrLn stderr cBooterVersion
475
476 -- We print out a Read-friendly string, but a prettier one than the
477 -- Show instance gives us
478 showInfo :: IO ()
479 showInfo = do
480     let sq x = " [" ++ x ++ "\n ]"
481     putStrLn $ sq $ concat $ intersperse "\n ," $ map show compilerInfo
482     exitWith ExitSuccess
483
484 showSupportedLanguages :: IO ()
485 showSupportedLanguages = do mapM_ putStrLn supportedLanguages
486                             exitWith ExitSuccess
487
488 showVersion :: IO ()
489 showVersion = do
490   putStrLn (cProjectName ++ ", version " ++ cProjectVersion)
491   exitWith ExitSuccess
492
493 showGhcUsage :: DynFlags -> CmdLineMode -> IO ()
494 showGhcUsage dflags cli_mode = do 
495   let usage_path 
496         | DoInteractive <- cli_mode = ghciUsagePath dflags
497         | otherwise                 = ghcUsagePath dflags
498   usage <- readFile usage_path
499   dump usage
500   exitWith ExitSuccess
501   where
502      dump ""          = return ()
503      dump ('$':'$':s) = putStr progName >> dump s
504      dump (c:s)       = putChar c >> dump s
505
506 dumpFinalStats :: DynFlags -> IO ()
507 dumpFinalStats dflags = 
508   when (dopt Opt_D_faststring_stats dflags) $ dumpFastStringStats dflags
509
510 dumpFastStringStats :: DynFlags -> IO ()
511 dumpFastStringStats dflags = do
512   buckets <- getFastStringTable
513   let (entries, longest, is_z, has_z) = countFS 0 0 0 0 buckets
514       msg = text "FastString stats:" $$
515             nest 4 (vcat [text "size:           " <+> int (length buckets),
516                           text "entries:        " <+> int entries,
517                           text "longest chain:  " <+> int longest,
518                           text "z-encoded:      " <+> (is_z `pcntOf` entries),
519                           text "has z-encoding: " <+> (has_z `pcntOf` entries)
520                          ])
521         -- we usually get more "has z-encoding" than "z-encoded", because
522         -- when we z-encode a string it might hash to the exact same string,
523         -- which will is not counted as "z-encoded".  Only strings whose
524         -- Z-encoding is different from the original string are counted in
525         -- the "z-encoded" total.
526   putMsg dflags msg
527   where
528    x `pcntOf` y = int ((x * 100) `quot` y) <> char '%'
529
530 countFS :: Int -> Int -> Int -> Int -> [[FastString]] -> (Int, Int, Int, Int)
531 countFS entries longest is_z has_z [] = (entries, longest, is_z, has_z)
532 countFS entries longest is_z has_z (b:bs) = 
533   let
534         len = length b
535         longest' = max len longest
536         entries' = entries + len
537         is_zs = length (filter isZEncoded b)
538         has_zs = length (filter hasZEncoding b)
539   in
540         countFS entries' longest' (is_z + is_zs) (has_z + has_zs) bs
541
542 -- -----------------------------------------------------------------------------
543 -- Util
544
545 unknownFlagsErr :: [String] -> a
546 unknownFlagsErr fs = throwDyn (UsageError ("unrecognised flags: " ++ unwords fs))