summaryrefslogtreecommitdiff
path: root/ghc/compiler/main/Main.hs
blob: 5c98696970d496f05a5497fe819285dacda28644 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
{-# OPTIONS -fno-warn-incomplete-patterns #-}
-----------------------------------------------------------------------------
-- $Id: Main.hs,v 1.59 2001/03/06 11:23:46 simonmar Exp $
--
-- GHC Driver program
--
-- (c) Simon Marlow 2000
--
-----------------------------------------------------------------------------

-- with path so that ghc -M can find config.h
#include "../includes/config.h"

module Main (main) where

#include "HsVersions.h"


#ifdef GHCI
import InteractiveUI
import Char		( toLower )
#endif

#ifndef mingw32_TARGET_OS
import Dynamic
import Posix
#endif

import CompManager
import ParsePkgConf
import DriverPipeline
import DriverState
import DriverFlags
import DriverMkDepend
import DriverUtil
import Panic
import DriverPhases	( Phase(..), haskellish_file, objish_file )
import CmdLineOpts
import TmpFiles
import Finder		( initFinder )
import CmStaticInfo
import Config
import Outputable
import Util

import Concurrent
import Directory
import IOExts
import Exception

import IO
import Monad
import List
import System
import Maybe


-----------------------------------------------------------------------------
-- Changes:

-- * -fglasgow-exts NO LONGER IMPLIES -package lang!!!  (-fglasgow-exts is a
--   dynamic flag whereas -package is a static flag.)

-----------------------------------------------------------------------------
-- ToDo:

-- -nohi doesn't work
-- new mkdependHS doesn't support all the options that the old one did (-X et al.)
-- time commands when run with -v
-- split marker
-- java generation
-- user ways
-- Win32 support: proper signal handling
-- make sure OPTIONS in .hs file propogate to .hc file if -C or -keep-hc-file-too
-- reading the package configuration file is too slow
-- -K<size>

-----------------------------------------------------------------------------
-- Differences vs. old driver:

-- No more "Enter your Haskell program, end with ^D (on a line of its own):"
-- consistency checking removed (may do this properly later)
-- removed -noC
-- no -Ofile

-----------------------------------------------------------------------------
-- Main loop

main =
  -- top-level exception handler: any unrecognised exception is a compiler bug.
  handle (\exception -> do hPutStr stderr (show (Panic (show exception)))
			   exitWith (ExitFailure 1)
         ) $ do

  -- all error messages are propagated as exceptions
  handleDyn (\dyn -> case dyn of
			  PhaseFailed _phase code -> exitWith code
			  Interrupted -> exitWith (ExitFailure 1)
			  _ -> do hPutStrLn stderr (show (dyn :: GhcException))
			          exitWith (ExitFailure 1)
	    ) $ do

   -- make sure we clean up after ourselves
   later (do  forget_it <- readIORef v_Keep_tmp_files
	      unless forget_it $ do
	      verb <- dynFlag verbosity
	      cleanTempFiles verb
     ) $ do
	-- exceptions will be blocked while we clean the temporary files,
	-- so there shouldn't be any difficulty if we receive further
	-- signals.

	-- install signal handlers
   main_thread <- myThreadId
#ifndef mingw32_TARGET_OS
   let sig_handler = Catch (throwTo main_thread 
				(DynException (toDyn Interrupted)))
   installHandler sigQUIT sig_handler Nothing 
   installHandler sigINT  sig_handler Nothing
#endif

   argv   <- getArgs

	-- grab any -B options from the command line first
   argv'  <- setTopDir argv
   top_dir <- readIORef v_TopDir

   let installed s = top_dir ++ '/':s
       inplace s   = top_dir ++ '/':cCURRENT_DIR ++ '/':s

       installed_pkgconfig = installed ("package.conf")
       inplace_pkgconfig   = inplace (cGHC_DRIVER_DIR ++ "/package.conf.inplace")

	-- discover whether we're running in a build tree or in an installation,
	-- by looking for the package configuration file.
   am_installed <- doesFileExist installed_pkgconfig

   if am_installed
	then writeIORef v_Path_package_config installed_pkgconfig
	else do am_inplace <- doesFileExist inplace_pkgconfig
	        if am_inplace
		    then writeIORef v_Path_package_config inplace_pkgconfig
		    else throwDyn (OtherError ("Can't find package.conf in " ++ inplace_pkgconfig))

	-- set the location of our various files
   if am_installed
	then do writeIORef v_Path_usage (installed "ghc-usage.txt")
		writeIORef v_Pgm_L (installed "unlit")
		writeIORef v_Pgm_m (installed "ghc-asm")
		writeIORef v_Pgm_s (installed "ghc-split")

	else do writeIORef v_Path_usage (inplace (cGHC_DRIVER_DIR ++ "/ghc-usage.txt"))
		writeIORef v_Pgm_L (inplace cGHC_UNLIT)
		writeIORef v_Pgm_m (inplace cGHC_MANGLER)
		writeIORef v_Pgm_s (inplace cGHC_SPLIT)

	-- read the package configuration
   conf_file <- readIORef v_Path_package_config
   r <- parsePkgConf conf_file
   case r of {
	Left err -> throwDyn (OtherError (showSDoc err));
	Right pkg_details -> do

   writeIORef v_Package_details pkg_details

	-- find the phase to stop after (i.e. -E, -C, -c, -S flags)
   (flags2, mode, stop_flag) <- getGhcMode argv'
   writeIORef v_GhcMode mode

	-- Show the GHCi banner?
#  ifdef GHCI
   when (mode == DoInteractive) $
      hPutStrLn stdout ghciWelcomeMsg
#  endif

	-- process all the other arguments, and get the source files
   non_static <- processArgs static_flags flags2 []

	-- -O and --interactive are not a good combination
	-- ditto with any kind of way selection
   orig_opt_level <- readIORef v_OptLevel
   when (orig_opt_level > 0 && mode == DoInteractive) $
      do putStr "warning: -O conflicts with --interactive; -O turned off.\n"
         writeIORef v_OptLevel 0
   orig_ways <- readIORef v_Ways
   when (not (null orig_ways) && mode == DoInteractive) $
      do throwDyn (OtherError 
                   "--interactive can't be used with -prof, -ticky, -unreg or -smp.")

	-- Find the build tag, and re-process the build-specific options.
	-- Also add in flags for unregisterised compilation, if 
	-- GhcUnregisterised=YES.
   way_opts <- findBuildTag
   let unreg_opts | cGhcUnregisterised == "YES" = unregFlags
		  | otherwise = []
   way_non_static <- processArgs static_flags (unreg_opts ++ way_opts) []

	-- give the static flags to hsc
   static_opts <- buildStaticHscOpts
   writeIORef v_Static_hsc_opts static_opts

   -- build the default DynFlags (these may be adjusted on a per
   -- module basis by OPTIONS pragmas and settings in the interpreter).

   core_todo <- buildCoreToDo
   stg_todo  <- buildStgToDo

   -- set the "global" HscLang.  The HscLang can be further adjusted on a module
   -- by module basis, using only the -fvia-C and -fasm flags.  If the global
   -- HscLang is not HscC or HscAsm, -fvia-C and -fasm have no effect.
   opt_level  <- readIORef v_OptLevel


   let lang = case mode of 
		 StopBefore HCc -> HscC
		 DoInteractive  -> HscInterpreted
		 _other        | opt_level >= 1  -> HscC  -- -O implies -fvia-C 
			       | otherwise       -> defaultHscLang

   writeIORef v_DynFlags 
	defaultDynFlags{ coreToDo = core_todo,
		  	 stgToDo  = stg_todo,
                  	 hscLang  = lang,
		  	 -- leave out hscOutName for now
                  	 hscOutName = panic "Main.main:hscOutName not set",

		  	 verbosity = case mode of
					DoInteractive -> 1
					DoMake	      -> 1
					_other        -> 0,
			}

	-- the rest of the arguments are "dynamic"
   srcs <- processArgs dynamic_flags (way_non_static ++ non_static) []
	-- save the "initial DynFlags" away
   init_dyn_flags <- readIORef v_DynFlags
   writeIORef v_InitDynFlags init_dyn_flags

    	-- complain about any unknown flags
   mapM unknownFlagErr [ f | f@('-':_) <- srcs ]

   verb <- dynFlag verbosity

   when (verb >= 2) 
	(do hPutStr stderr "Glasgow Haskell Compiler, Version "
 	    hPutStr stderr cProjectVersion
	    hPutStr stderr ", for Haskell 98, compiled by GHC version "
	    hPutStrLn stderr cBooterVersion)

   when (verb >= 2) 
	(hPutStrLn stderr ("Using package config file: " ++ conf_file))

   when (verb >= 3) 
	(hPutStrLn stderr ("Hsc static flags: " ++ unwords static_opts))

	-- initialise the finder
   pkg_avails <- getPackageInfo
   initFinder pkg_avails

	-- mkdependHS is special
   when (mode == DoMkDependHS) beginMkDependHS

	-- make/interactive require invoking the compilation manager
   if (mode == DoMake)        then beginMake srcs        else do
   if (mode == DoInteractive) then beginInteractive srcs else do

	-- sanity checking
   o_file <- readIORef v_Output_file
   ohi    <- readIORef v_Output_hi
   if length srcs > 1 && (isJust ohi || (isJust o_file && mode /= DoLink && mode /= DoMkDLL))
	then throwDyn (UsageError "can't apply -o or -ohi options to multiple source files")
	else do

   if null srcs then throwDyn (UsageError "no input files") else do

   let compileFile src = do
	  writeIORef v_DynFlags init_dyn_flags

	  -- We compile in two stages, because the file may have an
	  -- OPTIONS pragma that affects the compilation pipeline (eg. -fvia-C)

	  let (basename, suffix) = splitFilename src

	  -- just preprocess
	  pp <- if not (haskellish_file src) || mode == StopBefore Hsc
			then return src else do
		phases <- genPipeline (StopBefore Hsc) stop_flag
			    False{-not persistent-} defaultHscLang src
	  	pipeLoop phases src False{-no linking-} False{-no -o flag-}
			basename suffix

	  -- rest of compilation
	  dyn_flags <- readIORef v_DynFlags
	  phases <- genPipeline mode stop_flag True (hscLang dyn_flags) pp
	  r <- pipeLoop phases pp (mode==DoLink || mode==DoMkDLL) True{-use -o flag-}
			basename suffix
	  return r

   o_files <- mapM compileFile srcs

   when (mode == DoMkDependHS) endMkDependHS
   when (mode == DoLink) (doLink o_files)
   when (mode == DoMkDLL) (doMkDLL o_files)
  }
	-- grab the last -B option on the command line, and
	-- set topDir to its value.
setTopDir :: [String] -> IO [String]
setTopDir args = do
  let (minusbs, others) = partition (prefixMatch "-B") args
  (case minusbs of
    []   -> writeIORef v_TopDir clibdir
    some -> writeIORef v_TopDir (drop 2 (last some)))
  return others

beginMake :: [String] -> IO ()
beginMake fileish_args
  = do let (objs, mods) = partition objish_file fileish_args
       mapM (add v_Ld_inputs) objs

       case mods of
	 []    -> throwDyn (UsageError "no input files")
	 [mod] -> do state <- cmInit Batch
		     cmLoadModule state mod
		     return ()
	 _     -> throwDyn (UsageError "only one module allowed with --make")


beginInteractive :: [String] -> IO ()
#ifndef GHCI
beginInteractive = throwDyn (OtherError "not built for interactive use")
#else
beginInteractive fileish_args
  = do minus_ls <- readIORef v_Cmdline_libraries

       let (objs, mods) = partition objish_file fileish_args
	   libs = map Left objs ++ map Right minus_ls

       state <- cmInit Interactive
       case mods of
	  []    -> interactiveUI state Nothing    libs
	  [mod] -> interactiveUI state (Just mod) libs
	  _     -> throwDyn (UsageError 
                             "only one module allowed with --interactive")
#endif