Fix for 1st half of #2203
[ghc-hetmet.git] / ghc / 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.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, staticFlagWarnings) <- parseStaticFlags argv1
81
82   -- 2. Parse the "mode" flags (--make, --interactive etc.)
83   (cli_mode, argv3, modeFlagWarnings) <- 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   (dflags2, fileish_args, dynamicFlagWarnings) <- GHC.parseDynamicFlags dflags1 argv3
132
133   let flagWarnings = staticFlagWarnings
134                   ++ modeFlagWarnings
135                   ++ dynamicFlagWarnings
136   handleFlagWarnings dflags2 flagWarnings
137
138         -- make sure we clean up after ourselves
139   GHC.defaultCleanupHandler dflags2 $ do
140
141   showBanner cli_mode dflags2
142
143   -- we've finished manipulating the DynFlags, update the session
144   GHC.setSessionDynFlags session dflags2
145   dflags3 <- GHC.getSessionDynFlags session
146   hsc_env <- GHC.sessionHscEnv      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 normalise 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 dflags3 >= 4) $
161         dumpPackages dflags3
162
163   when (verbosity dflags3 >= 3) $ do
164         hPutStrLn stderr ("Hsc static flags: " ++ unwords staticFlags)
165
166         ---------------- Final sanity checking -----------
167   checkOptions cli_mode dflags3 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 dflags3 cli_mode
174     PrintLibdir            -> putStrLn (topDir dflags3)
175     ShowSupportedLanguages -> alreadyHandled
176     ShowVersion            -> alreadyHandled
177     ShowNumVersion         -> alreadyHandled
178     ShowInterface f        -> doShowIface dflags3 f
179     DoMake                 -> doMake session srcs
180     DoMkDependHS           -> doMkDependHS session (map fst srcs)
181     StopBefore p           -> oneShot hsc_env p srcs
182     DoInteractive          -> interactiveUI session srcs Nothing
183     DoEval exprs           -> interactiveUI session srcs $ Just $ reverse exprs
184
185   dumpFinalStats dflags3
186   exitWith ExitSuccess
187
188 #ifndef GHCI
189 interactiveUI :: a -> b -> c -> IO ()
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 :: [String] -> [(String, Maybe Phase)] -> [String]
200                -> ([(String, Maybe Phase)], [String])
201 partition_args [] srcs objs = (reverse srcs, reverse objs)
202 partition_args ("-x":suff:args) srcs objs
203   | "none" <- suff      = partition_args args srcs objs
204   | StopLn <- phase     = partition_args args srcs (slurp ++ objs)
205   | otherwise           = partition_args rest (these_srcs ++ srcs) objs
206         where phase = startPhase suff
207               (slurp,rest) = break (== "-x") args 
208               these_srcs = zip slurp (repeat (Just phase))
209 partition_args (arg:args) srcs objs
210   | looks_like_an_input arg = partition_args args ((arg,Nothing):srcs) objs
211   | otherwise               = partition_args args srcs (arg:objs)
212
213     {-
214       We split out the object files (.o, .dll) and add them
215       to v_Ld_inputs for use by the linker.
216
217       The following things should be considered compilation manager inputs:
218
219        - haskell source files (strings ending in .hs, .lhs or other 
220          haskellish extension),
221
222        - module names (not forgetting hierarchical module names),
223
224        - and finally we consider everything not containing a '.' to be
225          a comp manager input, as shorthand for a .hs or .lhs filename.
226
227       Everything else is considered to be a linker object, and passed
228       straight through to the linker.
229     -}
230 looks_like_an_input :: String -> Bool
231 looks_like_an_input m =  isSourceFilename m 
232                       || looksLikeModuleName m
233                       || '.' `notElem` m
234
235 -- -----------------------------------------------------------------------------
236 -- Option sanity checks
237
238 checkOptions :: CmdLineMode -> DynFlags -> [(String,Maybe Phase)] -> [String] -> IO ()
239      -- Final sanity checking before kicking off a compilation (pipeline).
240 checkOptions cli_mode dflags srcs objs = do
241      -- Complain about any unknown flags
242    let unknown_opts = [ f | (f@('-':_), _) <- srcs ]
243    when (notNull unknown_opts) (unknownFlagsErr unknown_opts)
244
245    when (notNull (filter isRTSWay (wayNames dflags))
246          && isInterpretiveMode cli_mode) $
247         putStrLn ("Warning: -debug, -threaded and -ticky are ignored by GHCi")
248
249         -- -prof and --interactive are not a good combination
250    when (notNull (filter (not . isRTSWay) (wayNames dflags))
251          && isInterpretiveMode cli_mode) $
252       do throwDyn (UsageError 
253                    "--interactive can't be used with -prof or -unreg.")
254         -- -ohi sanity check
255    if (isJust (outputHi dflags) && 
256       (isCompManagerMode cli_mode || srcs `lengthExceeds` 1))
257         then throwDyn (UsageError "-ohi can only be used when compiling a single source file")
258         else do
259
260         -- -o sanity checking
261    if (srcs `lengthExceeds` 1 && isJust (outputFile dflags)
262          && not (isLinkMode cli_mode))
263         then throwDyn (UsageError "can't apply -o to multiple source files")
264         else do
265
266         -- Check that there are some input files
267         -- (except in the interactive case)
268    if null srcs && null objs && needsInputsMode cli_mode
269         then throwDyn (UsageError "no input files")
270         else do
271
272      -- Verify that output files point somewhere sensible.
273    verifyOutputFiles dflags
274
275
276 -- Compiler output options
277
278 -- called to verify that the output files & directories
279 -- point somewhere valid. 
280 --
281 -- The assumption is that the directory portion of these output
282 -- options will have to exist by the time 'verifyOutputFiles'
283 -- is invoked.
284 -- 
285 verifyOutputFiles :: DynFlags -> IO ()
286 verifyOutputFiles dflags = do
287   -- not -odir: we create the directory for -odir if it doesn't exist (#2278).
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], [String])
359 parseModeFlags args = do
360   let ((leftover, errs, warns), (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, warns)
365
366 type ModeM = CmdLineP (CmdLineMode, String, [String])
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 :: [Flag ModeM]
371 mode_flags =
372   [  ------- help / version ----------------------------------------------
373     Flag "?"                    (PassFlag (setMode ShowUsage))
374          Supported
375   , Flag "-help"                (PassFlag (setMode ShowUsage))
376          Supported
377   , Flag "-print-libdir"        (PassFlag (setMode PrintLibdir))
378          Supported
379   , Flag "V"                    (PassFlag (setMode ShowVersion))
380          Supported
381   , Flag "-version"             (PassFlag (setMode ShowVersion))
382          Supported
383   , Flag "-numeric-version"     (PassFlag (setMode ShowNumVersion))
384          Supported
385   , Flag "-info"                (PassFlag (setMode ShowInfo))
386          Supported
387   , Flag "-supported-languages" (PassFlag (setMode ShowSupportedLanguages))
388          Supported
389
390       ------- interfaces ----------------------------------------------------
391   , Flag "-show-iface"  (HasArg (\f -> setMode (ShowInterface f)
392                                                "--show-iface"))
393          Supported
394
395       ------- primary modes ------------------------------------------------
396   , Flag "M"            (PassFlag (setMode DoMkDependHS))
397          Supported
398   , Flag "E"            (PassFlag (setMode (StopBefore anyHsc)))
399          Supported
400   , Flag "C"            (PassFlag (\f -> do setMode (StopBefore HCc) f
401                                             addFlag "-fvia-C"))
402          Supported
403   , Flag "S"            (PassFlag (setMode (StopBefore As)))
404          Supported
405   , Flag "-make"        (PassFlag (setMode DoMake))
406          Supported
407   , Flag "-interactive" (PassFlag (setMode DoInteractive))
408          Supported
409   , Flag "e"            (HasArg   (\s -> updateMode (updateDoEval s) "-e"))
410          Supported
411
412        -- -fno-code says to stop after Hsc but don't generate any code.
413   , Flag "fno-code"     (PassFlag (\f -> do setMode (StopBefore HCc) f
414                                             addFlag "-fno-code"
415                                             addFlag "-fforce-recomp"))
416          Supported
417   ]
418
419 setMode :: CmdLineMode -> String -> ModeM ()
420 setMode m flag = updateMode (\_ -> m) flag
421
422 updateDoEval :: String -> CmdLineMode -> CmdLineMode
423 updateDoEval expr (DoEval exprs) = DoEval (expr : exprs)
424 updateDoEval expr _              = DoEval [expr]
425
426 updateMode :: (CmdLineMode -> CmdLineMode) -> String -> ModeM ()
427 updateMode f flag = do
428   (old_mode, old_flag, flags') <- getCmdLineState
429   if notNull old_flag && flag /= old_flag
430       then throwDyn (UsageError
431                ("cannot use `" ++ old_flag ++ "' with `" ++ flag ++ "'"))
432       else putCmdLineState (f old_mode, flag, flags')
433
434 addFlag :: String -> ModeM ()
435 addFlag s = do
436   (m, f, flags') <- getCmdLineState
437   putCmdLineState (m, f, s:flags')
438
439
440 -- ----------------------------------------------------------------------------
441 -- Run --make mode
442
443 doMake :: Session -> [(String,Maybe Phase)] -> IO ()
444 doMake _    []    = throwDyn (UsageError "no input files")
445 doMake sess srcs  = do 
446     let (hs_srcs, non_hs_srcs) = partition haskellish srcs
447
448         haskellish (f,Nothing) = 
449           looksLikeModuleName f || isHaskellSrcFilename f || '.' `notElem` f
450         haskellish (_,Just phase) = 
451           phase `notElem` [As, Cc, CmmCpp, Cmm, StopLn]
452
453     hsc_env <- GHC.sessionHscEnv sess
454     o_files <- mapM (compileFile hsc_env StopLn) non_hs_srcs
455     mapM_ (consIORef v_Ld_inputs) (reverse o_files)
456
457     targets <- mapM (uncurry GHC.guessTarget) hs_srcs
458     GHC.setTargets sess targets
459     ok_flag <- GHC.load sess LoadAllTargets
460     when (failed ok_flag) (exitWith (ExitFailure 1))
461     return ()
462
463
464 -- ---------------------------------------------------------------------------
465 -- --show-iface mode
466
467 doShowIface :: DynFlags -> FilePath -> IO ()
468 doShowIface dflags file = do
469   hsc_env <- newHscEnv dflags
470   showIface hsc_env file
471
472 -- ---------------------------------------------------------------------------
473 -- Various banners and verbosity output.
474
475 showBanner :: CmdLineMode -> DynFlags -> IO ()
476 showBanner _cli_mode dflags = do
477    let verb = verbosity dflags
478
479 #ifdef GHCI
480    -- Show the GHCi banner
481    when (isInteractiveMode _cli_mode && verb >= 1) $ putStrLn ghciWelcomeMsg
482 #endif
483
484    -- Display details of the configuration in verbose mode
485    when (verb >= 2) $
486     do hPutStr stderr "Glasgow Haskell Compiler, Version "
487        hPutStr stderr cProjectVersion
488        hPutStr stderr ", for Haskell 98, stage "
489        hPutStr stderr cStage
490        hPutStr stderr " booted by GHC version "
491        hPutStrLn stderr cBooterVersion
492
493 -- We print out a Read-friendly string, but a prettier one than the
494 -- Show instance gives us
495 showInfo :: IO ()
496 showInfo = do
497     let sq x = " [" ++ x ++ "\n ]"
498     putStrLn $ sq $ concat $ intersperse "\n ," $ map show compilerInfo
499     exitWith ExitSuccess
500
501 showSupportedLanguages :: IO ()
502 showSupportedLanguages = do mapM_ putStrLn supportedLanguages
503                             exitWith ExitSuccess
504
505 showVersion :: IO ()
506 showVersion = do
507   putStrLn (cProjectName ++ ", version " ++ cProjectVersion)
508   exitWith ExitSuccess
509
510 showGhcUsage :: DynFlags -> CmdLineMode -> IO ()
511 showGhcUsage dflags cli_mode = do 
512   let usage_path 
513         | DoInteractive <- cli_mode = ghciUsagePath dflags
514         | otherwise                 = ghcUsagePath dflags
515   usage <- readFile usage_path
516   dump usage
517   exitWith ExitSuccess
518   where
519      dump ""          = return ()
520      dump ('$':'$':s) = putStr progName >> dump s
521      dump (c:s)       = putChar c >> dump s
522
523 dumpFinalStats :: DynFlags -> IO ()
524 dumpFinalStats dflags = 
525   when (dopt Opt_D_faststring_stats dflags) $ dumpFastStringStats dflags
526
527 dumpFastStringStats :: DynFlags -> IO ()
528 dumpFastStringStats dflags = do
529   buckets <- getFastStringTable
530   let (entries, longest, is_z, has_z) = countFS 0 0 0 0 buckets
531       msg = text "FastString stats:" $$
532             nest 4 (vcat [text "size:           " <+> int (length buckets),
533                           text "entries:        " <+> int entries,
534                           text "longest chain:  " <+> int longest,
535                           text "z-encoded:      " <+> (is_z `pcntOf` entries),
536                           text "has z-encoding: " <+> (has_z `pcntOf` entries)
537                          ])
538         -- we usually get more "has z-encoding" than "z-encoded", because
539         -- when we z-encode a string it might hash to the exact same string,
540         -- which will is not counted as "z-encoded".  Only strings whose
541         -- Z-encoding is different from the original string are counted in
542         -- the "z-encoded" total.
543   putMsg dflags msg
544   where
545    x `pcntOf` y = int ((x * 100) `quot` y) <> char '%'
546
547 countFS :: Int -> Int -> Int -> Int -> [[FastString]] -> (Int, Int, Int, Int)
548 countFS entries longest is_z has_z [] = (entries, longest, is_z, has_z)
549 countFS entries longest is_z has_z (b:bs) = 
550   let
551         len = length b
552         longest' = max len longest
553         entries' = entries + len
554         is_zs = length (filter isZEncoded b)
555         has_zs = length (filter hasZEncoding b)
556   in
557         countFS entries' longest' (is_z + is_zs) (has_z + has_zs) bs
558
559 -- -----------------------------------------------------------------------------
560 -- Util
561
562 unknownFlagsErr :: [String] -> a
563 unknownFlagsErr fs = throwDyn (UsageError ("unrecognised flags: " ++ unwords fs))