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