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