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