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