[project @ 2001-07-16 10:48:42 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                                          ++ " -I" ++ installed "include/mingw")
247                         | otherwise    = cGCC
248               perl_path | am_installed = installed_bin cGHC_PERL
249                         | otherwise    = cGHC_PERL
250
251         -- 'touch' is a GHC util for Windows, and similarly unlit, mangle
252         ; let touch_path  | am_installed = installed_bin cGHC_TOUCHY
253                           | otherwise    = inplace cGHC_TOUCHY_DIR cGHC_TOUCHY
254
255         -- On Win32 we don't want to rely on #!/bin/perl, so we prepend 
256         -- a call to Perl to get the invocation of split and mangle
257         ; let split_path  = perl_path ++ " " ++ split_script
258               mangle_path = perl_path ++ " " ++ mangle_script
259
260         ; let mkdll_path = cMKDLL
261 #else
262         --              UNIX-SPECIFIC STUFF
263         -- On Unix, the "standard" tools are assumed to be
264         -- in the same place whether we are running "in-place" or "installed"
265         -- That place is wherever the build-time configure script found them.
266         ; let   gcc_path   = cGCC
267                 touch_path = cGHC_TOUCHY
268                 mkdll_path = panic "Can't build DLLs on a non-Win32 system"
269
270         -- On Unix, scripts are invoked using the '#!' method.  Binary
271         -- installations of GHC on Unix place the correct line on the front
272         -- of the script at installation time, so we don't want to wire-in
273         -- our knowledge of $(PERL) on the host system here.
274         ; let split_path  = split_script
275               mangle_path = mangle_script
276 #endif
277
278         -- cpp is derived from gcc on all platforms
279         ; let cpp_path  = gcc_path ++ " -E " ++ cRAWCPP_FLAGS
280
281         -- For all systems, copy and remove are provided by the host
282         -- system; architecture-specific stuff is done when building Config.hs
283         ; let   cp_path = cGHC_CP
284         
285         -- Other things being equal, as and ld are simply gcc
286         ; let   as_path  = gcc_path
287                 ld_path  = gcc_path
288
289                                        
290         -- Initialise the global vars
291         ; writeIORef v_Path_package_config pkgconfig_path
292         ; writeIORef v_Path_usage          ghc_usage_msg_path
293
294         ; writeIORef v_Pgm_sysman          (top_dir ++ "/ghc/rts/parallel/SysMan")
295                 -- Hans: this isn't right in general, but you can 
296                 -- elaborate it in the same way as the others
297
298         ; writeIORef v_Pgm_L               unlit_path
299         ; writeIORef v_Pgm_P               cpp_path
300         ; writeIORef v_Pgm_c               gcc_path
301         ; writeIORef v_Pgm_m               mangle_path
302         ; writeIORef v_Pgm_s               split_path
303         ; writeIORef v_Pgm_a               as_path
304         ; writeIORef v_Pgm_l               ld_path
305         ; writeIORef v_Pgm_MkDLL           mkdll_path
306         ; writeIORef v_Pgm_T               touch_path
307         ; writeIORef v_Pgm_CP              cp_path
308
309         ; return top_dir
310         }
311 \end{code}
312
313 setPgm is called when a command-line option like
314         -pgmLld
315 is used to override a particular program with a new onw
316
317 \begin{code}
318 setPgm :: String -> IO ()
319 -- The string is the flag, minus the '-pgm' prefix
320 -- So the first character says which program to override
321
322 setPgm ('P' : pgm) = writeIORef v_Pgm_P pgm
323 setPgm ('c' : pgm) = writeIORef v_Pgm_c pgm
324 setPgm ('m' : pgm) = writeIORef v_Pgm_m pgm
325 setPgm ('s' : pgm) = writeIORef v_Pgm_s pgm
326 setPgm ('a' : pgm) = writeIORef v_Pgm_a pgm
327 setPgm ('l' : pgm) = writeIORef v_Pgm_l pgm
328 setPgm pgm         = unknownFlagErr ("-pgm" ++ pgm)
329 \end{code}
330
331
332 \begin{code}
333 -- Find TopDir
334 --      for "installed" this is the root of GHC's support files
335 --      for "in-place" it is the root of the build tree
336 --
337 -- Plan of action:
338 -- 1. Set proto_top_dir
339 --      a) look for (the last) -B flag, and use it
340 --      b) if there are no -B flags, get the directory 
341 --         where GHC is running (only on Windows)
342 --
343 -- 2. If package.conf exists in proto_top_dir, we are running
344 --      installed; and TopDir = proto_top_dir
345 --
346 -- 3. Otherwise we are running in-place, so
347 --      proto_top_dir will be /...stuff.../ghc/compiler
348 --      Set TopDir to /...stuff..., which is the root of the build tree
349 --
350 -- This is very gruesome indeed
351
352 getTopDir :: [String]
353           -> IO (Bool,          -- True <=> am installed, False <=> in-place
354                  String)        -- TopDir (in Unix format '/' separated)
355
356 getTopDir minusbs
357   = do { top_dir <- get_proto
358         -- Discover whether we're running in a build tree or in an installation,
359         -- by looking for the package configuration file.
360        ; am_installed <- doesFileExist (top_dir `slash` "package.conf")
361
362        ; return (am_installed, top_dir)
363        }
364   where
365     -- get_proto returns a Unix-format path
366     get_proto | not (null minusbs)
367               = return (unDosifyPath (drop 2 (last minusbs)))   -- 2 for "-B"
368               | otherwise          
369               = do { maybe_exec_dir <- getExecDir -- Get directory of executable
370                    ; case maybe_exec_dir of       -- (only works on Windows; 
371                                                   --  returns Nothing on Unix)
372                         Nothing  -> throwDyn (InstallationError "missing -B<dir> option")
373                         Just dir -> return (unDosifyPath dir)
374                    }
375 \end{code}
376
377
378 %************************************************************************
379 %*                                                                      *
380 \subsection{Running an external program}
381 n%*                                                                     *
382 %************************************************************************
383
384
385 \begin{code}
386 runUnlit :: [String] -> IO ()
387 runUnlit args = do p <- readIORef v_Pgm_L
388                    runSomething "Literate pre-processor" p args
389
390 runCpp :: [String] -> IO ()
391 runCpp args =   do p <- readIORef v_Pgm_P
392                    runSomething "C pre-processor" p args
393
394 runCc :: [String] -> IO ()
395 runCc args =   do p <- readIORef v_Pgm_c
396                   runSomething "C Compiler" p args
397
398 runMangle :: [String] -> IO ()
399 runMangle args = do p <- readIORef v_Pgm_m
400                     runSomething "Mangler" p args
401
402 runSplit :: [String] -> IO ()
403 runSplit args = do p <- readIORef v_Pgm_s
404                    runSomething "Splitter" p args
405
406 runAs :: [String] -> IO ()
407 runAs args = do p <- readIORef v_Pgm_a
408                 runSomething "Assembler" p args
409
410 runLink :: [String] -> IO ()
411 runLink args = do p <- readIORef v_Pgm_l
412                   runSomething "Linker" p args
413
414 runMkDLL :: [String] -> IO ()
415 runMkDLL args = do p <- readIORef v_Pgm_MkDLL
416                    runSomething "Make DLL" p args
417
418 touch :: String -> String -> IO ()
419 touch purpose arg =  do p <- readIORef v_Pgm_T
420                         runSomething purpose p [arg]
421
422 copy :: String -> String -> String -> IO ()
423 copy purpose from to = do
424   verb <- dynFlag verbosity
425   when (verb >= 2) $ hPutStrLn stderr ("*** " ++ purpose)
426
427   h <- openFile to WriteMode
428   ls <- readFile from -- inefficient, but it'll do for now.
429                       -- ToDo: speed up via slurping.
430   hPutStr h ls
431   hClose h
432 \end{code}
433
434 \begin{code}
435 getSysMan :: IO String  -- How to invoke the system manager 
436                         -- (parallel system only)
437 getSysMan = readIORef v_Pgm_sysman
438 \end{code}
439
440 %************************************************************************
441 %*                                                                      *
442 \subsection{GHC Usage message}
443 %*                                                                      *
444 %************************************************************************
445
446 Show the usage message and exit
447
448 \begin{code}
449 showGhcUsage = do { usage_path <- readIORef v_Path_usage
450                   ; usage      <- readFile usage_path
451                   ; dump usage
452                   ; exitWith ExitSuccess }
453   where
454      dump ""          = return ()
455      dump ('$':'$':s) = hPutStr stderr progName >> dump s
456      dump (c:s)       = hPutChar stderr c >> dump s
457
458 packageConfigPath = readIORef v_Path_package_config
459 \end{code}
460
461
462 %************************************************************************
463 %*                                                                      *
464 \subsection{Managing temporary files
465 %*                                                                      *
466 %************************************************************************
467
468 \begin{code}
469 GLOBAL_VAR(v_FilesToClean, [],               [String] )
470 GLOBAL_VAR(v_TmpDir,       cDEFAULT_TMPDIR,  String   )
471         -- v_TmpDir has no closing '/'
472 \end{code}
473
474 \begin{code}
475 setTmpDir dir = writeIORef v_TmpDir dir
476
477 cleanTempFiles :: Int -> IO ()
478 cleanTempFiles verb = do fs <- readIORef v_FilesToClean
479                          removeTmpFiles verb fs
480
481 cleanTempFilesExcept :: Int -> [FilePath] -> IO ()
482 cleanTempFilesExcept verb dont_delete
483   = do fs <- readIORef v_FilesToClean
484        let leftovers = filter (`notElem` dont_delete) fs
485        removeTmpFiles verb leftovers
486        writeIORef v_FilesToClean dont_delete
487
488
489 -- find a temporary name that doesn't already exist.
490 newTempName :: Suffix -> IO FilePath
491 newTempName extn
492   = do x <- getProcessID
493        tmp_dir <- readIORef v_TmpDir
494        findTempName tmp_dir x
495   where 
496     findTempName tmp_dir x
497       = do let filename = tmp_dir ++ "/ghc" ++ show x ++ '.':extn
498            b  <- doesFileExist filename
499            if b then findTempName tmp_dir (x+1)
500                 else do add v_FilesToClean filename -- clean it up later
501                         return filename
502
503 addFilesToClean :: [FilePath] -> IO ()
504 -- May include wildcards [used by DriverPipeline.run_phase SplitMangle]
505 addFilesToClean files = mapM_ (add v_FilesToClean) files
506
507 removeTmpFiles :: Int -> [FilePath] -> IO ()
508 removeTmpFiles verb fs
509   = traceCmd "Deleting temp files" 
510              ("Deleting: " ++ unwords fs)
511              (mapM_ rm fs)
512   where
513     rm f = removeFile f `catchAllIO` 
514                 (\_ignored -> 
515                     when (verb >= 2) $
516                       hPutStrLn stderr ("Warning: deleting non-existent " ++ f)
517                 )
518
519 \end{code}
520
521
522 %************************************************************************
523 %*                                                                      *
524 \subsection{Running a program}
525 %*                                                                      *
526 %************************************************************************
527
528 \begin{code}
529 GLOBAL_VAR(v_Dry_run, False, Bool)
530
531 setDryRun :: IO () 
532 setDryRun = writeIORef v_Dry_run True
533
534 -----------------------------------------------------------------------------
535 -- Running an external program
536
537 runSomething :: String          -- For -v message
538              -> String          -- Command name (possibly a full path)
539                                 --      assumed already dos-ified
540              -> [String]        -- Arguments
541                                 --      runSomething will dos-ify them
542              -> IO ()
543
544 runSomething phase_name pgm args
545  = traceCmd phase_name cmd_line $
546    do   { exit_code <- system cmd_line
547         ; if exit_code /= ExitSuccess
548           then throwDyn (PhaseFailed phase_name exit_code)
549           else return ()
550         }
551   where
552     cmd_line = unwords (pgm : dosifyPaths args)
553         -- The pgm is already in native format (appropriate dir separators)
554
555 traceCmd :: String -> String -> IO () -> IO ()
556 -- a) trace the command (at two levels of verbosity)
557 -- b) don't do it at all if dry-run is set
558 traceCmd phase_name cmd_line action
559  = do   { verb <- dynFlag verbosity
560         ; when (verb >= 2) $ hPutStrLn stderr ("*** " ++ phase_name)
561         ; when (verb >= 3) $ hPutStrLn stderr cmd_line
562         ; hFlush stderr
563         
564            -- Test for -n flag
565         ; n <- readIORef v_Dry_run
566         ; unless n $ do {
567
568            -- And run it!
569         ; action `catchAllIO` handle_exn verb
570         }}
571   where
572     handle_exn verb exn = do { when (verb >= 2) (hPutStr   stderr "\n")
573                              ; when (verb >= 3) (hPutStrLn stderr ("Failed: " ++ cmd_line))
574                              ; throwDyn (PhaseFailed phase_name (ExitFailure 1)) }
575 \end{code}
576
577
578 %************************************************************************
579 %*                                                                      *
580 \subsection{Path names}
581 %*                                                                      *
582 %************************************************************************
583
584 We maintain path names in Unix form ('/'-separated) right until 
585 the last moment.  On Windows we dos-ify them just before passing them
586 to the Windows command.
587
588 The alternative, of using '/' consistently on Unix and '\' on Windows,
589 proved quite awkward.  There were a lot more calls to dosifyPath,
590 and even on Windows we might invoke a unix-like utility (eg 'sh'), which
591 interpreted a command line 'foo\baz' as 'foobaz'.
592
593 \begin{code}
594 -----------------------------------------------------------------------------
595 -- Convert filepath into MSDOS form.
596
597 dosifyPaths :: [String] -> [String]
598 -- dosifyPaths does two things
599 -- a) change '/' to '\'
600 -- b) remove initial '/cygdrive/'
601
602 unDosifyPath :: String -> String
603 -- Just change '\' to '/'
604
605 pgmPath :: String               -- Directory string in Unix format
606         -> String               -- Program name with no directory separators
607                                 --      (e.g. copy /y)
608         -> String               -- Program invocation string in native format
609
610
611
612 #if defined(mingw32_TARGET_OS)
613
614 --------------------- Windows version ------------------
615 dosifyPaths xs = map dosifyPath xs
616
617 unDosifyPath xs = subst '\\' '/' xs
618
619 pgmPath dir pgm = dosifyPath dir ++ '\\' : pgm
620
621 dosifyPath stuff
622   = subst '/' '\\' real_stuff
623  where
624    -- fully convince myself that /cygdrive/ prefixes cannot
625    -- really appear here.
626   cygdrive_prefix = "/cygdrive/"
627
628   real_stuff
629     | cygdrive_prefix `isPrefixOf` stuff = drop (length cygdrive_prefix) stuff
630     | otherwise = stuff
631    
632 #else
633
634 --------------------- Unix version ---------------------
635 dosifyPaths  ps = ps
636 unDosifyPath xs = xs
637 pgmPath dir pgm = dir ++ '/' : pgm
638 --------------------------------------------------------
639 #endif
640
641 subst a b ls = map (\ x -> if x == a then b else x) ls
642 \end{code}
643
644
645 -----------------------------------------------------------------------------
646    Path name construction
647
648 \begin{code}
649 slash            :: String -> String -> String
650 absPath, relPath :: [String] -> String
651
652 isSlash '/'   = True
653 isSlash other = False
654
655 relPath [] = ""
656 relPath xs = foldr1 slash xs
657
658 absPath xs = "" `slash` relPath xs
659
660 slash s1 s2 = s1 ++ ('/' : s2)
661 \end{code}
662
663
664 %************************************************************************
665 %*                                                                      *
666 \subsection{Support code}
667 %*                                                                      *
668 %************************************************************************
669
670 \begin{code}
671 -----------------------------------------------------------------------------
672 -- Define       getExecDir     :: IO (Maybe String)
673
674 #if defined(mingw32_TARGET_OS)
675 getExecDir :: IO (Maybe String)
676 getExecDir = do h <- getModuleHandle Nothing
677                 n <- getModuleFileName h
678                 return (Just (reverse (tail (dropWhile (not . isSlash) (reverse (unDosifyPath n))))))
679 #else
680 getExecDir :: IO (Maybe String) = do return Nothing
681 #endif
682
683 #ifdef mingw32_TARGET_OS
684 foreign import "_getpid" getProcessID :: IO Int -- relies on Int == Int32 on Windows
685 #else
686 getProcessID :: IO Int
687 getProcessID = Posix.getProcessID
688 #endif
689 \end{code}