b65b4e9b873cba4ec3c71d7f351581f590a62cba
[ghc-hetmet.git] / ghc / compiler / main / SysTools.lhs
1 -----------------------------------------------------------------------------
2 -- Access to system tools: gcc, cp, rm etc
3 --
4 -- (c) The University of Glasgow 2000
5 --
6 -----------------------------------------------------------------------------
7
8 \begin{code}
9 module SysTools (
10         -- Initialisation
11         initSysTools,
12         setPgm,                 -- String -> IO ()
13                                 -- Command-line override
14         setDryRun,
15
16         packageConfigPath,      -- IO String    
17                                 -- Where package.conf is
18
19         -- Interface to system tools
20         runUnlit, runCpp, runCc, -- [String] -> IO ()
21         runMangle, runSplit,     -- [String] -> IO ()
22         runAs, runLink,          -- [String] -> IO ()
23         runMkDLL,
24
25         touch,                  -- String -> String -> IO ()
26         copy,                   -- String -> String -> String -> IO ()
27         
28         -- Temporary-file management
29         setTmpDir,
30         newTempName,
31         cleanTempFiles, cleanTempFilesExcept, removeTmpFiles,
32         addFilesToClean,
33
34         -- System interface
35         getProcessID,           -- IO Int
36         System.system,          -- String -> IO Int     -- System.system
37
38         -- Misc
39         showGhcUsage,           -- IO ()        Shows usage message and exits
40         getSysMan,              -- IO String    Parallel system only
41         dosifyPath,             -- String -> String
42
43         runSomething    -- ToDo: make private
44  ) where
45
46 import DriverUtil
47 import Config
48 import Outputable
49 import Panic            ( progName, GhcException(..) )
50 import Util             ( global )
51 import CmdLineOpts      ( dynFlag, verbosity )
52
53 import List             ( intersperse, isPrefixOf )
54 import Exception        ( throwDyn, catchAllIO )
55 import IO               ( openFile, hClose, IOMode(..),
56                           hPutStr, hPutChar, hPutStrLn, hFlush, stderr
57                         )
58 import Directory        ( doesFileExist, removeFile )
59 import IOExts           ( IORef, readIORef, writeIORef )
60 import Monad            ( when, unless )
61 import qualified System
62 import System           ( ExitCode(..) )
63
64 #include "../includes/config.h"
65
66 #if !defined(mingw32_TARGET_OS)
67 import qualified Posix
68 #else
69 import Addr              ( nullAddr )
70 #endif
71
72 #include "HsVersions.h"
73
74 {-# DEPRECATED runSomething "runSomething should be private to SysTools" #-}
75
76 \end{code}
77
78
79                 The configuration story
80                 ~~~~~~~~~~~~~~~~~~~~~~~
81
82 GHC needs various support files (library packages, RTS etc), plus
83 various auxiliary programs (cp, gcc, etc).  It finds these in one
84 of two places:
85
86 * When running as an *installed program*, GHC finds most of this support
87   stuff in the installed library tree.  The path to this tree is passed
88   to GHC via the -B flag, and given to initSysTools .
89
90 * When running *in-place* in a build tree, GHC finds most of this support
91   stuff in the build tree.  The path to the build tree is, again passed
92   to GHC via -B. 
93
94 GHC tells which of the two is the case by seeing whether package.conf
95 is in TopDir [installed] or in TopDir/ghc/driver [inplace] (what a hack).
96
97
98 SysTools.initSysProgs figures out exactly where all the auxiliary programs
99 are, and initialises mutable variables to make it easy to call them.
100 To to this, it makes use of definitions in Config.hs, which is a Haskell
101 file containing variables whose value is figured out by the build system.
102
103 Config.hs contains two sorts of things
104
105   cGCC,         The *names* of the programs
106   cCPP            e.g.  cGCC = gcc
107   cUNLIT                cCPP = gcc -E
108   etc           They do *not* include paths
109                                 
110
111   cUNLIT_DIR    The *path* to the directory containing unlit, split etc
112   cSPLIT_DIR    *relative* to the root of the build tree,
113                 for use when running *in-place* in a build tree (only)
114                 
115
116
117 %************************************************************************
118 %*                                                                      *
119 \subsection{Global variables to contain system programs}
120 %*                                                                      *
121 %************************************************************************
122
123 \begin{code}
124 GLOBAL_VAR(v_Pgm_L,     error "pgm_L",   String)        -- unlit
125 GLOBAL_VAR(v_Pgm_P,     error "pgm_P",   String)        -- cpp
126 GLOBAL_VAR(v_Pgm_c,     error "pgm_c",   String)        -- gcc
127 GLOBAL_VAR(v_Pgm_m,     error "pgm_m",   String)        -- asm code mangler
128 GLOBAL_VAR(v_Pgm_s,     error "pgm_s",   String)        -- asm code splitter
129 GLOBAL_VAR(v_Pgm_a,     error "pgm_a",   String)        -- as
130 GLOBAL_VAR(v_Pgm_l,     error "pgm_l",   String)        -- ld
131 GLOBAL_VAR(v_Pgm_MkDLL, error "pgm_dll", String)        -- mkdll
132
133 GLOBAL_VAR(v_Pgm_PERL, error "pgm_PERL", String)        -- perl
134 GLOBAL_VAR(v_Pgm_T,    error "pgm_T",    String)        -- touch
135 GLOBAL_VAR(v_Pgm_CP,   error "pgm_CP",   String)        -- cp
136
137 GLOBAL_VAR(v_Path_package_config, error "path_package_config", String)
138 GLOBAL_VAR(v_Path_usage,          error "ghc_usage.txt",       String)
139
140 -- Parallel system only
141 GLOBAL_VAR(v_Pgm_sysman, error "pgm_sysman", String)    -- system manager
142 \end{code}
143
144
145 %************************************************************************
146 %*                                                                      *
147 \subsection{Initialisation}
148 %*                                                                      *
149 %************************************************************************
150
151 \begin{code}
152 initSysTools :: [String]        -- Command-line arguments starting "-B"
153
154              -> IO String       -- Set all the mutable variables above, holding 
155                                 --      (a) the system programs
156                                 --      (b) the package-config file
157                                 --      (c) the GHC usage message
158                                 -- Return TopDir
159
160
161 initSysTools minusB_args
162   = do  { (am_installed, top_dir) <- getTopDir minusB_args
163                 -- top_dir
164                 --      for "installed" this is the root of GHC's support files
165                 --      for "in-place" it is the root of the build tree
166
167         ; let installed   pgm = top_dir `slash` "extra-bin" `slash` pgm
168               inplace dir pgm = top_dir `slash` dir         `slash` pgm
169
170         ; let pkgconfig_path | am_installed = top_dir `slash` "package.conf"
171                              | otherwise    = top_dir `slash` cGHC_DRIVER_DIR `slash` "package.conf.inplace"
172
173         -- Check that the in-place package config exists if 
174         -- the installed one does not (we need at least one!)
175         ; config_exists <- doesFileExist pkgconfig_path
176         ; if config_exists then return ()
177           else throwDyn (InstallationError 
178                            ("Can't find package.conf in " ++ pkgconfig_path))
179
180         -- The GHC usage help message is found similarly to the package configuration
181         ; let ghc_usage_msg_path | am_installed = installed "ghc-usage.txt"
182                                  | otherwise    = inplace cGHC_DRIVER_DIR "ghc-usage.txt"
183
184
185         -- For all systems, unlit, split, mangle are GHC utilities
186         -- architecture-specific stuff is done when building Config.hs
187         ; let unlit_path  | am_installed = installed cGHC_UNLIT
188                           | otherwise    = inplace cGHC_UNLIT_DIR cGHC_UNLIT
189
190                 -- split and mangle are Perl scripts
191               split_script  | am_installed = installed cGHC_SPLIT
192                             | otherwise    = inplace cGHC_SPLIT_DIR cGHC_SPLIT
193               mangle_script | am_installed = installed cGHC_MANGLER
194                             | otherwise    = inplace cGHC_MANGLER_DIR cGHC_MANGLER
195
196
197 #if defined(mingw32_TARGET_OS)
198         --              WINDOWS-SPECIFIC STUFF
199         -- On Windows, gcc and friends are distributed with GHC,
200         --      so when "installed" we look in TopDir/bin
201         -- When "in-place" we look wherever the build-time configure 
202         --      script found them
203         ; let cpp_path  | am_installed = installed cRAWCPP
204                         | otherwise    = cRAWCPP
205               gcc_path  | am_installed = installed cGCC
206                         | otherwise    = cGCC
207               perl_path | am_installed = installed cGHC_PERL
208                         | otherwise    = cGHC_PERL
209
210         -- 'touch' is a GHC util for Windows, and similarly unlit, mangle
211         ; let touch_path  | am_installed = installed cGHC_TOUCHY
212                           | otherwise    = inplace cGHC_TOUCHY_DIR cGHC_TOUCHY
213
214         -- On Win32 we don't want to rely on #!/bin/perl, so we prepend 
215         -- a call to Perl to get the invocation of split and mangle
216         ; let split_path  = perl_path ++ " " ++ split_script
217               mangle_path = perl_path ++ " " ++ mangle_script
218
219         ; let mkdll_path = cMKDLL
220 #else
221         --              UNIX-SPECIFIC STUFF
222         -- On Unix, the "standard" tools are assumed to be
223         -- in the same place whether we are running "in-place" or "installed"
224         -- That place is wherever the build-time configure script found them.
225         ; let   cpp_path   = cRAWCPP
226                 gcc_path   = cGCC
227                 touch_path = cGHC_TOUCHY
228                 perl_path  = cGHC_PERL
229                 mkdll_path = panic "Cant build DLLs on a non-Win32 system"
230
231         -- On Unix, for some historical reason, we do an install-time
232         -- configure to find Perl, and slam that on the front of
233         -- the installed script; so we can invoke them directly 
234         -- (not via perl)
235         -- a call to Perl to get the invocation of split and mangle
236         ; let split_path  = split_script
237               mangle_path = mangle_script
238
239 #endif
240
241         -- For all systems, copy and remove are provided by the host 
242         -- system; architecture-specific stuff is done when building Config.hs
243         ; let   cp_path = cGHC_CP
244         
245         -- Other things being equal, as and ld are simply gcc
246         ; let   as_path  = gcc_path
247                 ld_path  = gcc_path
248
249                                        
250         -- Initialise the global vars
251         ; writeIORef v_Path_package_config pkgconfig_path
252         ; writeIORef v_Path_usage          ghc_usage_msg_path
253
254         ; writeIORef v_Pgm_sysman          (top_dir ++ "/ghc/rts/parallel/SysMan")
255                 -- Hans: this isn't right in general, but you can 
256                 -- elaborate it in the same way as the others
257
258         ; writeIORef v_Pgm_L               unlit_path
259         ; writeIORef v_Pgm_P               cpp_path
260         ; writeIORef v_Pgm_c               gcc_path
261         ; writeIORef v_Pgm_m               mangle_path
262         ; writeIORef v_Pgm_s               split_path
263         ; writeIORef v_Pgm_a               as_path
264         ; writeIORef v_Pgm_l               ld_path
265         ; writeIORef v_Pgm_MkDLL           mkdll_path
266         ; writeIORef v_Pgm_T               touch_path
267         ; writeIORef v_Pgm_CP              cp_path
268         ; writeIORef v_Pgm_PERL            perl_path
269
270         ; return top_dir
271         }
272 \end{code}
273
274 setPgm is called when a command-line option like
275         -pgmLld
276 is used to override a particular program with a new onw
277
278 \begin{code}
279 setPgm :: String -> IO ()
280 -- The string is the flag, minus the '-pgm' prefix
281 -- So the first character says which program to override
282
283 setPgm ('P' : pgm) = writeIORef v_Pgm_P pgm
284 setPgm ('c' : pgm) = writeIORef v_Pgm_c pgm
285 setPgm ('m' : pgm) = writeIORef v_Pgm_m pgm
286 setPgm ('s' : pgm) = writeIORef v_Pgm_s pgm
287 setPgm ('a' : pgm) = writeIORef v_Pgm_a pgm
288 setPgm ('l' : pgm) = writeIORef v_Pgm_l pgm
289 setPgm pgm         = unknownFlagErr ("-pgm" ++ pgm)
290 \end{code}
291
292
293 \begin{code}
294 -- Find TopDir
295 --      for "installed" this is the root of GHC's support files
296 --      for "in-place" it is the root of the build tree
297 --
298 -- Plan of action:
299 -- 1. Set proto_top_dir
300 --      a) look for (the last) -B flag, and use it
301 --      b) if there are no -B flags, get the directory 
302 --         where GHC is running
303 --
304 -- 2. If package.conf exists in proto_top_dir, we are running
305 --      installed; and TopDir = proto_top_dir
306 --
307 -- 3. Otherwise we are running in-place, so
308 --      proto_top_dir will be /...stuff.../ghc/compiler
309 --      Set TopDir to /...stuff..., which is the root of the build tree
310 --
311 -- This is very gruesome indeed
312
313 getTopDir :: [String]
314           -> IO (Bool,          -- True <=> am installed, False <=> in-place
315                  String)        -- TopDir
316
317 getTopDir minusbs
318   = do { proto_top_dir <- get_proto
319
320         -- Discover whether we're running in a build tree or in an installation,
321         -- by looking for the package configuration file.
322        ; am_installed <- doesFileExist (proto_top_dir `slash` "package.conf")
323
324        ; if am_installed then
325             return (True, proto_top_dir)
326          else
327             return (False, remove_suffix proto_top_dir)
328        }
329   where
330     get_proto | not (null minusbs) 
331               = return (dosifyPath (drop 2 (last minusbs)))
332               | otherwise          
333               = do { maybe_exec_dir <- getExecDir       -- Get directory of executable
334                    ; case maybe_exec_dir of             -- (only works on Windows)
335                         Nothing  -> throwDyn (InstallationError ("missing -B<dir> option"))
336                         Just dir -> return dir }
337
338     remove_suffix dir   -- "/...stuff.../ghc/compiler" --> "/...stuff..."
339         = ASSERT2( not (null p1) && 
340                    not (null p2) && 
341                    dosifyPath dir == dosifyPath (top_dir ++ "/ghc/compiler"),
342                    text dir )
343           top_dir
344         where
345          p1      = dropWhile (not . isSlash) (reverse dir)
346          p2      = dropWhile (not . isSlash) (tail p1)  -- head is '/'
347          top_dir = reverse (tail p2)                    -- head is '/'
348 \end{code}
349
350
351 %************************************************************************
352 %*                                                                      *
353 \subsection{Running an external program}
354 n%*                                                                     *
355 %************************************************************************
356
357
358 \begin{code}
359 runUnlit :: [String] -> IO ()
360 runUnlit args = do p <- readIORef v_Pgm_L
361                    runSomething "Literate pre-processor" p args
362
363 runCpp :: [String] -> IO ()
364 runCpp args =   do p <- readIORef v_Pgm_P
365                    runSomething "C pre-processor" p args
366
367 runCc :: [String] -> IO ()
368 runCc args =   do p <- readIORef v_Pgm_c
369                   runSomething "C Compiler" p args
370
371 runMangle :: [String] -> IO ()
372 runMangle args = do p <- readIORef v_Pgm_m
373                     runSomething "Mangler" p args
374
375 runSplit :: [String] -> IO ()
376 runSplit args = do p <- readIORef v_Pgm_s
377                    runSomething "Splitter" p args
378
379 runAs :: [String] -> IO ()
380 runAs args = do p <- readIORef v_Pgm_a
381                 runSomething "Assembler" p args
382
383 runLink :: [String] -> IO ()
384 runLink args = do p <- readIORef v_Pgm_l
385                   runSomething "Linker" p args
386
387 runMkDLL :: [String] -> IO ()
388 runMkDLL args = do p <- readIORef v_Pgm_MkDLL
389                    runSomething "Make DLL" p args
390
391 touch :: String -> String -> IO ()
392 touch purpose arg =  do p <- readIORef v_Pgm_T
393                         runSomething purpose p [arg]
394
395 copy :: String -> String -> String -> IO ()
396 copy purpose from to = do p <- readIORef v_Pgm_CP
397                           runSomething purpose p [from,to]
398 \end{code}
399
400 \begin{code}
401 getSysMan :: IO String  -- How to invoke the system manager 
402                         -- (parallel system only)
403 getSysMan = readIORef v_Pgm_sysman
404 \end{code}
405
406 %************************************************************************
407 %*                                                                      *
408 \subsection{GHC Usage message}
409 %*                                                                      *
410 %************************************************************************
411
412 Show the usage message and exit
413
414 \begin{code}
415 showGhcUsage = do { usage_path <- readIORef v_Path_usage
416                   ; usage      <- readFile usage_path
417                   ; dump usage
418                   ; System.exitWith System.ExitSuccess }
419   where
420      dump ""          = return ()
421      dump ('$':'$':s) = hPutStr stderr progName >> dump s
422      dump (c:s)       = hPutChar stderr c >> dump s
423
424 packageConfigPath = readIORef v_Path_package_config
425 \end{code}
426
427
428 %************************************************************************
429 %*                                                                      *
430 \subsection{Managing temporary files
431 %*                                                                      *
432 %************************************************************************
433
434 One reason this code is here is because SysTools.system needs to make
435 a temporary file.
436
437 \begin{code}
438 GLOBAL_VAR(v_FilesToClean, [],               [String] )
439 GLOBAL_VAR(v_TmpDir,       cDEFAULT_TMPDIR,  String   )
440         -- v_TmpDir has no closing '/'
441 \end{code}
442
443 \begin{code}
444 setTmpDir dir = writeIORef v_TmpDir dir
445
446 cleanTempFiles :: Int -> IO ()
447 cleanTempFiles verb = do fs <- readIORef v_FilesToClean
448                          removeTmpFiles verb fs
449
450 cleanTempFilesExcept :: Int -> [FilePath] -> IO ()
451 cleanTempFilesExcept verb dont_delete
452   = do fs <- readIORef v_FilesToClean
453        let leftovers = filter (`notElem` dont_delete) fs
454        removeTmpFiles verb leftovers
455        writeIORef v_FilesToClean dont_delete
456
457
458 -- find a temporary name that doesn't already exist.
459 newTempName :: Suffix -> IO FilePath
460 newTempName extn
461   = do x <- getProcessID
462        tmp_dir <- readIORef v_TmpDir
463        findTempName tmp_dir x
464   where 
465     findTempName tmp_dir x
466       = do let filename = tmp_dir ++ "/ghc" ++ show x ++ '.':extn
467            b  <- doesFileExist filename
468            if b then findTempName tmp_dir (x+1)
469                 else do add v_FilesToClean filename -- clean it up later
470                         return filename
471
472 addFilesToClean :: [FilePath] -> IO ()
473 -- May include wildcards [used by DriverPipeline.run_phase SplitMangle]
474 addFilesToClean files = mapM_ (add v_FilesToClean) files
475
476 removeTmpFiles :: Int -> [FilePath] -> IO ()
477 removeTmpFiles verb fs
478   = traceCmd "Deleting temp files" 
479              ("Deleting: " ++ concat (intersperse " " fs))
480              (mapM_ rm fs)
481   where
482     rm f = removeFile f `catchAllIO`
483                 (\exn -> hPutStrLn stderr ("Warning: deleting non-existent " ++ f) >>
484                          return ())
485
486 \end{code}
487
488
489 %************************************************************************
490 %*                                                                      *
491 \subsection{Running a program}
492 %*                                                                      *
493 %************************************************************************
494
495 \begin{code}
496 GLOBAL_VAR(v_Dry_run, False, Bool)
497
498 setDryRun :: IO () 
499 setDryRun = writeIORef v_Dry_run True
500
501 -----------------------------------------------------------------------------
502 -- Running an external program
503
504 runSomething :: String          -- For -v message
505              -> String          -- Command name (possibly a full path)
506                                 --      assumed already dos-ified
507              -> [String]        -- Arguments
508                                 --      runSomthing will dos-ify them
509              -> IO ()
510
511 runSomething phase_name pgm args
512  = traceCmd phase_name cmd_line $
513    do   { exit_code <- System.system cmd_line
514         ; if exit_code /= ExitSuccess
515           then throwDyn (PhaseFailed phase_name exit_code)
516           else return ()
517         }
518   where
519     cmd_line = unwords (pgm : dosifyPaths args)
520
521 traceCmd :: String -> String -> IO () -> IO ()
522 -- a) trace the command (at two levels of verbosity)
523 -- b) don't do it at all if dry-run is set
524 traceCmd phase_name cmd_line action
525  = do   { verb <- dynFlag verbosity
526         ; when (verb >= 2) $ hPutStrLn stderr ("*** " ++ phase_name)
527         ; when (verb >= 3) $ hPutStrLn stderr cmd_line
528         ; hFlush stderr
529         
530            -- Test for -n flag
531         ; n <- readIORef v_Dry_run
532         ; unless n $ do {
533
534            -- And run it!
535         ; action `catchAllIO` handle_exn verb
536         }}
537   where
538     handle_exn verb exn = do { when (verb >= 2) (hPutStr   stderr "\n")
539                              ; when (verb >= 3) (hPutStrLn stderr ("Failed: " ++ cmd_line))
540                              ; throwDyn (PhaseFailed phase_name (ExitFailure 1)) }
541 \end{code}
542
543
544 %************************************************************************
545 %*                                                                      *
546 \subsection{Support code}
547 %*                                                                      *
548 %************************************************************************
549
550
551 \begin{code}
552 -----------------------------------------------------------------------------
553 -- Convert filepath into MSDOS form.
554
555 dosifyPaths :: [String] -> [String]
556 dosifyPath  :: String -> String
557 -- dosifyPath does two things
558 -- a) change '/' to '\'
559 -- b) remove initial '/cygdrive/'
560
561 #if defined(mingw32_TARGET_OS)
562 dosifyPaths xs = map dosifyPath xs
563
564 dosifyPath stuff
565   = subst '/' '\\' real_stuff
566  where
567    -- fully convince myself that /cygdrive/ prefixes cannot
568    -- really appear here.
569   cygdrive_prefix = "/cygdrive/"
570
571   real_stuff
572     | cygdrive_prefix `isPrefixOf` stuff = drop (length cygdrive_prefix) stuff
573     | otherwise = stuff
574    
575   subst a b ls = map (\ x -> if x == a then b else x) ls
576 #else
577 dosifyPaths xs = xs
578 dosifyPath  xs = xs
579 #endif
580
581 -----------------------------------------------------------------------------
582 -- Path name construction
583 --      At the moment, we always use '/' and rely on dosifyPath 
584 --      to switch to DOS pathnames when necessary
585
586 slash            :: String -> String -> String
587 absPath, relPath :: [String] -> String
588
589 isSlash '/'   = True
590 isSlash '\\'  = True
591 isSlash other = False
592
593 relPath [] = ""
594 relPath xs = foldr1 slash xs
595
596 absPath xs = "" `slash` relPath xs
597
598 #if defined(mingw32_TARGET_OS)
599 slash s1 s2 = s1 ++ ('\\' : s2)
600 #else
601 slash s1 s2 = s1 ++ ('/' : s2)
602 #endif
603
604 -----------------------------------------------------------------------------
605 -- Define       myGetProcessId :: IO Int
606 --              getExecDir     :: IO (Maybe String)
607
608 #ifdef mingw32_TARGET_OS
609 foreign import "_getpid" getProcessID :: IO Int -- relies on Int == Int32 on Windows
610
611 getExecDir :: IO (Maybe String)
612 getExecDir = return Nothing
613 {-
614 foreign import stdcall "GetCurrentDirectoryA" getCurrentDirectory :: Int32 -> CString -> IO Int32
615 getExecDir = do len <- getCurrentDirectory 0 nullAddr
616                 buf <- mallocArray (fromIntegral len)
617                 ret <- getCurrentDirectory len buf
618                 if ret == 0 then return Nothing
619                             else do s <- peekCString buf
620                                     destructArray (fromIntegral len) buf
621                                     return (Just s)
622 -}
623 #else
624 getProcessID :: IO Int
625 getProcessID = Posix.getProcessID
626 getExecDir :: IO (Maybe String) = do return Nothing
627 #endif
628 \end{code}