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