[project @ 2005-01-27 18:38:21 by panne]
[ghc-hetmet.git] / ghc / compiler / main / DriverState.hs
1 -----------------------------------------------------------------------------
2 --
3 -- Settings for the driver
4 --
5 -- (c) The University of Glasgow 2002
6 --
7 -----------------------------------------------------------------------------
8
9 module DriverState where
10
11 #include "../includes/ghcconfig.h"
12 #include "HsVersions.h"
13
14 import CmdLineOpts
15 import DriverPhases
16 import DriverUtil
17 import Util
18 import Config
19 import Panic
20
21 import DATA_IOREF       ( IORef, readIORef, writeIORef )
22 import EXCEPTION
23
24 import List
25 import Char  
26 import Monad
27 import Maybe            ( fromJust, isJust )
28 import Directory        ( doesDirectoryExist )
29
30 -----------------------------------------------------------------------------
31 -- non-configured things
32
33 cHaskell1Version = "5" -- i.e., Haskell 98
34
35 -----------------------------------------------------------------------------
36 -- GHC modes of operation
37
38 data GhcMode
39   = DoMkDependHS                        -- ghc -M
40   | DoMkDLL                             -- ghc --mk-dll
41   | StopBefore Phase                    -- ghc -E | -C | -S | -c
42   | DoMake                              -- ghc --make
43   | DoInteractive                       -- ghc --interactive
44   | DoLink                              -- [ the default ]
45   | DoEval String                       -- ghc -e
46   deriving (Show)
47
48 GLOBAL_VAR(v_GhcMode,     DoLink, GhcMode)
49 GLOBAL_VAR(v_GhcModeFlag, "",     String)
50
51 setMode :: GhcMode -> String -> IO ()
52 setMode m flag = do
53   old_mode <- readIORef v_GhcMode
54   old_flag <- readIORef v_GhcModeFlag
55   when (notNull old_flag && flag /= old_flag) $
56       throwDyn (UsageError 
57           ("cannot use `" ++ old_flag ++ "' with `" ++ flag ++ "'"))
58   writeIORef v_GhcMode m
59   writeIORef v_GhcModeFlag flag
60
61 isInteractiveMode, isInterpretiveMode     :: GhcMode -> Bool
62 isMakeMode, isLinkMode, isCompManagerMode :: GhcMode -> Bool
63
64 isInteractiveMode DoInteractive = True
65 isInteractiveMode _             = False
66
67 -- isInterpretiveMode: byte-code compiler involved
68 isInterpretiveMode DoInteractive = True
69 isInterpretiveMode (DoEval _)    = True
70 isInterpretiveMode _             = False
71
72 isMakeMode DoMake = True
73 isMakeMode _      = False
74
75 isLinkMode DoLink  = True
76 isLinkMode DoMkDLL = True
77 isLinkMode _       = False
78
79 isCompManagerMode DoMake        = True
80 isCompManagerMode DoInteractive = True
81 isCompManagerMode (DoEval _)    = True
82 isCompManagerMode _             = False
83
84 -----------------------------------------------------------------------------
85 -- Global compilation flags
86
87 -- Default CPP defines in Haskell source
88 hsSourceCppOpts =
89         [ "-D__HASKELL1__="++cHaskell1Version
90         , "-D__GLASGOW_HASKELL__="++cProjectVersionInt                          
91         , "-D__HASKELL98__"
92         , "-D__CONCURRENT_HASKELL__"
93         ]
94
95
96 -- Keep output from intermediate phases
97 GLOBAL_VAR(v_Keep_hi_diffs,             False,          Bool)
98 GLOBAL_VAR(v_Keep_hc_files,             False,          Bool)
99 GLOBAL_VAR(v_Keep_s_files,              False,          Bool)
100 GLOBAL_VAR(v_Keep_raw_s_files,          False,          Bool)
101 GLOBAL_VAR(v_Keep_tmp_files,            False,          Bool)
102 #ifdef ILX
103 GLOBAL_VAR(v_Keep_il_files,             False,          Bool)
104 GLOBAL_VAR(v_Keep_ilx_files,            False,          Bool)
105 #endif
106
107 -- Misc
108 GLOBAL_VAR(v_Scale_sizes_by,            1.0,            Double)
109 GLOBAL_VAR(v_Static,                    True,           Bool)
110 GLOBAL_VAR(v_NoLink,                    False,          Bool)
111 GLOBAL_VAR(v_NoHsMain,                  False,          Bool)
112 GLOBAL_VAR(v_MainModIs,                 Nothing,        Maybe String)
113 GLOBAL_VAR(v_MainFunIs,                 Nothing,        Maybe String)
114 GLOBAL_VAR(v_Collect_ghc_timing,        False,          Bool)
115 GLOBAL_VAR(v_Do_asm_mangling,           True,           Bool)
116 GLOBAL_VAR(v_Excess_precision,          False,          Bool)
117 GLOBAL_VAR(v_Read_DotGHCi,              True,           Bool)
118
119 -- Preprocessor flags
120 GLOBAL_VAR(v_Hs_source_pp_opts, [], [String])
121
122 -----------------------------------------------------------------------------
123 -- Splitting object files (for libraries)
124
125 GLOBAL_VAR(v_Split_object_files,        False,          Bool)
126 GLOBAL_VAR(v_Split_info,                ("",0),         (String,Int))
127         -- The split prefix and number of files
128
129         
130 can_split :: Bool
131 can_split =  prefixMatch "i386"    cTARGETPLATFORM
132           || prefixMatch "alpha"   cTARGETPLATFORM
133           || prefixMatch "hppa"    cTARGETPLATFORM
134           || prefixMatch "m68k"    cTARGETPLATFORM
135           || prefixMatch "mips"    cTARGETPLATFORM
136           || prefixMatch "powerpc" cTARGETPLATFORM
137           || prefixMatch "rs6000"  cTARGETPLATFORM
138           || prefixMatch "sparc"   cTARGETPLATFORM
139
140 -----------------------------------------------------------------------------
141 -- Compiler output options
142
143 GLOBAL_VAR(v_Output_dir,  Nothing, Maybe String)
144 GLOBAL_VAR(v_Output_file, Nothing, Maybe String)
145 GLOBAL_VAR(v_Output_hi,   Nothing, Maybe String)
146
147 -- called to verify that the output files & directories
148 -- point somewhere valid. 
149 --
150 -- The assumption is that the directory portion of these output
151 -- options will have to exist by the time 'verifyOutputFiles'
152 -- is invoked.
153 -- 
154 verifyOutputFiles :: IO ()
155 verifyOutputFiles = do
156   odir <- readIORef v_Output_dir
157   when (isJust odir) $ do
158      let dir = fromJust odir
159      flg <- doesDirectoryExist dir
160      when (not flg) (nonExistentDir "-odir" dir)
161   ofile <- readIORef v_Output_file
162   when (isJust ofile) $ do
163      let fn = fromJust ofile
164      flg <- doesDirNameExist fn
165      when (not flg) (nonExistentDir "-o" fn)
166   ohi <- readIORef v_Output_hi
167   when (isJust ohi) $ do
168      let hi = fromJust ohi
169      flg <- doesDirNameExist hi
170      when (not flg) (nonExistentDir "-ohi" hi)
171  where
172    nonExistentDir flg dir = 
173      throwDyn (CmdLineError ("error: directory portion of " ++ 
174                              show dir ++ " does not exist (used with " ++ 
175                              show flg ++ " option.)"))
176
177 GLOBAL_VAR(v_Object_suf,  phaseInputExt StopLn, String)
178 GLOBAL_VAR(v_HC_suf,      phaseInputExt HCc,    String)
179 GLOBAL_VAR(v_Hi_dir,      Nothing, Maybe String)
180 GLOBAL_VAR(v_Hi_suf,      "hi",    String)
181
182 GLOBAL_VAR(v_Ld_inputs, [],      [String])
183
184 odir_ify :: String -> IO String
185 odir_ify f = do
186   odir_opt <- readIORef v_Output_dir
187   case odir_opt of
188         Nothing -> return f
189         Just d  -> return (replaceFilenameDirectory f d)
190
191 osuf_ify :: String -> IO String
192 osuf_ify f = do
193   osuf <- readIORef v_Object_suf
194   return (replaceFilenameSuffix f osuf)
195
196 GLOBAL_VAR(v_StgStats,                  False, Bool)
197
198 buildStgToDo :: IO [ StgToDo ]
199 buildStgToDo = do
200   stg_stats <- readIORef v_StgStats
201   let flags1 | stg_stats = [ D_stg_stats ]
202              | otherwise = [ ]
203
204         -- STG passes
205   ways_ <- readIORef v_Ways
206   let flags2 | WayProf `elem` ways_ = StgDoMassageForProfiling : flags1
207              | otherwise            = flags1
208
209   return flags2
210
211 -----------------------------------------------------------------------------
212 -- Paths & Libraries
213
214 split_marker = ':'   -- not configurable (ToDo)
215
216 v_Include_paths, v_Library_paths :: IORef [String]
217 GLOBAL_VAR(v_Include_paths, [], [String])
218 GLOBAL_VAR(v_Library_paths, [],  [String])
219
220 #ifdef darwin_TARGET_OS
221 GLOBAL_VAR(v_Framework_paths, [], [String])
222 GLOBAL_VAR(v_Cmdline_frameworks, [], [String])
223 #endif
224
225 addToDirList :: IORef [String] -> String -> IO ()
226 addToDirList ref path
227   = do paths           <- readIORef ref
228        shiny_new_ones  <- splitPathList path
229        writeIORef ref (paths ++ shiny_new_ones)
230
231
232 splitPathList :: String -> IO [String]
233 splitPathList s = do ps <- splitUp s; return (filter notNull ps)
234                 -- empty paths are ignored: there might be a trailing
235                 -- ':' in the initial list, for example.  Empty paths can
236                 -- cause confusion when they are translated into -I options
237                 -- for passing to gcc.
238   where
239 #ifdef mingw32_TARGET_OS
240      -- 'hybrid' support for DOS-style paths in directory lists.
241      -- 
242      -- That is, if "foo:bar:baz" is used, this interpreted as
243      -- consisting of three entries, 'foo', 'bar', 'baz'.
244      -- However, with "c:/foo:c:\\foo;x:/bar", this is interpreted
245      -- as four elts, "c:/foo", "c:\\foo", "x", and "/bar" --
246      -- *provided* c:/foo exists and x:/bar doesn't.
247      --
248      -- Notice that no attempt is made to fully replace the 'standard'
249      -- split marker ':' with the Windows / DOS one, ';'. The reason being
250      -- that this will cause too much breakage for users & ':' will
251      -- work fine even with DOS paths, if you're not insisting on being silly.
252      -- So, use either.
253     splitUp []         = return []
254     splitUp (x:':':div:xs) 
255       | div `elem` dir_markers = do
256           let (p,rs) = findNextPath xs
257           ps  <- splitUp rs
258            {-
259              Consult the file system to check the interpretation
260              of (x:':':div:p) -- this is arguably excessive, we
261              could skip this test & just say that it is a valid
262              dir path.
263            -}
264           flg <- doesDirectoryExist (x:':':div:p)
265           if flg then
266              return ((x:':':div:p):ps)
267            else
268              return ([x]:(div:p):ps)
269     splitUp xs = do
270       let (p,rs) = findNextPath xs
271       ps <- splitUp rs
272       return (cons p ps)
273     
274     cons "" xs = xs
275     cons x  xs = x:xs
276
277     -- will be called either when we've consumed nought or the "<Drive>:/" part of
278     -- a DOS path, so splitting is just a Q of finding the next split marker.
279     findNextPath xs = 
280         case break (`elem` split_markers) xs of
281            (p, d:ds) -> (p, ds)
282            (p, xs)   -> (p, xs)
283
284     split_markers :: [Char]
285     split_markers = [':', ';']
286
287     dir_markers :: [Char]
288     dir_markers = ['/', '\\']
289
290 #else
291     splitUp xs = return (split split_marker xs)
292 #endif
293
294 -----------------------------------------------------------------------------
295 -- Ways
296
297 -- The central concept of a "way" is that all objects in a given
298 -- program must be compiled in the same "way".  Certain options change
299 -- parameters of the virtual machine, eg. profiling adds an extra word
300 -- to the object header, so profiling objects cannot be linked with
301 -- non-profiling objects.
302
303 -- After parsing the command-line options, we determine which "way" we
304 -- are building - this might be a combination way, eg. profiling+ticky-ticky.
305
306 -- We then find the "build-tag" associated with this way, and this
307 -- becomes the suffix used to find .hi files and libraries used in
308 -- this compilation.
309
310 GLOBAL_VAR(v_Build_tag, "", String)
311
312 -- The RTS has its own build tag, because there are some ways that
313 -- affect the RTS only.
314 GLOBAL_VAR(v_RTS_Build_tag, "", String)
315
316 data WayName
317   = WayThreaded
318   | WayDebug
319   | WayProf
320   | WayUnreg
321   | WayTicky
322   | WayPar
323   | WayGran
324   | WaySMP
325   | WayNDP
326   | WayUser_a
327   | WayUser_b
328   | WayUser_c
329   | WayUser_d
330   | WayUser_e
331   | WayUser_f
332   | WayUser_g
333   | WayUser_h
334   | WayUser_i
335   | WayUser_j
336   | WayUser_k
337   | WayUser_l
338   | WayUser_m
339   | WayUser_n
340   | WayUser_o
341   | WayUser_A
342   | WayUser_B
343   deriving (Eq,Ord)
344
345 GLOBAL_VAR(v_Ways, [] ,[WayName])
346
347 allowed_combination way = and [ x `allowedWith` y 
348                               | x <- way, y <- way, x < y ]
349   where
350         -- Note ordering in these tests: the left argument is
351         -- <= the right argument, according to the Ord instance
352         -- on Way above.
353
354         -- debug is allowed with everything
355         _ `allowedWith` WayDebug                = True
356         WayDebug `allowedWith` _                = True
357
358         WayThreaded `allowedWith` WayProf       = True
359         WayProf `allowedWith` WayUnreg          = True
360         WayProf `allowedWith` WaySMP            = True
361         WayProf `allowedWith` WayNDP            = True
362         _ `allowedWith` _                       = False
363
364
365 findBuildTag :: IO [String]  -- new options
366 findBuildTag = do
367   way_names <- readIORef v_Ways
368   let ws = sort way_names
369   if not (allowed_combination ws)
370       then throwDyn (CmdLineError $
371                     "combination not supported: "  ++
372                     foldr1 (\a b -> a ++ '/':b) 
373                     (map (wayName . lkupWay) ws))
374       else let ways    = map lkupWay ws
375                tag     = mkBuildTag (filter (not.wayRTSOnly) ways)
376                rts_tag = mkBuildTag ways
377                flags   = map wayOpts ways
378            in do
379            writeIORef v_Build_tag tag
380            writeIORef v_RTS_Build_tag rts_tag
381            return (concat flags)
382
383 mkBuildTag :: [Way] -> String
384 mkBuildTag ways = concat (intersperse "_" (map wayTag ways))
385
386 lkupWay w = 
387    case lookup w way_details of
388         Nothing -> error "findBuildTag"
389         Just details -> details
390
391 data Way = Way {
392   wayTag     :: String,
393   wayRTSOnly :: Bool,
394   wayName    :: String,
395   wayOpts    :: [String]
396   }
397
398 way_details :: [ (WayName, Way) ]
399 way_details =
400   [ (WayThreaded, Way "thr" True "Threaded" [
401 #if defined(freebsd_TARGET_OS)
402           "-optc-pthread"
403         , "-optl-pthread"
404 #endif
405         ] ),
406
407     (WayDebug, Way "debug" True "Debug" [] ),
408
409     (WayProf, Way  "p" False "Profiling"
410         [ "-fscc-profiling"
411         , "-DPROFILING"
412         , "-optc-DPROFILING"
413         , "-fvia-C" ]),
414
415     (WayTicky, Way  "t" False "Ticky-ticky Profiling"  
416         [ "-fticky-ticky"
417         , "-DTICKY_TICKY"
418         , "-optc-DTICKY_TICKY"
419         , "-fvia-C" ]),
420
421     (WayUnreg, Way  "u" False "Unregisterised" 
422         unregFlags ),
423
424     -- optl's below to tell linker where to find the PVM library -- HWL
425     (WayPar, Way  "mp" False "Parallel" 
426         [ "-fparallel"
427         , "-D__PARALLEL_HASKELL__"
428         , "-optc-DPAR"
429         , "-package concurrent"
430         , "-optc-w"
431         , "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}"
432         , "-optl-lpvm3"
433         , "-optl-lgpvm3"
434         , "-fvia-C" ]),
435
436     -- at the moment we only change the RTS and could share compiler and libs!
437     (WayPar, Way  "mt" False "Parallel ticky profiling" 
438         [ "-fparallel"
439         , "-D__PARALLEL_HASKELL__"
440         , "-optc-DPAR"
441         , "-optc-DPAR_TICKY"
442         , "-package concurrent"
443         , "-optc-w"
444         , "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}"
445         , "-optl-lpvm3"
446         , "-optl-lgpvm3"
447         , "-fvia-C" ]),
448
449     (WayPar, Way  "md" False "Distributed" 
450         [ "-fparallel"
451         , "-D__PARALLEL_HASKELL__"
452         , "-D__DISTRIBUTED_HASKELL__"
453         , "-optc-DPAR"
454         , "-optc-DDIST"
455         , "-package concurrent"
456         , "-optc-w"
457         , "-optl-L${PVM_ROOT}/lib/${PVM_ARCH}"
458         , "-optl-lpvm3"
459         , "-optl-lgpvm3"
460         , "-fvia-C" ]),
461
462     (WayGran, Way  "mg" False "GranSim"
463         [ "-fgransim"
464         , "-D__GRANSIM__"
465         , "-optc-DGRAN"
466         , "-package concurrent"
467         , "-fvia-C" ]),
468
469     (WaySMP, Way  "s" False "SMP"
470         [ "-fsmp"
471         , "-optc-pthread"
472 #ifndef freebsd_TARGET_OS
473         , "-optl-pthread"
474 #endif
475         , "-optc-DSMP"
476         , "-fvia-C" ]),
477
478     (WayNDP, Way  "ndp" False "Nested data parallelism"
479         [ "-fparr"
480         , "-fflatten"]),
481
482     (WayUser_a,  Way  "a"  False "User way 'a'"  ["$WAY_a_REAL_OPTS"]), 
483     (WayUser_b,  Way  "b"  False "User way 'b'"  ["$WAY_b_REAL_OPTS"]), 
484     (WayUser_c,  Way  "c"  False "User way 'c'"  ["$WAY_c_REAL_OPTS"]), 
485     (WayUser_d,  Way  "d"  False "User way 'd'"  ["$WAY_d_REAL_OPTS"]), 
486     (WayUser_e,  Way  "e"  False "User way 'e'"  ["$WAY_e_REAL_OPTS"]), 
487     (WayUser_f,  Way  "f"  False "User way 'f'"  ["$WAY_f_REAL_OPTS"]), 
488     (WayUser_g,  Way  "g"  False "User way 'g'"  ["$WAY_g_REAL_OPTS"]), 
489     (WayUser_h,  Way  "h"  False "User way 'h'"  ["$WAY_h_REAL_OPTS"]), 
490     (WayUser_i,  Way  "i"  False "User way 'i'"  ["$WAY_i_REAL_OPTS"]), 
491     (WayUser_j,  Way  "j"  False "User way 'j'"  ["$WAY_j_REAL_OPTS"]), 
492     (WayUser_k,  Way  "k"  False "User way 'k'"  ["$WAY_k_REAL_OPTS"]), 
493     (WayUser_l,  Way  "l"  False "User way 'l'"  ["$WAY_l_REAL_OPTS"]), 
494     (WayUser_m,  Way  "m"  False "User way 'm'"  ["$WAY_m_REAL_OPTS"]), 
495     (WayUser_n,  Way  "n"  False "User way 'n'"  ["$WAY_n_REAL_OPTS"]), 
496     (WayUser_o,  Way  "o"  False "User way 'o'"  ["$WAY_o_REAL_OPTS"]), 
497     (WayUser_A,  Way  "A"  False "User way 'A'"  ["$WAY_A_REAL_OPTS"]), 
498     (WayUser_B,  Way  "B"  False "User way 'B'"  ["$WAY_B_REAL_OPTS"]) 
499   ]
500
501 unregFlags = 
502    [ "-optc-DNO_REGS"
503    , "-optc-DUSE_MINIINTERPRETER"
504    , "-fno-asm-mangling"
505    , "-funregisterised"
506    , "-fvia-C" ]
507
508 -----------------------------------------------------------------------------
509 -- Options for particular phases
510
511 GLOBAL_VAR(v_Opt_dep,    [], [String])
512 GLOBAL_VAR(v_Anti_opt_C, [], [String])
513 GLOBAL_VAR(v_Opt_C,      [], [String])
514 GLOBAL_VAR(v_Opt_l,      [], [String])
515 GLOBAL_VAR(v_Opt_dll,    [], [String])
516
517 getStaticOpts :: IORef [String] -> IO [String]
518 getStaticOpts ref = readIORef ref >>= return . reverse