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