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