copyFile: try removing the target file before opening it for writing
[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     , findExecutable
43
44     -- * Existence tests
45     , doesFileExist             -- :: FilePath -> IO Bool
46     , doesDirectoryExist        -- :: FilePath -> IO Bool
47
48     -- * Permissions
49
50     -- $permissions
51
52     , Permissions(
53         Permissions,
54         readable,               -- :: Permissions -> Bool
55         writable,               -- :: Permissions -> Bool
56         executable,             -- :: Permissions -> Bool
57         searchable              -- :: Permissions -> Bool
58       )
59
60     , getPermissions            -- :: FilePath -> IO Permissions
61     , setPermissions            -- :: FilePath -> Permissions -> IO ()
62
63     -- * Timestamps
64
65     , getModificationTime       -- :: FilePath -> IO ClockTime
66    ) where
67
68 import System.Directory.Internals
69 import System.Environment      ( getEnv )
70 import System.IO.Error
71 import Control.Monad           ( when, unless )
72
73 #ifdef __NHC__
74 import Directory
75 import NHC.FFI
76 #endif /* __NHC__ */
77
78 #ifdef __HUGS__
79 import Hugs.Directory
80 #endif /* __HUGS__ */
81
82 #if defined(__GLASGOW_HASKELL__) || defined(mingw32_HOST_OS)
83 import Foreign
84 import Foreign.C
85 #endif
86
87 #ifdef __GLASGOW_HASKELL__
88 import Prelude
89
90 import Control.Exception       ( bracket )
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) (tail (pathParents file))
277     (_, False,  _) -> createDirectory file
278
279 #if __GLASGOW_HASKELL__
280 {- | @'removeDirectory' dir@ removes an existing directory /dir/.  The
281 implementation may specify additional constraints which must be
282 satisfied before a directory can be removed (e.g. the directory has to
283 be empty, or may not be in use by other processes).  It is not legal
284 for an implementation to partially remove a directory unless the
285 entire directory is removed. A conformant implementation need not
286 support directory removal in all situations (e.g. removal of the root
287 directory).
288
289 The operation may fail with:
290
291 * 'HardwareFault'
292 A physical I\/O error has occurred.
293 EIO
294
295 * 'InvalidArgument'
296 The operand is not a valid directory name.
297 [ENAMETOOLONG, ELOOP]
298
299 * 'isDoesNotExistError' \/ 'NoSuchThing'
300 The directory does not exist. 
301 @[ENOENT, ENOTDIR]@
302
303 * 'isPermissionError' \/ 'PermissionDenied'
304 The process has insufficient privileges to perform the operation.
305 @[EROFS, EACCES, EPERM]@
306
307 * 'UnsatisfiedConstraints'
308 Implementation-dependent constraints are not satisfied.  
309 @[EBUSY, ENOTEMPTY, EEXIST]@
310
311 * 'UnsupportedOperation'
312 The implementation does not support removal in this situation.
313 @[EINVAL]@
314
315 * 'InappropriateType'
316 The operand refers to an existing non-directory object.
317 @[ENOTDIR]@
318
319 -}
320
321 removeDirectory :: FilePath -> IO ()
322 removeDirectory path = do
323   modifyIOError (`ioeSetFileName` path) $
324     withCString path $ \s ->
325        throwErrnoIfMinus1Retry_ "removeDirectory" (c_rmdir s)
326 #endif
327
328 -- | @'removeDirectoryRecursive' dir@  removes an existing directory /dir/
329 -- together with its content and all subdirectories. Be careful, 
330 -- if the directory contains symlinks, the function will follow them.
331 removeDirectoryRecursive :: FilePath -> IO ()
332 removeDirectoryRecursive startLoc = do
333   cont <- getDirectoryContents startLoc
334   sequence_ [rm (startLoc `joinFileName` x) | x <- cont, x /= "." && x /= ".."]
335   removeDirectory startLoc
336   where
337     rm :: FilePath -> IO ()
338     rm f = do temp <- try (removeFile f)
339               case temp of
340                 Left e  -> do isDir <- doesDirectoryExist f
341                               -- If f is not a directory, re-throw the error
342                               unless isDir $ ioError e
343                               removeDirectoryRecursive f
344                 Right _ -> return ()
345
346 #if __GLASGOW_HASKELL__
347 {- |'removeFile' /file/ removes the directory entry for an existing file
348 /file/, where /file/ is not itself a directory. The
349 implementation may specify additional constraints which must be
350 satisfied before a file can be removed (e.g. the file may not be in
351 use by other processes).
352
353 The operation may fail with:
354
355 * 'HardwareFault'
356 A physical I\/O error has occurred.
357 @[EIO]@
358
359 * 'InvalidArgument'
360 The operand is not a valid file name.
361 @[ENAMETOOLONG, ELOOP]@
362
363 * 'isDoesNotExistError' \/ 'NoSuchThing'
364 The file does not exist. 
365 @[ENOENT, ENOTDIR]@
366
367 * 'isPermissionError' \/ 'PermissionDenied'
368 The process has insufficient privileges to perform the operation.
369 @[EROFS, EACCES, EPERM]@
370
371 * 'UnsatisfiedConstraints'
372 Implementation-dependent constraints are not satisfied.  
373 @[EBUSY]@
374
375 * 'InappropriateType'
376 The operand refers to an existing directory.
377 @[EPERM, EINVAL]@
378
379 -}
380
381 removeFile :: FilePath -> IO ()
382 removeFile path = do
383   modifyIOError (`ioeSetFileName` path) $
384     withCString path $ \s ->
385       throwErrnoIfMinus1Retry_ "removeFile" (c_unlink s)
386
387 {- |@'renameDirectory' old new@ changes the name of an existing
388 directory from /old/ to /new/.  If the /new/ directory
389 already exists, it is atomically replaced by the /old/ directory.
390 If the /new/ directory is neither the /old/ directory nor an
391 alias of the /old/ directory, it is removed as if by
392 'removeDirectory'.  A conformant implementation need not support
393 renaming directories in all situations (e.g. renaming to an existing
394 directory, or across different physical devices), but the constraints
395 must be documented.
396
397 On Win32 platforms, @renameDirectory@ fails if the /new/ directory already
398 exists.
399
400 The operation may fail with:
401
402 * 'HardwareFault'
403 A physical I\/O error has occurred.
404 @[EIO]@
405
406 * 'InvalidArgument'
407 Either operand is not a valid directory name.
408 @[ENAMETOOLONG, ELOOP]@
409
410 * 'isDoesNotExistError' \/ 'NoSuchThing'
411 The original directory does not exist, or there is no path to the target.
412 @[ENOENT, ENOTDIR]@
413
414 * 'isPermissionError' \/ 'PermissionDenied'
415 The process has insufficient privileges to perform the operation.
416 @[EROFS, EACCES, EPERM]@
417
418 * 'ResourceExhausted'
419 Insufficient resources are available to perform the operation.  
420 @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
421
422 * 'UnsatisfiedConstraints'
423 Implementation-dependent constraints are not satisfied.
424 @[EBUSY, ENOTEMPTY, EEXIST]@
425
426 * 'UnsupportedOperation'
427 The implementation does not support renaming in this situation.
428 @[EINVAL, EXDEV]@
429
430 * 'InappropriateType'
431 Either path refers to an existing non-directory object.
432 @[ENOTDIR, EISDIR]@
433
434 -}
435
436 renameDirectory :: FilePath -> FilePath -> IO ()
437 renameDirectory opath npath =
438    withFileStatus "renameDirectory" opath $ \st -> do
439    is_dir <- isDirectory st
440    if (not is_dir)
441         then ioException (IOError Nothing InappropriateType "renameDirectory"
442                             ("not a directory") (Just opath))
443         else do
444
445    withCString opath $ \s1 ->
446      withCString npath $ \s2 ->
447         throwErrnoIfMinus1Retry_ "renameDirectory" (c_rename s1 s2)
448
449 {- |@'renameFile' old new@ changes the name of an existing file system
450 object from /old/ to /new/.  If the /new/ object already
451 exists, it is atomically replaced by the /old/ object.  Neither
452 path may refer to an existing directory.  A conformant implementation
453 need not support renaming files in all situations (e.g. renaming
454 across different physical devices), but the constraints must be
455 documented.
456
457 The operation may fail with:
458
459 * 'HardwareFault'
460 A physical I\/O error has occurred.
461 @[EIO]@
462
463 * 'InvalidArgument'
464 Either operand is not a valid file name.
465 @[ENAMETOOLONG, ELOOP]@
466
467 * 'isDoesNotExistError' \/ 'NoSuchThing'
468 The original file does not exist, or there is no path to the target.
469 @[ENOENT, ENOTDIR]@
470
471 * 'isPermissionError' \/ 'PermissionDenied'
472 The process has insufficient privileges to perform the operation.
473 @[EROFS, EACCES, EPERM]@
474
475 * 'ResourceExhausted'
476 Insufficient resources are available to perform the operation.  
477 @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
478
479 * 'UnsatisfiedConstraints'
480 Implementation-dependent constraints are not satisfied.
481 @[EBUSY]@
482
483 * 'UnsupportedOperation'
484 The implementation does not support renaming in this situation.
485 @[EXDEV]@
486
487 * 'InappropriateType'
488 Either path refers to an existing directory.
489 @[ENOTDIR, EISDIR, EINVAL, EEXIST, ENOTEMPTY]@
490
491 -}
492
493 renameFile :: FilePath -> FilePath -> IO ()
494 renameFile opath npath =
495    withFileOrSymlinkStatus "renameFile" opath $ \st -> do
496    is_dir <- isDirectory st
497    if is_dir
498         then ioException (IOError Nothing InappropriateType "renameFile"
499                            "is a directory" (Just opath))
500         else do
501
502     withCString opath $ \s1 ->
503       withCString npath $ \s2 ->
504          throwErrnoIfMinus1Retry_ "renameFile" (c_rename s1 s2)
505
506 #endif /* __GLASGOW_HASKELL__ */
507
508 {- |@'copyFile' old new@ copies the existing file from /old/ to /new/.
509 If the /new/ file already exists, it is atomically replaced by the /old/ file.
510 Neither path may refer to an existing directory.
511 -}
512 copyFile :: FilePath -> FilePath -> IO ()
513 copyFile fromFPath toFPath = do
514         -- We try removing the target file before opening it for
515         -- writing.  In the event that the target file is locked or in
516         -- use, this allows us to replace it safely.  However, it
517         -- leaves a race condition: someone else might create the file
518         -- after we delete it, but there isn't much we can do about
519         -- that.
520 #if (!(defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ > 600))
521         contents <- readFile fromFPath
522         try (removeFile toFPath)
523         writeFile toFPath contents
524         try (copyPermissions fromFPath toFPath)
525         return ()
526 #else
527         (bracket (openBinaryFile fromFPath ReadMode) hClose $ \hFrom -> do
528          try (removeFile toFPath)
529          bracket (openBinaryFile toFPath WriteMode) hClose $ \hTo -> do
530          allocaBytes bufferSize $ \buffer -> do
531                 copyContents hFrom hTo buffer
532                 try (copyPermissions fromFPath toFPath)
533                 return ()) `catch` (ioError . changeFunName)
534         where
535                 bufferSize = 1024
536                 
537                 changeFunName (IOError h iot fun str mb_fp) = IOError h iot "copyFile" str mb_fp
538                 
539                 copyContents hFrom hTo buffer = do
540                         count <- hGetBuf hFrom buffer bufferSize
541                         when (count > 0) $ do
542                                 hPutBuf hTo buffer count
543                                 copyContents hFrom hTo buffer
544 #endif
545
546 #ifdef __GLASGOW_HASKELL__
547 -- | Given path referring to a file or directory, returns a
548 -- canonicalized path, with the intent that two paths referring
549 -- to the same file\/directory will map to the same canonicalized
550 -- path. Note that it is impossible to guarantee that the
551 -- implication (same file\/dir \<=\> same canonicalizedPath) holds
552 -- in either direction: this function can make only a best-effort
553 -- attempt.
554 canonicalizePath :: FilePath -> IO FilePath
555 canonicalizePath fpath =
556   withCString fpath $ \pInPath ->
557   allocaBytes long_path_size $ \pOutPath ->
558 #if defined(mingw32_HOST_OS)
559   alloca $ \ppFilePart ->
560     do c_GetFullPathName pInPath (fromIntegral long_path_size) pOutPath ppFilePart
561 #else
562     do c_realpath pInPath pOutPath
563 #endif
564        peekCString pOutPath
565
566 #if defined(mingw32_HOST_OS)
567 foreign import stdcall unsafe "GetFullPathNameA"
568             c_GetFullPathName :: CString
569                               -> CInt
570                               -> CString
571                               -> Ptr CString
572                               -> IO CInt
573 #else
574 foreign import ccall unsafe "realpath"
575                    c_realpath :: CString
576                               -> CString
577                               -> IO CString
578 #endif
579 #else /* !__GLASGOW_HASKELL__ */
580 -- dummy implementation
581 canonicalizePath :: FilePath -> IO FilePath
582 canonicalizePath fpath = return fpath
583 #endif /* !__GLASGOW_HASKELL__ */
584
585 -- | Given an executable file name, searches for such file
586 -- in the directories listed in system PATH. The returned value 
587 -- is the path to the found executable or Nothing if there isn't
588 -- such executable. For example (findExecutable \"ghc\")
589 -- gives you the path to GHC.
590 findExecutable :: String -> IO (Maybe FilePath)
591 findExecutable binary =
592 #if defined(mingw32_HOST_OS)
593   withCString binary $ \c_binary ->
594   withCString ('.':exeExtension) $ \c_ext ->
595   allocaBytes long_path_size $ \pOutPath ->
596   alloca $ \ppFilePart -> do
597     res <- c_SearchPath nullPtr c_binary c_ext (fromIntegral long_path_size) pOutPath ppFilePart
598     if res > 0 && res < fromIntegral long_path_size
599       then do fpath <- peekCString pOutPath
600               return (Just fpath)
601       else return Nothing
602
603 foreign import stdcall unsafe "SearchPathA"
604             c_SearchPath :: CString
605                          -> CString
606                          -> CString
607                          -> CInt
608                          -> CString
609                          -> Ptr CString
610                          -> IO CInt
611 # if !defined(__GLASGOW_HASKELL__)
612 long_path_size :: Int
613 long_path_size = 4096
614 # endif
615 #else
616  do
617   path <- getEnv "PATH"
618   search (parseSearchPath path)
619   where
620     fileName = binary `joinFileExt` exeExtension
621
622     search :: [FilePath] -> IO (Maybe FilePath)
623     search [] = return Nothing
624     search (d:ds) = do
625         let path = d `joinFileName` fileName
626         b <- doesFileExist path
627         if b then return (Just path)
628              else search ds
629 #endif
630
631
632 #ifdef __GLASGOW_HASKELL__
633 {- |@'getDirectoryContents' dir@ returns a list of /all/ entries
634 in /dir/. 
635
636 The operation may fail with:
637
638 * 'HardwareFault'
639 A physical I\/O error has occurred.
640 @[EIO]@
641
642 * 'InvalidArgument'
643 The operand is not a valid directory name.
644 @[ENAMETOOLONG, ELOOP]@
645
646 * 'isDoesNotExistError' \/ 'NoSuchThing'
647 The directory does not exist.
648 @[ENOENT, ENOTDIR]@
649
650 * 'isPermissionError' \/ 'PermissionDenied'
651 The process has insufficient privileges to perform the operation.
652 @[EACCES]@
653
654 * 'ResourceExhausted'
655 Insufficient resources are available to perform the operation.
656 @[EMFILE, ENFILE]@
657
658 * 'InappropriateType'
659 The path refers to an existing non-directory object.
660 @[ENOTDIR]@
661
662 -}
663
664 getDirectoryContents :: FilePath -> IO [FilePath]
665 getDirectoryContents path = do
666   modifyIOError (`ioeSetFileName` path) $
667    alloca $ \ ptr_dEnt ->
668      bracket
669         (withCString path $ \s -> 
670            throwErrnoIfNullRetry desc (c_opendir s))
671         (\p -> throwErrnoIfMinus1_ desc (c_closedir p))
672         (\p -> loop ptr_dEnt p)
673   where
674     desc = "getDirectoryContents"
675
676     loop :: Ptr (Ptr CDirent) -> Ptr CDir -> IO [String]
677     loop ptr_dEnt dir = do
678       resetErrno
679       r <- readdir dir ptr_dEnt
680       if (r == 0)
681          then do
682                  dEnt    <- peek ptr_dEnt
683                  if (dEnt == nullPtr)
684                    then return []
685                    else do
686                     entry   <- (d_name dEnt >>= peekCString)
687                     freeDirEnt dEnt
688                     entries <- loop ptr_dEnt dir
689                     return (entry:entries)
690          else do errno <- getErrno
691                  if (errno == eINTR) then loop ptr_dEnt dir else do
692                  let (Errno eo) = errno
693                  if (eo == end_of_dir)
694                     then return []
695                     else throwErrno desc
696
697
698
699 {- |If the operating system has a notion of current directories,
700 'getCurrentDirectory' returns an absolute path to the
701 current directory of the calling process.
702
703 The operation may fail with:
704
705 * 'HardwareFault'
706 A physical I\/O error has occurred.
707 @[EIO]@
708
709 * 'isDoesNotExistError' \/ 'NoSuchThing'
710 There is no path referring to the current directory.
711 @[EPERM, ENOENT, ESTALE...]@
712
713 * 'isPermissionError' \/ 'PermissionDenied'
714 The process has insufficient privileges to perform the operation.
715 @[EACCES]@
716
717 * 'ResourceExhausted'
718 Insufficient resources are available to perform the operation.
719
720 * 'UnsupportedOperation'
721 The operating system has no notion of current directory.
722
723 -}
724
725 getCurrentDirectory :: IO FilePath
726 getCurrentDirectory = do
727   p <- mallocBytes long_path_size
728   go p long_path_size
729   where go p bytes = do
730           p' <- c_getcwd p (fromIntegral bytes)
731           if p' /= nullPtr 
732              then do s <- peekCString p'
733                      free p'
734                      return s
735              else do errno <- getErrno
736                      if errno == eRANGE
737                         then do let bytes' = bytes * 2
738                                 p' <- reallocBytes p bytes'
739                                 go p' bytes'
740                         else throwErrno "getCurrentDirectory"
741
742 {- |If the operating system has a notion of current directories,
743 @'setCurrentDirectory' dir@ changes the current
744 directory of the calling process to /dir/.
745
746 The operation may fail with:
747
748 * 'HardwareFault'
749 A physical I\/O error has occurred.
750 @[EIO]@
751
752 * 'InvalidArgument'
753 The operand is not a valid directory name.
754 @[ENAMETOOLONG, ELOOP]@
755
756 * 'isDoesNotExistError' \/ 'NoSuchThing'
757 The directory does not exist.
758 @[ENOENT, ENOTDIR]@
759
760 * 'isPermissionError' \/ 'PermissionDenied'
761 The process has insufficient privileges to perform the operation.
762 @[EACCES]@
763
764 * 'UnsupportedOperation'
765 The operating system has no notion of current directory, or the
766 current directory cannot be dynamically changed.
767
768 * 'InappropriateType'
769 The path refers to an existing non-directory object.
770 @[ENOTDIR]@
771
772 -}
773
774 setCurrentDirectory :: FilePath -> IO ()
775 setCurrentDirectory path = do
776   modifyIOError (`ioeSetFileName` path) $
777     withCString path $ \s -> 
778        throwErrnoIfMinus1Retry_ "setCurrentDirectory" (c_chdir s)
779         -- ToDo: add path to error
780
781 {- |The operation 'doesDirectoryExist' returns 'True' if the argument file
782 exists and is a directory, and 'False' otherwise.
783 -}
784
785 doesDirectoryExist :: FilePath -> IO Bool
786 doesDirectoryExist name = 
787  catch
788    (withFileStatus "doesDirectoryExist" name $ \st -> isDirectory st)
789    (\ _ -> return False)
790
791 {- |The operation 'doesFileExist' returns 'True'
792 if the argument file exists and is not a directory, and 'False' otherwise.
793 -}
794
795 doesFileExist :: FilePath -> IO Bool
796 doesFileExist name = do 
797  catch
798    (withFileStatus "doesFileExist" name $ \st -> do b <- isDirectory st; return (not b))
799    (\ _ -> return False)
800
801 {- |The 'getModificationTime' operation returns the
802 clock time at which the file or directory was last modified.
803
804 The operation may fail with:
805
806 * 'isPermissionError' if the user is not permitted to access
807   the modification time; or
808
809 * 'isDoesNotExistError' if the file or directory does not exist.
810
811 -}
812
813 getModificationTime :: FilePath -> IO ClockTime
814 getModificationTime name =
815  withFileStatus "getModificationTime" name $ \ st ->
816  modificationTime st
817
818 withFileStatus :: String -> FilePath -> (Ptr CStat -> IO a) -> IO a
819 withFileStatus loc name f = do
820   modifyIOError (`ioeSetFileName` name) $
821     allocaBytes sizeof_stat $ \p ->
822       withCString (fileNameEndClean name) $ \s -> do
823         throwErrnoIfMinus1Retry_ loc (c_stat s p)
824         f p
825
826 withFileOrSymlinkStatus :: String -> FilePath -> (Ptr CStat -> IO a) -> IO a
827 withFileOrSymlinkStatus loc name f = do
828   modifyIOError (`ioeSetFileName` name) $
829     allocaBytes sizeof_stat $ \p ->
830       withCString name $ \s -> do
831         throwErrnoIfMinus1Retry_ loc (lstat s p)
832         f p
833
834 modificationTime :: Ptr CStat -> IO ClockTime
835 modificationTime stat = do
836     mtime <- st_mtime stat
837     let realToInteger = round . realToFrac :: Real a => a -> Integer
838     return (TOD (realToInteger (mtime :: CTime)) 0)
839     
840 isDirectory :: Ptr CStat -> IO Bool
841 isDirectory stat = do
842   mode <- st_mode stat
843   return (s_isdir mode)
844
845 fileNameEndClean :: String -> String
846 fileNameEndClean name = 
847   if i > 0 && (ec == '\\' || ec == '/') then 
848      fileNameEndClean (take i name)
849    else
850      name
851   where
852       i  = (length name) - 1
853       ec = name !! i
854
855 foreign import ccall unsafe "__hscore_long_path_size"
856   long_path_size :: Int
857
858 foreign import ccall unsafe "__hscore_R_OK" r_OK :: CMode
859 foreign import ccall unsafe "__hscore_W_OK" w_OK :: CMode
860 foreign import ccall unsafe "__hscore_X_OK" x_OK :: CMode
861
862 foreign import ccall unsafe "__hscore_S_IRUSR" s_IRUSR :: CMode
863 foreign import ccall unsafe "__hscore_S_IWUSR" s_IWUSR :: CMode
864 foreign import ccall unsafe "__hscore_S_IXUSR" s_IXUSR :: CMode
865
866 #endif /* __GLASGOW_HASKELL__ */
867
868 {- | Returns the current user's home directory.
869
870 The directory returned is expected to be writable by the current user,
871 but note that it isn't generally considered good practice to store
872 application-specific data here; use 'getAppUserDataDirectory'
873 instead.
874
875 On Unix, 'getHomeDirectory' returns the value of the @HOME@
876 environment variable.  On Windows, the system is queried for a
877 suitable path; a typical path might be 
878 @C:/Documents And Settings/user@.
879
880 The operation may fail with:
881
882 * 'UnsupportedOperation'
883 The operating system has no notion of home directory.
884
885 * 'isDoesNotExistError'
886 The home directory for the current user does not exist, or
887 cannot be found.
888 -}
889 getHomeDirectory :: IO FilePath
890 getHomeDirectory =
891 #if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
892   allocaBytes long_path_size $ \pPath -> do
893      r <- c_SHGetFolderPath nullPtr csidl_PROFILE nullPtr 0 pPath
894      if (r < 0)
895        then do
896           r <- c_SHGetFolderPath nullPtr csidl_WINDOWS nullPtr 0 pPath
897           when (r < 0) (raiseUnsupported "System.Directory.getHomeDirectory")
898        else return ()
899      peekCString pPath
900 #else
901   getEnv "HOME"
902 #endif
903
904 {- | Returns the pathname of a directory in which application-specific
905 data for the current user can be stored.  The result of
906 'getAppUserDataDirectory' for a given application is specific to
907 the current user.
908
909 The argument should be the name of the application, which will be used
910 to construct the pathname (so avoid using unusual characters that
911 might result in an invalid pathname).
912
913 Note: the directory may not actually exist, and may need to be created
914 first.  It is expected that the parent directory exists and is
915 writable.
916
917 On Unix, this function returns @$HOME\/.appName@.  On Windows, a
918 typical path might be 
919
920 > C:/Documents And Settings/user/Application Data/appName
921
922 The operation may fail with:
923
924 * 'UnsupportedOperation'
925 The operating system has no notion of application-specific data directory.
926
927 * 'isDoesNotExistError'
928 The home directory for the current user does not exist, or
929 cannot be found.
930 -}
931 getAppUserDataDirectory :: String -> IO FilePath
932 getAppUserDataDirectory appName = do
933 #if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
934   allocaBytes long_path_size $ \pPath -> do
935      r <- c_SHGetFolderPath nullPtr csidl_APPDATA nullPtr 0 pPath
936      when (r<0) (raiseUnsupported "System.Directory.getAppUserDataDirectory")
937      s <- peekCString pPath
938      return (s++'\\':appName)
939 #else
940   path <- getEnv "HOME"
941   return (path++'/':'.':appName)
942 #endif
943
944 {- | Returns the current user's document directory.
945
946 The directory returned is expected to be writable by the current user,
947 but note that it isn't generally considered good practice to store
948 application-specific data here; use 'getAppUserDataDirectory'
949 instead.
950
951 On Unix, 'getUserDocumentsDirectory' returns the value of the @HOME@
952 environment variable.  On Windows, the system is queried for a
953 suitable path; a typical path might be 
954 @C:\/Documents and Settings\/user\/My Documents@.
955
956 The operation may fail with:
957
958 * 'UnsupportedOperation'
959 The operating system has no notion of document directory.
960
961 * 'isDoesNotExistError'
962 The document directory for the current user does not exist, or
963 cannot be found.
964 -}
965 getUserDocumentsDirectory :: IO FilePath
966 getUserDocumentsDirectory = do
967 #if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
968   allocaBytes long_path_size $ \pPath -> do
969      r <- c_SHGetFolderPath nullPtr csidl_PERSONAL nullPtr 0 pPath
970      when (r<0) (raiseUnsupported "System.Directory.getUserDocumentsDirectory")
971      peekCString pPath
972 #else
973   getEnv "HOME"
974 #endif
975
976 {- | Returns the current directory for temporary files.
977
978 On Unix, 'getTemporaryDirectory' returns the value of the @TMPDIR@
979 environment variable or \"\/tmp\" if the variable isn\'t defined.
980 On Windows, the function checks for the existence of environment variables in 
981 the following order and uses the first path found:
982
983
984 TMP environment variable. 
985
986 *
987 TEMP environment variable. 
988
989 *
990 USERPROFILE environment variable. 
991
992 *
993 The Windows directory
994
995 The operation may fail with:
996
997 * 'UnsupportedOperation'
998 The operating system has no notion of temporary directory.
999
1000 The function doesn\'t verify whether the path exists.
1001 -}
1002 getTemporaryDirectory :: IO FilePath
1003 getTemporaryDirectory = do
1004 #if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
1005   allocaBytes long_path_size $ \pPath -> do
1006      r <- c_GetTempPath (fromIntegral long_path_size) pPath
1007      peekCString pPath
1008 #else
1009   catch (getEnv "TMPDIR") (\ex -> return "/tmp")
1010 #endif
1011
1012 #if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
1013 foreign import ccall unsafe "__hscore_getFolderPath"
1014             c_SHGetFolderPath :: Ptr () 
1015                               -> CInt 
1016                               -> Ptr () 
1017                               -> CInt 
1018                               -> CString 
1019                               -> IO CInt
1020 foreign import ccall unsafe "__hscore_CSIDL_PROFILE"  csidl_PROFILE  :: CInt
1021 foreign import ccall unsafe "__hscore_CSIDL_APPDATA"  csidl_APPDATA  :: CInt
1022 foreign import ccall unsafe "__hscore_CSIDL_WINDOWS"  csidl_WINDOWS  :: CInt
1023 foreign import ccall unsafe "__hscore_CSIDL_PERSONAL" csidl_PERSONAL :: CInt
1024
1025 foreign import stdcall unsafe "GetTempPathA" c_GetTempPath :: CInt -> CString -> IO CInt
1026
1027 raiseUnsupported loc = 
1028    ioException (IOError Nothing UnsupportedOperation loc "unsupported operation" Nothing)
1029
1030 #endif