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