1 {-# OPTIONS -fno-warn-incomplete-patterns -optc-DNON_POSIX_SOURCE #-}
3 -----------------------------------------------------------------------------
7 -- (c) The University of Glasgow 2005
9 -----------------------------------------------------------------------------
11 module Main (main) where
13 #include "HsVersions.h"
15 -- The official GHC API
17 import GHC ( DynFlags(..), HscTarget(..),
18 GhcMode(..), GhcLink(..),
19 LoadHowMuch(..), dopt, DynFlag(..),
23 -- Implementations of the various modes (--show-iface, mkdependHS. etc.)
24 import LoadIface ( showIface )
25 import HscMain ( newHscEnv )
26 import DriverPipeline ( oneShot, compileFile )
27 import DriverMkDepend ( doMkDependHS )
29 import InteractiveUI ( interactiveUI, ghciWelcomeMsg )
32 -- Various other random stuff that we need
35 import Packages ( dumpPackages )
36 import DriverPhases ( Phase(..), isSourceFilename, anyHsc,
37 startPhase, isHaskellSrcFilename )
38 import BasicTypes ( failed )
40 import StaticFlagParser
48 import MonadUtils ( liftIO )
50 -- Standard Haskell libraries
52 import System.Environment
54 import System.FilePath
59 -----------------------------------------------------------------------------
62 -- time commands when run with -v
64 -- Win32 support: proper signal handling
65 -- reading the package configuration file is too slow
68 -----------------------------------------------------------------------------
69 -- GHC's command-line interface
74 GHC.defaultErrorHandler defaultDynFlags $ do
75 -- 1. extract the -B flag from the args
79 (minusB_args, argv1) = partition ("-B" `isPrefixOf`) argv0
80 mbMinusB | null minusB_args = Nothing
81 | otherwise = Just (drop 2 (last minusB_args))
83 let argv1' = map (mkGeneralLocated "on the commandline") argv1
84 (argv2, staticFlagWarnings) <- parseStaticFlags argv1'
86 -- 2. Parse the "mode" flags (--make, --interactive etc.)
87 (m_uber_mode, cli_mode, argv3, modeFlagWarnings) <- parseModeFlags argv2
89 -- If all we want to do is to show the version number then do it
90 -- now, before we start a GHC session etc.
91 -- If we do it later then bootstrapping gets confused as it tries
92 -- to find out what version of GHC it's using before package.conf
93 -- exists, so starting the session fails.
95 -- ShowUsage currently has to be handled specially, as it needs to
96 -- actually start up GHC so that it can find the usage.txt files
97 -- in the libdir. It would be nice to embed the text in the
98 -- executable so that we don't have to do that, and things are more
100 Just ShowUsage -> return ()
104 ShowSupportedLanguages -> showSupportedLanguages
105 ShowVersion -> showVersion
106 ShowNumVersion -> putStrLn cProjectVersion
110 -- start our GHC session
111 GHC.runGhc mbMinusB $ do
113 dflags0 <- GHC.getSessionDynFlags
115 -- set the default GhcMode, HscTarget and GhcLink. The HscTarget
116 -- can be further adjusted on a module by module basis, using only
117 -- the -fvia-C and -fasm flags. If the default HscTarget is not
118 -- HscC or HscAsm, -fvia-C and -fasm have no effect.
119 let dflt_target = hscTarget dflags0
122 DoInteractive -> (CompManager, HscInterpreted, LinkInMemory)
123 DoEval _ -> (CompManager, HscInterpreted, LinkInMemory)
124 DoMake -> (CompManager, dflt_target, LinkBinary)
125 DoMkDependHS -> (MkDepend, dflt_target, LinkBinary)
126 _ -> (OneShot, dflt_target, LinkBinary)
128 let dflags1 = dflags0{ ghcMode = mode,
131 -- leave out hscOutName for now
132 hscOutName = panic "Main.main:hscOutName not set",
133 verbosity = case cli_mode of
138 -- turn on -fimplicit-import-qualified for GHCi now, so that it
139 -- can be overriden from the command-line
140 dflags1a | DoInteractive <- cli_mode = imp_qual_enabled
141 | DoEval _ <- cli_mode = imp_qual_enabled
142 | otherwise = dflags1
143 where imp_qual_enabled = dflags1 `dopt_set` Opt_ImplicitImportQualified
145 -- The rest of the arguments are "dynamic"
146 -- Leftover ones are presumably files
147 (dflags2, fileish_args, dynamicFlagWarnings) <- GHC.parseDynamicFlags dflags1a argv3
149 -- As noted earlier, currently we hvae to handle ShowUsage down here
151 Just ShowUsage -> liftIO $ showGhcUsage dflags2 cli_mode
154 let flagWarnings = staticFlagWarnings
156 ++ dynamicFlagWarnings
158 handleSourceError (\e -> do
159 GHC.printExceptionAndWarnings e
160 liftIO $ exitWith (ExitFailure 1)) $
161 handleFlagWarnings dflags2 flagWarnings
163 -- make sure we clean up after ourselves
164 GHC.defaultCleanupHandler dflags2 $ do
166 liftIO $ showBanner cli_mode dflags2
168 -- we've finished manipulating the DynFlags, update the session
169 GHC.setSessionDynFlags dflags2
170 dflags3 <- GHC.getSessionDynFlags
171 hsc_env <- GHC.getSession
174 -- To simplify the handling of filepaths, we normalise all filepaths right
175 -- away - e.g., for win32 platforms, backslashes are converted
176 -- into forward slashes.
177 normal_fileish_paths = map (normalise . unLoc) fileish_args
178 (srcs, objs) = partition_args normal_fileish_paths [] []
180 -- Note: have v_Ld_inputs maintain the order in which 'objs' occurred on
182 liftIO $ mapM_ (consIORef v_Ld_inputs) (reverse objs)
184 ---------------- Display configuration -----------
185 when (verbosity dflags3 >= 4) $
186 liftIO $ dumpPackages dflags3
188 when (verbosity dflags3 >= 3) $ do
189 liftIO $ hPutStrLn stderr ("Hsc static flags: " ++ unwords staticFlags)
191 ---------------- Final sanity checking -----------
192 liftIO $ checkOptions cli_mode dflags3 srcs objs
194 ---------------- Do the business -----------
195 handleSourceError (\e -> do
196 GHC.printExceptionAndWarnings e
197 liftIO $ exitWith (ExitFailure 1)) $ do
199 PrintLibdir -> liftIO $ putStrLn (topDir dflags3)
200 ShowInterface f -> liftIO $ doShowIface dflags3 f
201 DoMake -> doMake srcs
202 DoMkDependHS -> doMkDependHS (map fst srcs)
203 StopBefore p -> oneShot hsc_env p srcs >> GHC.printWarnings
204 DoInteractive -> interactiveUI srcs Nothing
205 DoEval exprs -> interactiveUI srcs $ Just $ reverse exprs
207 liftIO $ dumpFinalStats dflags3
208 liftIO $ exitWith ExitSuccess
211 interactiveUI :: b -> c -> Ghc ()
213 ghcError (CmdLineError "not built for interactive use")
216 -- -----------------------------------------------------------------------------
217 -- Splitting arguments into source files and object files. This is where we
218 -- interpret the -x <suffix> option, and attach a (Maybe Phase) to each source
219 -- file indicating the phase specified by the -x option in force, if any.
221 partition_args :: [String] -> [(String, Maybe Phase)] -> [String]
222 -> ([(String, Maybe Phase)], [String])
223 partition_args [] srcs objs = (reverse srcs, reverse objs)
224 partition_args ("-x":suff:args) srcs objs
225 | "none" <- suff = partition_args args srcs objs
226 | StopLn <- phase = partition_args args srcs (slurp ++ objs)
227 | otherwise = partition_args rest (these_srcs ++ srcs) objs
228 where phase = startPhase suff
229 (slurp,rest) = break (== "-x") args
230 these_srcs = zip slurp (repeat (Just phase))
231 partition_args (arg:args) srcs objs
232 | looks_like_an_input arg = partition_args args ((arg,Nothing):srcs) objs
233 | otherwise = partition_args args srcs (arg:objs)
236 We split out the object files (.o, .dll) and add them
237 to v_Ld_inputs for use by the linker.
239 The following things should be considered compilation manager inputs:
241 - haskell source files (strings ending in .hs, .lhs or other
242 haskellish extension),
244 - module names (not forgetting hierarchical module names),
246 - and finally we consider everything not containing a '.' to be
247 a comp manager input, as shorthand for a .hs or .lhs filename.
249 Everything else is considered to be a linker object, and passed
250 straight through to the linker.
252 looks_like_an_input :: String -> Bool
253 looks_like_an_input m = isSourceFilename m
254 || looksLikeModuleName m
257 -- -----------------------------------------------------------------------------
258 -- Option sanity checks
260 -- | Ensure sanity of options.
262 -- Throws 'UsageError' or 'CmdLineError' if not.
263 checkOptions :: CmdLineMode -> DynFlags -> [(String,Maybe Phase)] -> [String] -> IO ()
264 -- Final sanity checking before kicking off a compilation (pipeline).
265 checkOptions cli_mode dflags srcs objs = do
266 -- Complain about any unknown flags
267 let unknown_opts = [ f | (f@('-':_), _) <- srcs ]
268 when (notNull unknown_opts) (unknownFlagsErr unknown_opts)
270 when (notNull (filter isRTSWay (wayNames dflags))
271 && isInterpretiveMode cli_mode) $
272 hPutStrLn stderr ("Warning: -debug, -threaded and -ticky are ignored by GHCi")
274 -- -prof and --interactive are not a good combination
275 when (notNull (filter (not . isRTSWay) (wayNames dflags))
276 && isInterpretiveMode cli_mode) $
277 do ghcError (UsageError
278 "--interactive can't be used with -prof or -unreg.")
280 if (isJust (outputHi dflags) &&
281 (isCompManagerMode cli_mode || srcs `lengthExceeds` 1))
282 then ghcError (UsageError "-ohi can only be used when compiling a single source file")
285 -- -o sanity checking
286 if (srcs `lengthExceeds` 1 && isJust (outputFile dflags)
287 && not (isLinkMode cli_mode))
288 then ghcError (UsageError "can't apply -o to multiple source files")
291 let not_linking = not (isLinkMode cli_mode) || isNoLink (ghcLink dflags)
293 when (not_linking && not (null objs)) $
294 hPutStrLn stderr ("Warning: the following files would be used as linker inputs, but linking is not being done: " ++ unwords objs)
296 -- Check that there are some input files
297 -- (except in the interactive case)
298 if null srcs && (null objs || not_linking) && needsInputsMode cli_mode
299 then ghcError (UsageError "no input files")
302 -- Verify that output files point somewhere sensible.
303 verifyOutputFiles dflags
306 -- Compiler output options
308 -- called to verify that the output files & directories
309 -- point somewhere valid.
311 -- The assumption is that the directory portion of these output
312 -- options will have to exist by the time 'verifyOutputFiles'
315 verifyOutputFiles :: DynFlags -> IO ()
316 verifyOutputFiles dflags = do
317 -- not -odir: we create the directory for -odir if it doesn't exist (#2278).
318 let ofile = outputFile dflags
319 when (isJust ofile) $ do
320 let fn = fromJust ofile
321 flg <- doesDirNameExist fn
322 when (not flg) (nonExistentDir "-o" fn)
323 let ohi = outputHi dflags
324 when (isJust ohi) $ do
325 let hi = fromJust ohi
326 flg <- doesDirNameExist hi
327 when (not flg) (nonExistentDir "-ohi" hi)
329 nonExistentDir flg dir =
330 ghcError (CmdLineError ("error: directory portion of " ++
331 show dir ++ " does not exist (used with " ++
332 show flg ++ " option.)"))
334 -----------------------------------------------------------------------------
335 -- GHC modes of operation
338 = ShowUsage -- ghc -?
339 | ShowVersion -- ghc -V/--version
340 | ShowNumVersion -- ghc --numeric-version
341 | ShowSupportedLanguages -- ghc --supported-languages
342 | ShowInfo -- ghc --info
346 = PrintLibdir -- ghc --print-libdir
347 | ShowInterface String -- ghc --show-iface
348 | DoMkDependHS -- ghc -M
349 | StopBefore Phase -- ghc -E | -C | -S
350 -- StopBefore StopLn is the default
351 | DoMake -- ghc --make
352 | DoInteractive -- ghc --interactive
353 | DoEval [String] -- ghc -e foo -e bar => DoEval ["bar", "foo"]
357 isInteractiveMode :: CmdLineMode -> Bool
358 isInteractiveMode DoInteractive = True
359 isInteractiveMode _ = False
362 -- isInterpretiveMode: byte-code compiler involved
363 isInterpretiveMode :: CmdLineMode -> Bool
364 isInterpretiveMode DoInteractive = True
365 isInterpretiveMode (DoEval _) = True
366 isInterpretiveMode _ = False
368 needsInputsMode :: CmdLineMode -> Bool
369 needsInputsMode DoMkDependHS = True
370 needsInputsMode (StopBefore _) = True
371 needsInputsMode DoMake = True
372 needsInputsMode _ = False
374 -- True if we are going to attempt to link in this mode.
375 -- (we might not actually link, depending on the GhcLink flag)
376 isLinkMode :: CmdLineMode -> Bool
377 isLinkMode (StopBefore StopLn) = True
378 isLinkMode DoMake = True
379 isLinkMode DoInteractive = True
380 isLinkMode (DoEval _) = True
383 isCompManagerMode :: CmdLineMode -> Bool
384 isCompManagerMode DoMake = True
385 isCompManagerMode DoInteractive = True
386 isCompManagerMode (DoEval _) = True
387 isCompManagerMode _ = False
390 -- -----------------------------------------------------------------------------
391 -- Parsing the mode flag
393 parseModeFlags :: [Located String]
394 -> IO (Maybe UberMode,
398 parseModeFlags args = do
399 let ((leftover, errs, warns), (mUberMode, mode, _, flags')) =
400 runCmdLine (processArgs mode_flags args)
401 (Nothing, StopBefore StopLn, "", [])
402 when (not (null errs)) $ ghcError $ errorsToGhcException errs
403 return (mUberMode, mode, flags' ++ leftover, warns)
405 type ModeM = CmdLineP (Maybe UberMode, CmdLineMode, String, [Located String])
406 -- mode flags sometimes give rise to new DynFlags (eg. -C, see below)
407 -- so we collect the new ones and return them.
409 mode_flags :: [Flag ModeM]
411 [ ------- help / version ----------------------------------------------
412 Flag "?" (NoArg (setUberMode ShowUsage))
414 , Flag "-help" (NoArg (setUberMode ShowUsage))
416 , Flag "V" (NoArg (setUberMode ShowVersion))
418 , Flag "-version" (NoArg (setUberMode ShowVersion))
420 , Flag "-numeric-version" (NoArg (setUberMode ShowNumVersion))
422 , Flag "-info" (NoArg (setUberMode ShowInfo))
424 , Flag "-supported-languages" (NoArg (setUberMode ShowSupportedLanguages))
426 , Flag "-print-libdir" (PassFlag (setMode PrintLibdir))
429 ------- interfaces ----------------------------------------------------
430 , Flag "-show-iface" (HasArg (\f -> setMode (ShowInterface f)
434 ------- primary modes ------------------------------------------------
435 , Flag "M" (PassFlag (setMode DoMkDependHS))
437 , Flag "E" (PassFlag (setMode (StopBefore anyHsc)))
439 , Flag "C" (PassFlag (\f -> do setMode (StopBefore HCc) f
442 , Flag "S" (PassFlag (setMode (StopBefore As)))
444 , Flag "-make" (PassFlag (setMode DoMake))
446 , Flag "-interactive" (PassFlag (setMode DoInteractive))
448 , Flag "e" (HasArg (\s -> updateMode (updateDoEval s) "-e"))
451 -- -fno-code says to stop after Hsc but don't generate any code.
452 , Flag "fno-code" (PassFlag (\f -> do setMode (StopBefore HCc) f
454 addFlag "-fforce-recomp"))
458 setUberMode :: UberMode -> ModeM ()
460 (_, cmdLineMode, flag, flags') <- getCmdLineState
461 putCmdLineState (Just m, cmdLineMode, flag, flags')
463 setMode :: CmdLineMode -> String -> ModeM ()
464 setMode m flag = updateMode (\_ -> m) flag
466 updateDoEval :: String -> CmdLineMode -> CmdLineMode
467 updateDoEval expr (DoEval exprs) = DoEval (expr : exprs)
468 updateDoEval expr _ = DoEval [expr]
470 updateMode :: (CmdLineMode -> CmdLineMode) -> String -> ModeM ()
471 updateMode f flag = do
472 (m_uber_mode, old_mode, old_flag, flags') <- getCmdLineState
473 if null old_flag || flag == old_flag
474 then putCmdLineState (m_uber_mode, f old_mode, flag, flags')
475 else ghcError (UsageError
476 ("cannot use `" ++ old_flag ++ "' with `" ++ flag ++ "'"))
478 addFlag :: String -> ModeM ()
480 (u, m, f, flags') <- getCmdLineState
481 -- XXX Can we get a useful Loc?
482 putCmdLineState (u, m, f, mkGeneralLocated "addFlag" s : flags')
485 -- ----------------------------------------------------------------------------
488 doMake :: [(String,Maybe Phase)] -> Ghc ()
489 doMake [] = ghcError (UsageError "no input files")
491 let (hs_srcs, non_hs_srcs) = partition haskellish srcs
493 haskellish (f,Nothing) =
494 looksLikeModuleName f || isHaskellSrcFilename f || '.' `notElem` f
495 haskellish (_,Just phase) =
496 phase `notElem` [As, Cc, CmmCpp, Cmm, StopLn]
498 hsc_env <- GHC.getSession
499 o_files <- mapM (\x -> do
500 f <- compileFile hsc_env StopLn x
504 liftIO $ mapM_ (consIORef v_Ld_inputs) (reverse o_files)
506 targets <- mapM (uncurry GHC.guessTarget) hs_srcs
507 GHC.setTargets targets
508 ok_flag <- GHC.load LoadAllTargets
510 when (failed ok_flag) (liftIO $ exitWith (ExitFailure 1))
514 -- ---------------------------------------------------------------------------
517 doShowIface :: DynFlags -> FilePath -> IO ()
518 doShowIface dflags file = do
519 hsc_env <- newHscEnv defaultCallbacks dflags
520 showIface hsc_env file
522 -- ---------------------------------------------------------------------------
523 -- Various banners and verbosity output.
525 showBanner :: CmdLineMode -> DynFlags -> IO ()
526 showBanner _cli_mode dflags = do
527 let verb = verbosity dflags
530 -- Show the GHCi banner
531 when (isInteractiveMode _cli_mode && verb >= 1) $ putStrLn ghciWelcomeMsg
534 -- Display details of the configuration in verbose mode
536 do hPutStr stderr "Glasgow Haskell Compiler, Version "
537 hPutStr stderr cProjectVersion
538 hPutStr stderr ", for Haskell 98, stage "
539 hPutStr stderr cStage
540 hPutStr stderr " booted by GHC version "
541 hPutStrLn stderr cBooterVersion
543 -- We print out a Read-friendly string, but a prettier one than the
544 -- Show instance gives us
547 let sq x = " [" ++ x ++ "\n ]"
548 putStrLn $ sq $ concat $ intersperse "\n ," $ map show compilerInfo
551 showSupportedLanguages :: IO ()
552 showSupportedLanguages = do mapM_ putStrLn supportedLanguages
557 putStrLn (cProjectName ++ ", version " ++ cProjectVersion)
560 showGhcUsage :: DynFlags -> CmdLineMode -> IO ()
561 showGhcUsage dflags cli_mode = do
563 | DoInteractive <- cli_mode = ghciUsagePath dflags
564 | otherwise = ghcUsagePath dflags
565 usage <- readFile usage_path
570 dump ('$':'$':s) = putStr progName >> dump s
571 dump (c:s) = putChar c >> dump s
573 dumpFinalStats :: DynFlags -> IO ()
574 dumpFinalStats dflags =
575 when (dopt Opt_D_faststring_stats dflags) $ dumpFastStringStats dflags
577 dumpFastStringStats :: DynFlags -> IO ()
578 dumpFastStringStats dflags = do
579 buckets <- getFastStringTable
580 let (entries, longest, is_z, has_z) = countFS 0 0 0 0 buckets
581 msg = text "FastString stats:" $$
582 nest 4 (vcat [text "size: " <+> int (length buckets),
583 text "entries: " <+> int entries,
584 text "longest chain: " <+> int longest,
585 text "z-encoded: " <+> (is_z `pcntOf` entries),
586 text "has z-encoding: " <+> (has_z `pcntOf` entries)
588 -- we usually get more "has z-encoding" than "z-encoded", because
589 -- when we z-encode a string it might hash to the exact same string,
590 -- which will is not counted as "z-encoded". Only strings whose
591 -- Z-encoding is different from the original string are counted in
592 -- the "z-encoded" total.
595 x `pcntOf` y = int ((x * 100) `quot` y) <> char '%'
597 countFS :: Int -> Int -> Int -> Int -> [[FastString]] -> (Int, Int, Int, Int)
598 countFS entries longest is_z has_z [] = (entries, longest, is_z, has_z)
599 countFS entries longest is_z has_z (b:bs) =
602 longest' = max len longest
603 entries' = entries + len
604 is_zs = length (filter isZEncoded b)
605 has_zs = length (filter hasZEncoding b)
607 countFS entries' longest' (is_z + is_zs) (has_z + has_zs) bs
609 -- -----------------------------------------------------------------------------
612 unknownFlagsErr :: [String] -> a
613 unknownFlagsErr fs = ghcError (UsageError ("unrecognised flags: " ++ unwords fs))