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