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