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