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