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