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