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