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