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