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