fcdb937916240718d625f8f04562348e3736cfde
[haskell-directory.git] / System / Directory.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  System.Directory
4 -- Copyright   :  (c) The University of Glasgow 2001
5 -- License     :  BSD-style (see the file libraries/base/LICENSE)
6 -- 
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  stable
9 -- Portability :  portable
10 --
11 -- System-independent interface to directory manipulation.
12 --
13 -----------------------------------------------------------------------------
14
15 module System.Directory 
16    ( 
17     -- $intro
18
19     -- * Actions on directories
20       createDirectory           -- :: FilePath -> IO ()
21     , createDirectoryIfMissing  -- :: Bool -> FilePath -> IO ()
22     , removeDirectory           -- :: FilePath -> IO ()
23     , removeDirectoryRecursive  -- :: FilePath -> IO ()
24     , renameDirectory           -- :: FilePath -> FilePath -> IO ()
25
26     , getDirectoryContents      -- :: FilePath -> IO [FilePath]
27     , getCurrentDirectory       -- :: IO FilePath
28     , setCurrentDirectory       -- :: FilePath -> IO ()
29
30     -- * Pre-defined directories
31     , getHomeDirectory
32     , getAppUserDataDirectory
33     , getUserDocumentsDirectory
34     , getTemporaryDirectory
35
36     -- * Actions on files
37     , removeFile                -- :: FilePath -> IO ()
38     , renameFile                -- :: FilePath -> FilePath -> IO ()
39     , copyFile                  -- :: FilePath -> FilePath -> IO ()
40     
41     , canonicalizePath
42     , makeRelativeToCurrentDirectory
43     , findExecutable
44
45     -- * Existence tests
46     , doesFileExist             -- :: FilePath -> IO Bool
47     , doesDirectoryExist        -- :: FilePath -> IO Bool
48
49     -- * Permissions
50
51     -- $permissions
52
53     , Permissions(
54         Permissions,
55         readable,               -- :: Permissions -> Bool
56         writable,               -- :: Permissions -> Bool
57         executable,             -- :: Permissions -> Bool
58         searchable              -- :: Permissions -> Bool
59       )
60
61     , getPermissions            -- :: FilePath -> IO Permissions
62     , setPermissions            -- :: FilePath -> Permissions -> IO ()
63
64     -- * Timestamps
65
66     , getModificationTime       -- :: FilePath -> IO ClockTime
67    ) where
68
69 import Prelude hiding ( catch )
70
71 import System.Environment      ( getEnv )
72 import System.FilePath
73 import System.IO.Error hiding ( catch, try )
74 import Control.Monad           ( when, unless )
75 import Control.Exception
76
77 #ifdef __NHC__
78 import Directory
79 #endif /* __NHC__ */
80
81 #ifdef __HUGS__
82 import Hugs.Directory
83 #endif /* __HUGS__ */
84
85 import Foreign
86 import Foreign.C
87
88 {-# CFILES cbits/directory.c #-}
89
90 #ifdef __GLASGOW_HASKELL__
91 import System.Posix.Types
92 import System.Posix.Internals
93 import System.Time             ( ClockTime(..) )
94 import System.IO
95
96 import GHC.IOBase       ( IOException(..), IOErrorType(..), ioException )
97
98 {- $intro
99 A directory contains a series of entries, each of which is a named
100 reference to a file system object (file, directory etc.).  Some
101 entries may be hidden, inaccessible, or have some administrative
102 function (e.g. `.' or `..' under POSIX
103 <http://www.opengroup.org/onlinepubs/007904975/toc.htm>), but in 
104 this standard all such entries are considered to form part of the
105 directory contents. Entries in sub-directories are not, however,
106 considered to form part of the directory contents.
107
108 Each file system object is referenced by a /path/.  There is
109 normally at least one absolute path to each file system object.  In
110 some operating systems, it may also be possible to have paths which
111 are relative to the current directory.
112 -}
113
114 -----------------------------------------------------------------------------
115 -- Permissions
116
117 {- $permissions
118
119  The 'Permissions' type is used to record whether certain operations are
120  permissible on a file\/directory. 'getPermissions' and 'setPermissions'
121  get and set these permissions, respectively. Permissions apply both to
122  files and directories. For directories, the executable field will be
123  'False', and for files the searchable field will be 'False'. Note that
124  directories may be searchable without being readable, if permission has
125  been given to use them as part of a path, but not to examine the 
126  directory contents.
127
128 Note that to change some, but not all permissions, a construct on the following lines must be used. 
129
130 >  makeReadable f = do
131 >     p <- getPermissions f
132 >     setPermissions f (p {readable = True})
133
134 -}
135
136 data Permissions
137  = Permissions {
138     readable,   writable, 
139     executable, searchable :: Bool 
140    } deriving (Eq, Ord, Read, Show)
141
142 {- |The 'getPermissions' operation returns the
143 permissions for the file or directory.
144
145 The operation may fail with:
146
147 * 'isPermissionError' if the user is not permitted to access
148   the permissions; or
149
150 * 'isDoesNotExistError' if the file or directory does not exist.
151
152 -}
153
154 getPermissions :: FilePath -> IO Permissions
155 getPermissions name = do
156   withCString name $ \s -> do
157   read  <- c_access s r_OK
158   write <- c_access s w_OK
159   exec  <- c_access s x_OK
160   withFileStatus "getPermissions" name $ \st -> do
161   is_dir <- isDirectory st
162   return (
163     Permissions {
164       readable   = read  == 0,
165       writable   = write == 0,
166       executable = not is_dir && exec == 0,
167       searchable = is_dir && exec == 0
168     }
169    )
170
171 {- |The 'setPermissions' operation sets the
172 permissions for the file or directory.
173
174 The operation may fail with:
175
176 * 'isPermissionError' if the user is not permitted to set
177   the permissions; or
178
179 * 'isDoesNotExistError' if the file or directory does not exist.
180
181 -}
182
183 setPermissions :: FilePath -> Permissions -> IO ()
184 setPermissions name (Permissions r w e s) = do
185   allocaBytes sizeof_stat $ \ p_stat -> do
186   withCString name $ \p_name -> do
187     throwErrnoIfMinus1_ "setPermissions" $ do
188       c_stat p_name p_stat
189       mode <- st_mode p_stat
190       let mode1 = modifyBit r mode s_IRUSR
191       let mode2 = modifyBit w mode1 s_IWUSR
192       let mode3 = modifyBit (e || s) mode2 s_IXUSR
193       c_chmod p_name mode3
194
195  where
196    modifyBit :: Bool -> CMode -> CMode -> CMode
197    modifyBit False m b = m .&. (complement b)
198    modifyBit True  m b = m .|. b
199
200
201 copyPermissions :: FilePath -> FilePath -> IO ()
202 copyPermissions source dest = do
203   allocaBytes sizeof_stat $ \ p_stat -> do
204   withCString source $ \p_source -> do
205   withCString dest $ \p_dest -> do
206     throwErrnoIfMinus1_ "copyPermissions" $ c_stat p_source p_stat
207     mode <- st_mode p_stat
208     throwErrnoIfMinus1_ "copyPermissions" $ c_chmod p_dest mode
209
210 -----------------------------------------------------------------------------
211 -- Implementation
212
213 {- |@'createDirectory' dir@ creates a new directory @dir@ which is
214 initially empty, or as near to empty as the operating system
215 allows.
216
217 The operation may fail with:
218
219 * 'isPermissionError' \/ 'PermissionDenied'
220 The process has insufficient privileges to perform the operation.
221 @[EROFS, EACCES]@
222
223 * 'isAlreadyExistsError' \/ 'AlreadyExists'
224 The operand refers to a directory that already exists.  
225 @ [EEXIST]@
226
227 * 'HardwareFault'
228 A physical I\/O error has occurred.
229 @[EIO]@
230
231 * 'InvalidArgument'
232 The operand is not a valid directory name.
233 @[ENAMETOOLONG, ELOOP]@
234
235 * 'NoSuchThing'
236 There is no path to the directory. 
237 @[ENOENT, ENOTDIR]@
238
239 * 'ResourceExhausted'
240 Insufficient resources (virtual memory, process file descriptors,
241 physical disk space, etc.) are available to perform the operation.
242 @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
243
244 * 'InappropriateType'
245 The path refers to an existing non-directory object.
246 @[EEXIST]@
247
248 -}
249
250 createDirectory :: FilePath -> IO ()
251 createDirectory path = do
252   modifyIOError (`ioeSetFileName` path) $
253     withCString path $ \s -> do
254       throwErrnoIfMinus1Retry_ "createDirectory" $
255         mkdir s 0o777
256
257 #else /* !__GLASGOW_HASKELL__ */
258
259 copyPermissions :: FilePath -> FilePath -> IO ()
260 copyPermissions fromFPath toFPath
261   = getPermissions fromFPath >>= setPermissions toFPath
262
263 #endif
264
265 -- | @'createDirectoryIfMissing' parents dir@ creates a new directory 
266 -- @dir@ if it doesn\'t exist. If the first argument is 'True'
267 -- the function will also create all parent directories if they are missing.
268 createDirectoryIfMissing :: Bool     -- ^ Create its parents too?
269                          -> FilePath -- ^ The path to the directory you want to make
270                          -> IO ()
271 createDirectoryIfMissing parents file = do
272   b <- doesDirectoryExist file
273   case (b,parents, file) of
274     (_,     _, "") -> return ()
275     (True,  _,  _) -> return ()
276     (_,  True,  _) -> mapM_ (createDirectoryIfMissing False) $ mkParents file
277     (_, False,  _) -> createDirectory file
278  where mkParents = scanl1 (</>) . splitDirectories . normalise
279
280 #if __GLASGOW_HASKELL__
281 {- | @'removeDirectory' dir@ removes an existing directory /dir/.  The
282 implementation may specify additional constraints which must be
283 satisfied before a directory can be removed (e.g. the directory has to
284 be empty, or may not be in use by other processes).  It is not legal
285 for an implementation to partially remove a directory unless the
286 entire directory is removed. A conformant implementation need not
287 support directory removal in all situations (e.g. removal of the root
288 directory).
289
290 The operation may fail with:
291
292 * 'HardwareFault'
293 A physical I\/O error has occurred.
294 EIO
295
296 * 'InvalidArgument'
297 The operand is not a valid directory name.
298 [ENAMETOOLONG, ELOOP]
299
300 * 'isDoesNotExistError' \/ 'NoSuchThing'
301 The directory does not exist. 
302 @[ENOENT, ENOTDIR]@
303
304 * 'isPermissionError' \/ 'PermissionDenied'
305 The process has insufficient privileges to perform the operation.
306 @[EROFS, EACCES, EPERM]@
307
308 * 'UnsatisfiedConstraints'
309 Implementation-dependent constraints are not satisfied.  
310 @[EBUSY, ENOTEMPTY, EEXIST]@
311
312 * 'UnsupportedOperation'
313 The implementation does not support removal in this situation.
314 @[EINVAL]@
315
316 * 'InappropriateType'
317 The operand refers to an existing non-directory object.
318 @[ENOTDIR]@
319
320 -}
321
322 removeDirectory :: FilePath -> IO ()
323 removeDirectory path = do
324   modifyIOError (`ioeSetFileName` path) $
325     withCString path $ \s ->
326        throwErrnoIfMinus1Retry_ "removeDirectory" (c_rmdir s)
327 #endif
328
329 -- | @'removeDirectoryRecursive' dir@  removes an existing directory /dir/
330 -- together with its content and all subdirectories. Be careful, 
331 -- if the directory contains symlinks, the function will follow them.
332 removeDirectoryRecursive :: FilePath -> IO ()
333 removeDirectoryRecursive startLoc = do
334   cont <- getDirectoryContents startLoc
335   sequence_ [rm (startLoc </> x) | x <- cont, x /= "." && x /= ".."]
336   removeDirectory startLoc
337   where
338     rm :: FilePath -> IO ()
339     rm f = do temp <- try (removeFile f)
340               case temp of
341                 Left e  -> do isDir <- doesDirectoryExist f
342                               -- If f is not a directory, re-throw the error
343                               unless isDir $ throw e
344                               removeDirectoryRecursive f
345                 Right _ -> return ()
346
347 #if __GLASGOW_HASKELL__
348 {- |'removeFile' /file/ removes the directory entry for an existing file
349 /file/, where /file/ is not itself a directory. The
350 implementation may specify additional constraints which must be
351 satisfied before a file can be removed (e.g. the file may not be in
352 use by other processes).
353
354 The operation may fail with:
355
356 * 'HardwareFault'
357 A physical I\/O error has occurred.
358 @[EIO]@
359
360 * 'InvalidArgument'
361 The operand is not a valid file name.
362 @[ENAMETOOLONG, ELOOP]@
363
364 * 'isDoesNotExistError' \/ 'NoSuchThing'
365 The file does not exist. 
366 @[ENOENT, ENOTDIR]@
367
368 * 'isPermissionError' \/ 'PermissionDenied'
369 The process has insufficient privileges to perform the operation.
370 @[EROFS, EACCES, EPERM]@
371
372 * 'UnsatisfiedConstraints'
373 Implementation-dependent constraints are not satisfied.  
374 @[EBUSY]@
375
376 * 'InappropriateType'
377 The operand refers to an existing directory.
378 @[EPERM, EINVAL]@
379
380 -}
381
382 removeFile :: FilePath -> IO ()
383 removeFile path = do
384   modifyIOError (`ioeSetFileName` path) $
385     withCString path $ \s ->
386       throwErrnoIfMinus1Retry_ "removeFile" (c_unlink s)
387
388 {- |@'renameDirectory' old new@ changes the name of an existing
389 directory from /old/ to /new/.  If the /new/ directory
390 already exists, it is atomically replaced by the /old/ directory.
391 If the /new/ directory is neither the /old/ directory nor an
392 alias of the /old/ directory, it is removed as if by
393 'removeDirectory'.  A conformant implementation need not support
394 renaming directories in all situations (e.g. renaming to an existing
395 directory, or across different physical devices), but the constraints
396 must be documented.
397
398 On Win32 platforms, @renameDirectory@ fails if the /new/ directory already
399 exists.
400
401 The operation may fail with:
402
403 * 'HardwareFault'
404 A physical I\/O error has occurred.
405 @[EIO]@
406
407 * 'InvalidArgument'
408 Either operand is not a valid directory name.
409 @[ENAMETOOLONG, ELOOP]@
410
411 * 'isDoesNotExistError' \/ 'NoSuchThing'
412 The original directory does not exist, or there is no path to the target.
413 @[ENOENT, ENOTDIR]@
414
415 * 'isPermissionError' \/ 'PermissionDenied'
416 The process has insufficient privileges to perform the operation.
417 @[EROFS, EACCES, EPERM]@
418
419 * 'ResourceExhausted'
420 Insufficient resources are available to perform the operation.  
421 @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
422
423 * 'UnsatisfiedConstraints'
424 Implementation-dependent constraints are not satisfied.
425 @[EBUSY, ENOTEMPTY, EEXIST]@
426
427 * 'UnsupportedOperation'
428 The implementation does not support renaming in this situation.
429 @[EINVAL, EXDEV]@
430
431 * 'InappropriateType'
432 Either path refers to an existing non-directory object.
433 @[ENOTDIR, EISDIR]@
434
435 -}
436
437 renameDirectory :: FilePath -> FilePath -> IO ()
438 renameDirectory opath npath =
439    withFileStatus "renameDirectory" opath $ \st -> do
440    is_dir <- isDirectory st
441    if (not is_dir)
442         then ioException (IOError Nothing InappropriateType "renameDirectory"
443                             ("not a directory") (Just opath))
444         else do
445
446    withCString opath $ \s1 ->
447      withCString npath $ \s2 ->
448         throwErrnoIfMinus1Retry_ "renameDirectory" (c_rename s1 s2)
449
450 {- |@'renameFile' old new@ changes the name of an existing file system
451 object from /old/ to /new/.  If the /new/ object already
452 exists, it is atomically replaced by the /old/ object.  Neither
453 path may refer to an existing directory.  A conformant implementation
454 need not support renaming files in all situations (e.g. renaming
455 across different physical devices), but the constraints must be
456 documented.
457
458 The operation may fail with:
459
460 * 'HardwareFault'
461 A physical I\/O error has occurred.
462 @[EIO]@
463
464 * 'InvalidArgument'
465 Either operand is not a valid file name.
466 @[ENAMETOOLONG, ELOOP]@
467
468 * 'isDoesNotExistError' \/ 'NoSuchThing'
469 The original file does not exist, or there is no path to the target.
470 @[ENOENT, ENOTDIR]@
471
472 * 'isPermissionError' \/ 'PermissionDenied'
473 The process has insufficient privileges to perform the operation.
474 @[EROFS, EACCES, EPERM]@
475
476 * 'ResourceExhausted'
477 Insufficient resources are available to perform the operation.  
478 @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
479
480 * 'UnsatisfiedConstraints'
481 Implementation-dependent constraints are not satisfied.
482 @[EBUSY]@
483
484 * 'UnsupportedOperation'
485 The implementation does not support renaming in this situation.
486 @[EXDEV]@
487
488 * 'InappropriateType'
489 Either path refers to an existing directory.
490 @[ENOTDIR, EISDIR, EINVAL, EEXIST, ENOTEMPTY]@
491
492 -}
493
494 renameFile :: FilePath -> FilePath -> IO ()
495 renameFile opath npath =
496    withFileOrSymlinkStatus "renameFile" opath $ \st -> do
497    is_dir <- isDirectory st
498    if is_dir
499         then ioException (IOError Nothing InappropriateType "renameFile"
500                            "is a directory" (Just opath))
501         else do
502
503     withCString opath $ \s1 ->
504       withCString npath $ \s2 ->
505          throwErrnoIfMinus1Retry_ "renameFile" (c_rename s1 s2)
506
507 #endif /* __GLASGOW_HASKELL__ */
508
509 {- |@'copyFile' old new@ copies the existing file from /old/ to /new/.
510 If the /new/ file already exists, it is atomically replaced by the /old/ file.
511 Neither path may refer to an existing directory.  The permissions of /old/ are
512 copied to /new/, if possible.
513 -}
514
515 copyFile :: FilePath -> FilePath -> IO ()
516 copyFile fromFPath toFPath =
517     copy `catch` (\e -> case e of
518                         IOException e ->
519                             throw $ IOException $ ioeSetLocation e "copyFile"
520                         _ -> throw e)
521     where copy = bracket (openBinaryFile fromFPath ReadMode) hClose $ \hFrom ->
522                  bracketOnError openTmp cleanTmp $ \(tmpFPath, hTmp) ->
523                  do allocaBytes bufferSize $ copyContents hFrom hTmp
524                     hClose hTmp
525                     try (copyPermissions fromFPath toFPath)
526                     renameFile tmpFPath toFPath
527           openTmp = openBinaryTempFile (takeDirectory toFPath) ".copyFile.tmp"
528           cleanTmp (tmpFPath, hTmp) = do try $ hClose hTmp
529                                          try $ removeFile tmpFPath
530           bufferSize = 1024
531
532           copyContents hFrom hTo buffer = do
533                   count <- hGetBuf hFrom buffer bufferSize
534                   when (count > 0) $ do
535                           hPutBuf hTo buffer count
536                           copyContents hFrom hTo buffer
537
538 -- | Given path referring to a file or directory, returns a
539 -- canonicalized path, with the intent that two paths referring
540 -- to the same file\/directory will map to the same canonicalized
541 -- path. Note that it is impossible to guarantee that the
542 -- implication (same file\/dir \<=\> same canonicalizedPath) holds
543 -- in either direction: this function can make only a best-effort
544 -- attempt.
545 canonicalizePath :: FilePath -> IO FilePath
546 canonicalizePath fpath =
547   withCString fpath $ \pInPath ->
548   allocaBytes long_path_size $ \pOutPath ->
549 #if defined(mingw32_HOST_OS)
550   alloca $ \ppFilePart ->
551     do c_GetFullPathName pInPath (fromIntegral long_path_size) pOutPath ppFilePart
552 #else
553     do c_realpath pInPath pOutPath
554 #endif
555        peekCString pOutPath
556
557 #if defined(mingw32_HOST_OS)
558 foreign import stdcall unsafe "GetFullPathNameA"
559             c_GetFullPathName :: CString
560                               -> CInt
561                               -> CString
562                               -> Ptr CString
563                               -> IO CInt
564 #else
565 foreign import ccall unsafe "realpath"
566                    c_realpath :: CString
567                               -> CString
568                               -> IO CString
569 #endif
570
571 -- | 'makeRelative' the current directory.
572 makeRelativeToCurrentDirectory :: FilePath -> IO FilePath
573 makeRelativeToCurrentDirectory x = do
574     cur <- getCurrentDirectory
575     return $ makeRelative cur x
576
577 -- | Given an executable file name, searches for such file
578 -- in the directories listed in system PATH. The returned value 
579 -- is the path to the found executable or Nothing if there isn't
580 -- such executable. For example (findExecutable \"ghc\")
581 -- gives you the path to GHC.
582 findExecutable :: String -> IO (Maybe FilePath)
583 findExecutable binary =
584 #if defined(mingw32_HOST_OS)
585   withCString binary $ \c_binary ->
586   withCString ('.':exeExtension) $ \c_ext ->
587   allocaBytes long_path_size $ \pOutPath ->
588   alloca $ \ppFilePart -> do
589     res <- c_SearchPath nullPtr c_binary c_ext (fromIntegral long_path_size) pOutPath ppFilePart
590     if res > 0 && res < fromIntegral long_path_size
591       then do fpath <- peekCString pOutPath
592               return (Just fpath)
593       else return Nothing
594
595 foreign import stdcall unsafe "SearchPathA"
596             c_SearchPath :: CString
597                          -> CString
598                          -> CString
599                          -> CInt
600                          -> CString
601                          -> Ptr CString
602                          -> IO CInt
603 #else
604  do
605   path <- getEnv "PATH"
606   search (splitSearchPath path)
607   where
608     fileName = binary <.> exeExtension
609
610     search :: [FilePath] -> IO (Maybe FilePath)
611     search [] = return Nothing
612     search (d:ds) = do
613         let path = d </> fileName
614         b <- doesFileExist path
615         if b then return (Just path)
616              else search ds
617 #endif
618
619
620 #ifdef __GLASGOW_HASKELL__
621 {- |@'getDirectoryContents' dir@ returns a list of /all/ entries
622 in /dir/. 
623
624 The operation may fail with:
625
626 * 'HardwareFault'
627 A physical I\/O error has occurred.
628 @[EIO]@
629
630 * 'InvalidArgument'
631 The operand is not a valid directory name.
632 @[ENAMETOOLONG, ELOOP]@
633
634 * 'isDoesNotExistError' \/ 'NoSuchThing'
635 The directory does not exist.
636 @[ENOENT, ENOTDIR]@
637
638 * 'isPermissionError' \/ 'PermissionDenied'
639 The process has insufficient privileges to perform the operation.
640 @[EACCES]@
641
642 * 'ResourceExhausted'
643 Insufficient resources are available to perform the operation.
644 @[EMFILE, ENFILE]@
645
646 * 'InappropriateType'
647 The path refers to an existing non-directory object.
648 @[ENOTDIR]@
649
650 -}
651
652 getDirectoryContents :: FilePath -> IO [FilePath]
653 getDirectoryContents path = do
654   modifyIOError (`ioeSetFileName` path) $
655    alloca $ \ ptr_dEnt ->
656      bracket
657         (withCString path $ \s -> 
658            throwErrnoIfNullRetry desc (c_opendir s))
659         (\p -> throwErrnoIfMinus1_ desc (c_closedir p))
660         (\p -> loop ptr_dEnt p)
661   where
662     desc = "getDirectoryContents"
663
664     loop :: Ptr (Ptr CDirent) -> Ptr CDir -> IO [String]
665     loop ptr_dEnt dir = do
666       resetErrno
667       r <- readdir dir ptr_dEnt
668       if (r == 0)
669          then do
670                  dEnt    <- peek ptr_dEnt
671                  if (dEnt == nullPtr)
672                    then return []
673                    else do
674                     entry   <- (d_name dEnt >>= peekCString)
675                     freeDirEnt dEnt
676                     entries <- loop ptr_dEnt dir
677                     return (entry:entries)
678          else do errno <- getErrno
679                  if (errno == eINTR) then loop ptr_dEnt dir else do
680                  let (Errno eo) = errno
681                  if (eo == end_of_dir)
682                     then return []
683                     else throwErrno desc
684
685
686
687 {- |If the operating system has a notion of current directories,
688 'getCurrentDirectory' returns an absolute path to the
689 current directory of the calling process.
690
691 The operation may fail with:
692
693 * 'HardwareFault'
694 A physical I\/O error has occurred.
695 @[EIO]@
696
697 * 'isDoesNotExistError' \/ 'NoSuchThing'
698 There is no path referring to the current directory.
699 @[EPERM, ENOENT, ESTALE...]@
700
701 * 'isPermissionError' \/ 'PermissionDenied'
702 The process has insufficient privileges to perform the operation.
703 @[EACCES]@
704
705 * 'ResourceExhausted'
706 Insufficient resources are available to perform the operation.
707
708 * 'UnsupportedOperation'
709 The operating system has no notion of current directory.
710
711 -}
712
713 getCurrentDirectory :: IO FilePath
714 getCurrentDirectory = do
715   p <- mallocBytes long_path_size
716   go p long_path_size
717   where go p bytes = do
718           p' <- c_getcwd p (fromIntegral bytes)
719           if p' /= nullPtr 
720              then do s <- peekCString p'
721                      free p'
722                      return s
723              else do errno <- getErrno
724                      if errno == eRANGE
725                         then do let bytes' = bytes * 2
726                                 p' <- reallocBytes p bytes'
727                                 go p' bytes'
728                         else throwErrno "getCurrentDirectory"
729
730 {- |If the operating system has a notion of current directories,
731 @'setCurrentDirectory' dir@ changes the current
732 directory of the calling process to /dir/.
733
734 The operation may fail with:
735
736 * 'HardwareFault'
737 A physical I\/O error has occurred.
738 @[EIO]@
739
740 * 'InvalidArgument'
741 The operand is not a valid directory name.
742 @[ENAMETOOLONG, ELOOP]@
743
744 * 'isDoesNotExistError' \/ 'NoSuchThing'
745 The directory does not exist.
746 @[ENOENT, ENOTDIR]@
747
748 * 'isPermissionError' \/ 'PermissionDenied'
749 The process has insufficient privileges to perform the operation.
750 @[EACCES]@
751
752 * 'UnsupportedOperation'
753 The operating system has no notion of current directory, or the
754 current directory cannot be dynamically changed.
755
756 * 'InappropriateType'
757 The path refers to an existing non-directory object.
758 @[ENOTDIR]@
759
760 -}
761
762 setCurrentDirectory :: FilePath -> IO ()
763 setCurrentDirectory path = do
764   modifyIOError (`ioeSetFileName` path) $
765     withCString path $ \s -> 
766        throwErrnoIfMinus1Retry_ "setCurrentDirectory" (c_chdir s)
767         -- ToDo: add path to error
768
769 {- |The operation 'doesDirectoryExist' returns 'True' if the argument file
770 exists and is a directory, and 'False' otherwise.
771 -}
772
773 doesDirectoryExist :: FilePath -> IO Bool
774 doesDirectoryExist name = 
775  catch
776    (withFileStatus "doesDirectoryExist" name $ \st -> isDirectory st)
777    (\ _ -> return False)
778
779 {- |The operation 'doesFileExist' returns 'True'
780 if the argument file exists and is not a directory, and 'False' otherwise.
781 -}
782
783 doesFileExist :: FilePath -> IO Bool
784 doesFileExist name = do 
785  catch
786    (withFileStatus "doesFileExist" name $ \st -> do b <- isDirectory st; return (not b))
787    (\ _ -> return False)
788
789 {- |The 'getModificationTime' operation returns the
790 clock time at which the file or directory was last modified.
791
792 The operation may fail with:
793
794 * 'isPermissionError' if the user is not permitted to access
795   the modification time; or
796
797 * 'isDoesNotExistError' if the file or directory does not exist.
798
799 -}
800
801 getModificationTime :: FilePath -> IO ClockTime
802 getModificationTime name =
803  withFileStatus "getModificationTime" name $ \ st ->
804  modificationTime st
805
806 withFileStatus :: String -> FilePath -> (Ptr CStat -> IO a) -> IO a
807 withFileStatus loc name f = do
808   modifyIOError (`ioeSetFileName` name) $
809     allocaBytes sizeof_stat $ \p ->
810       withCString (fileNameEndClean name) $ \s -> do
811         throwErrnoIfMinus1Retry_ loc (c_stat s p)
812         f p
813
814 withFileOrSymlinkStatus :: String -> FilePath -> (Ptr CStat -> IO a) -> IO a
815 withFileOrSymlinkStatus loc name f = do
816   modifyIOError (`ioeSetFileName` name) $
817     allocaBytes sizeof_stat $ \p ->
818       withCString name $ \s -> do
819         throwErrnoIfMinus1Retry_ loc (lstat s p)
820         f p
821
822 modificationTime :: Ptr CStat -> IO ClockTime
823 modificationTime stat = do
824     mtime <- st_mtime stat
825     let realToInteger = round . realToFrac :: Real a => a -> Integer
826     return (TOD (realToInteger (mtime :: CTime)) 0)
827     
828 isDirectory :: Ptr CStat -> IO Bool
829 isDirectory stat = do
830   mode <- st_mode stat
831   return (s_isdir mode)
832
833 fileNameEndClean :: String -> String
834 fileNameEndClean name = if isDrive name then addTrailingPathSeparator name
835                                         else dropTrailingPathSeparator name
836
837 foreign import ccall unsafe "__hscore_R_OK" r_OK :: CInt
838 foreign import ccall unsafe "__hscore_W_OK" w_OK :: CInt
839 foreign import ccall unsafe "__hscore_X_OK" x_OK :: CInt
840
841 foreign import ccall unsafe "__hscore_S_IRUSR" s_IRUSR :: CMode
842 foreign import ccall unsafe "__hscore_S_IWUSR" s_IWUSR :: CMode
843 foreign import ccall unsafe "__hscore_S_IXUSR" s_IXUSR :: CMode
844
845 foreign import ccall unsafe "__hscore_long_path_size"
846   long_path_size :: Int
847
848 #else
849 long_path_size :: Int
850 long_path_size = 2048   --  // guess?
851
852 #endif /* __GLASGOW_HASKELL__ */
853
854 {- | Returns the current user's home directory.
855
856 The directory returned is expected to be writable by the current user,
857 but note that it isn't generally considered good practice to store
858 application-specific data here; use 'getAppUserDataDirectory'
859 instead.
860
861 On Unix, 'getHomeDirectory' returns the value of the @HOME@
862 environment variable.  On Windows, the system is queried for a
863 suitable path; a typical path might be 
864 @C:/Documents And Settings/user@.
865
866 The operation may fail with:
867
868 * 'UnsupportedOperation'
869 The operating system has no notion of home directory.
870
871 * 'isDoesNotExistError'
872 The home directory for the current user does not exist, or
873 cannot be found.
874 -}
875 getHomeDirectory :: IO FilePath
876 getHomeDirectory =
877 #if defined(mingw32_HOST_OS)
878   allocaBytes long_path_size $ \pPath -> do
879      r <- c_SHGetFolderPath nullPtr csidl_PROFILE nullPtr 0 pPath
880      if (r < 0)
881        then do
882           r <- c_SHGetFolderPath nullPtr csidl_WINDOWS nullPtr 0 pPath
883           when (r < 0) (raiseUnsupported "System.Directory.getHomeDirectory")
884        else return ()
885      peekCString pPath
886 #else
887   getEnv "HOME"
888 #endif
889
890 {- | Returns the pathname of a directory in which application-specific
891 data for the current user can be stored.  The result of
892 'getAppUserDataDirectory' for a given application is specific to
893 the current user.
894
895 The argument should be the name of the application, which will be used
896 to construct the pathname (so avoid using unusual characters that
897 might result in an invalid pathname).
898
899 Note: the directory may not actually exist, and may need to be created
900 first.  It is expected that the parent directory exists and is
901 writable.
902
903 On Unix, this function returns @$HOME\/.appName@.  On Windows, a
904 typical path might be 
905
906 > C:/Documents And Settings/user/Application Data/appName
907
908 The operation may fail with:
909
910 * 'UnsupportedOperation'
911 The operating system has no notion of application-specific data directory.
912
913 * 'isDoesNotExistError'
914 The home directory for the current user does not exist, or
915 cannot be found.
916 -}
917 getAppUserDataDirectory :: String -> IO FilePath
918 getAppUserDataDirectory appName = do
919 #if defined(mingw32_HOST_OS)
920   allocaBytes long_path_size $ \pPath -> do
921      r <- c_SHGetFolderPath nullPtr csidl_APPDATA nullPtr 0 pPath
922      when (r<0) (raiseUnsupported "System.Directory.getAppUserDataDirectory")
923      s <- peekCString pPath
924      return (s++'\\':appName)
925 #else
926   path <- getEnv "HOME"
927   return (path++'/':'.':appName)
928 #endif
929
930 {- | Returns the current user's document directory.
931
932 The directory returned is expected to be writable by the current user,
933 but note that it isn't generally considered good practice to store
934 application-specific data here; use 'getAppUserDataDirectory'
935 instead.
936
937 On Unix, 'getUserDocumentsDirectory' returns the value of the @HOME@
938 environment variable.  On Windows, the system is queried for a
939 suitable path; a typical path might be 
940 @C:\/Documents and Settings\/user\/My Documents@.
941
942 The operation may fail with:
943
944 * 'UnsupportedOperation'
945 The operating system has no notion of document directory.
946
947 * 'isDoesNotExistError'
948 The document directory for the current user does not exist, or
949 cannot be found.
950 -}
951 getUserDocumentsDirectory :: IO FilePath
952 getUserDocumentsDirectory = do
953 #if defined(mingw32_HOST_OS)
954   allocaBytes long_path_size $ \pPath -> do
955      r <- c_SHGetFolderPath nullPtr csidl_PERSONAL nullPtr 0 pPath
956      when (r<0) (raiseUnsupported "System.Directory.getUserDocumentsDirectory")
957      peekCString pPath
958 #else
959   getEnv "HOME"
960 #endif
961
962 {- | Returns the current directory for temporary files.
963
964 On Unix, 'getTemporaryDirectory' returns the value of the @TMPDIR@
965 environment variable or \"\/tmp\" if the variable isn\'t defined.
966 On Windows, the function checks for the existence of environment variables in 
967 the following order and uses the first path found:
968
969
970 TMP environment variable. 
971
972 *
973 TEMP environment variable. 
974
975 *
976 USERPROFILE environment variable. 
977
978 *
979 The Windows directory
980
981 The operation may fail with:
982
983 * 'UnsupportedOperation'
984 The operating system has no notion of temporary directory.
985
986 The function doesn\'t verify whether the path exists.
987 -}
988 getTemporaryDirectory :: IO FilePath
989 getTemporaryDirectory = do
990 #if defined(mingw32_HOST_OS)
991   allocaBytes long_path_size $ \pPath -> do
992      r <- c_GetTempPath (fromIntegral long_path_size) pPath
993      peekCString pPath
994 #else
995   catch (getEnv "TMPDIR") (\ex -> return "/tmp")
996 #endif
997
998 #if defined(mingw32_HOST_OS)
999 foreign import ccall unsafe "__hscore_getFolderPath"
1000             c_SHGetFolderPath :: Ptr () 
1001                               -> CInt 
1002                               -> Ptr () 
1003                               -> CInt 
1004                               -> CString 
1005                               -> IO CInt
1006 foreign import ccall unsafe "__hscore_CSIDL_PROFILE"  csidl_PROFILE  :: CInt
1007 foreign import ccall unsafe "__hscore_CSIDL_APPDATA"  csidl_APPDATA  :: CInt
1008 foreign import ccall unsafe "__hscore_CSIDL_WINDOWS"  csidl_WINDOWS  :: CInt
1009 foreign import ccall unsafe "__hscore_CSIDL_PERSONAL" csidl_PERSONAL :: CInt
1010
1011 foreign import stdcall unsafe "GetTempPathA" c_GetTempPath :: CInt -> CString -> IO CInt
1012
1013 raiseUnsupported loc = 
1014    ioException (IOError Nothing UnsupportedOperation loc "unsupported operation" Nothing)
1015
1016 #endif
1017
1018 -- ToDo: This should be determined via autoconf (AC_EXEEXT)
1019 -- | Extension for executable files
1020 -- (typically @\"\"@ on Unix and @\"exe\"@ on Windows or OS\/2)
1021 exeExtension :: String
1022 #ifdef mingw32_HOST_OS
1023 exeExtension = "exe"
1024 #else
1025 exeExtension = ""
1026 #endif
1027