enable canonicalizePath for non-GHC platforms
[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.  The permissions of /old/ are
511 copied to /new/, if possible.
512 -}
513
514 {- NOTES:
515
516 It's tempting to try to remove the target file before opening it for
517 writing.  This could be useful: for example if the target file is an
518 executable that is in use, writing will fail, but unlinking first
519 would succeed.
520
521 However, it certainly isn't always what you want.
522
523  * if the target file is hardlinked, removing it would break
524    the hard link, but just opening would preserve it.
525
526  * opening and truncating will preserve permissions and
527    ACLs on the target.
528
529  * If the destination file is read-only in a writable directory,
530    we might want copyFile to fail.  Removing the target first
531    would succeed, however.
532
533  * If the destination file is special (eg. /dev/null), removing
534    it is probably not the right thing.  Copying to /dev/null
535    should leave /dev/null intact, not replace it with a plain
536    file.
537
538  * There's a small race condition between removing the target and
539    opening it for writing during which time someone might
540    create it again.
541 -}
542 copyFile :: FilePath -> FilePath -> IO ()
543 copyFile fromFPath toFPath =
544 #if (!(defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ > 600))
545         do readFile fromFPath >>= writeFile toFPath
546            try (copyPermissions fromFPath toFPath)
547            return ()
548 #else
549         (bracket (openBinaryFile fromFPath ReadMode) hClose $ \hFrom ->
550          bracket (openBinaryFile toFPath WriteMode) hClose $ \hTo ->
551          allocaBytes bufferSize $ \buffer -> do
552                 copyContents hFrom hTo buffer
553                 try (copyPermissions fromFPath toFPath)
554                 return ()) `catch` (ioError . changeFunName)
555         where
556                 bufferSize = 1024
557                 
558                 changeFunName (IOError h iot fun str mb_fp) = IOError h iot "copyFile" str mb_fp
559                 
560                 copyContents hFrom hTo buffer = do
561                         count <- hGetBuf hFrom buffer bufferSize
562                         when (count > 0) $ do
563                                 hPutBuf hTo buffer count
564                                 copyContents hFrom hTo buffer
565 #endif
566
567 -- | Given path referring to a file or directory, returns a
568 -- canonicalized path, with the intent that two paths referring
569 -- to the same file\/directory will map to the same canonicalized
570 -- path. Note that it is impossible to guarantee that the
571 -- implication (same file\/dir \<=\> same canonicalizedPath) holds
572 -- in either direction: this function can make only a best-effort
573 -- attempt.
574 canonicalizePath :: FilePath -> IO FilePath
575 canonicalizePath fpath =
576   withCString fpath $ \pInPath ->
577   allocaBytes long_path_size $ \pOutPath ->
578 #if defined(mingw32_HOST_OS)
579   alloca $ \ppFilePart ->
580     do c_GetFullPathName pInPath (fromIntegral long_path_size) pOutPath ppFilePart
581 #else
582     do c_realpath pInPath pOutPath
583 #endif
584        peekCString pOutPath
585
586 #if defined(mingw32_HOST_OS)
587 foreign import stdcall unsafe "GetFullPathNameA"
588             c_GetFullPathName :: CString
589                               -> CInt
590                               -> CString
591                               -> Ptr CString
592                               -> IO CInt
593 #else
594 foreign import ccall unsafe "realpath"
595                    c_realpath :: CString
596                               -> CString
597                               -> IO CString
598 #endif
599
600 -- | Given an executable file name, searches for such file
601 -- in the directories listed in system PATH. The returned value 
602 -- is the path to the found executable or Nothing if there isn't
603 -- such executable. For example (findExecutable \"ghc\")
604 -- gives you the path to GHC.
605 findExecutable :: String -> IO (Maybe FilePath)
606 findExecutable binary =
607 #if defined(mingw32_HOST_OS)
608   withCString binary $ \c_binary ->
609   withCString ('.':exeExtension) $ \c_ext ->
610   allocaBytes long_path_size $ \pOutPath ->
611   alloca $ \ppFilePart -> do
612     res <- c_SearchPath nullPtr c_binary c_ext (fromIntegral long_path_size) pOutPath ppFilePart
613     if res > 0 && res < fromIntegral long_path_size
614       then do fpath <- peekCString pOutPath
615               return (Just fpath)
616       else return Nothing
617
618 foreign import stdcall unsafe "SearchPathA"
619             c_SearchPath :: CString
620                          -> CString
621                          -> CString
622                          -> CInt
623                          -> CString
624                          -> Ptr CString
625                          -> IO CInt
626 # if !defined(__GLASGOW_HASKELL__)
627 long_path_size :: Int
628 long_path_size = 4096
629 # endif
630 #else
631  do
632   path <- getEnv "PATH"
633   search (parseSearchPath path)
634   where
635     fileName = binary `joinFileExt` exeExtension
636
637     search :: [FilePath] -> IO (Maybe FilePath)
638     search [] = return Nothing
639     search (d:ds) = do
640         let path = d `joinFileName` fileName
641         b <- doesFileExist path
642         if b then return (Just path)
643              else search ds
644 #endif
645
646
647 #ifdef __GLASGOW_HASKELL__
648 {- |@'getDirectoryContents' dir@ returns a list of /all/ entries
649 in /dir/. 
650
651 The operation may fail with:
652
653 * 'HardwareFault'
654 A physical I\/O error has occurred.
655 @[EIO]@
656
657 * 'InvalidArgument'
658 The operand is not a valid directory name.
659 @[ENAMETOOLONG, ELOOP]@
660
661 * 'isDoesNotExistError' \/ 'NoSuchThing'
662 The directory does not exist.
663 @[ENOENT, ENOTDIR]@
664
665 * 'isPermissionError' \/ 'PermissionDenied'
666 The process has insufficient privileges to perform the operation.
667 @[EACCES]@
668
669 * 'ResourceExhausted'
670 Insufficient resources are available to perform the operation.
671 @[EMFILE, ENFILE]@
672
673 * 'InappropriateType'
674 The path refers to an existing non-directory object.
675 @[ENOTDIR]@
676
677 -}
678
679 getDirectoryContents :: FilePath -> IO [FilePath]
680 getDirectoryContents path = do
681   modifyIOError (`ioeSetFileName` path) $
682    alloca $ \ ptr_dEnt ->
683      bracket
684         (withCString path $ \s -> 
685            throwErrnoIfNullRetry desc (c_opendir s))
686         (\p -> throwErrnoIfMinus1_ desc (c_closedir p))
687         (\p -> loop ptr_dEnt p)
688   where
689     desc = "getDirectoryContents"
690
691     loop :: Ptr (Ptr CDirent) -> Ptr CDir -> IO [String]
692     loop ptr_dEnt dir = do
693       resetErrno
694       r <- readdir dir ptr_dEnt
695       if (r == 0)
696          then do
697                  dEnt    <- peek ptr_dEnt
698                  if (dEnt == nullPtr)
699                    then return []
700                    else do
701                     entry   <- (d_name dEnt >>= peekCString)
702                     freeDirEnt dEnt
703                     entries <- loop ptr_dEnt dir
704                     return (entry:entries)
705          else do errno <- getErrno
706                  if (errno == eINTR) then loop ptr_dEnt dir else do
707                  let (Errno eo) = errno
708                  if (eo == end_of_dir)
709                     then return []
710                     else throwErrno desc
711
712
713
714 {- |If the operating system has a notion of current directories,
715 'getCurrentDirectory' returns an absolute path to the
716 current directory of the calling process.
717
718 The operation may fail with:
719
720 * 'HardwareFault'
721 A physical I\/O error has occurred.
722 @[EIO]@
723
724 * 'isDoesNotExistError' \/ 'NoSuchThing'
725 There is no path referring to the current directory.
726 @[EPERM, ENOENT, ESTALE...]@
727
728 * 'isPermissionError' \/ 'PermissionDenied'
729 The process has insufficient privileges to perform the operation.
730 @[EACCES]@
731
732 * 'ResourceExhausted'
733 Insufficient resources are available to perform the operation.
734
735 * 'UnsupportedOperation'
736 The operating system has no notion of current directory.
737
738 -}
739
740 getCurrentDirectory :: IO FilePath
741 getCurrentDirectory = do
742   p <- mallocBytes long_path_size
743   go p long_path_size
744   where go p bytes = do
745           p' <- c_getcwd p (fromIntegral bytes)
746           if p' /= nullPtr 
747              then do s <- peekCString p'
748                      free p'
749                      return s
750              else do errno <- getErrno
751                      if errno == eRANGE
752                         then do let bytes' = bytes * 2
753                                 p' <- reallocBytes p bytes'
754                                 go p' bytes'
755                         else throwErrno "getCurrentDirectory"
756
757 {- |If the operating system has a notion of current directories,
758 @'setCurrentDirectory' dir@ changes the current
759 directory of the calling process to /dir/.
760
761 The operation may fail with:
762
763 * 'HardwareFault'
764 A physical I\/O error has occurred.
765 @[EIO]@
766
767 * 'InvalidArgument'
768 The operand is not a valid directory name.
769 @[ENAMETOOLONG, ELOOP]@
770
771 * 'isDoesNotExistError' \/ 'NoSuchThing'
772 The directory does not exist.
773 @[ENOENT, ENOTDIR]@
774
775 * 'isPermissionError' \/ 'PermissionDenied'
776 The process has insufficient privileges to perform the operation.
777 @[EACCES]@
778
779 * 'UnsupportedOperation'
780 The operating system has no notion of current directory, or the
781 current directory cannot be dynamically changed.
782
783 * 'InappropriateType'
784 The path refers to an existing non-directory object.
785 @[ENOTDIR]@
786
787 -}
788
789 setCurrentDirectory :: FilePath -> IO ()
790 setCurrentDirectory path = do
791   modifyIOError (`ioeSetFileName` path) $
792     withCString path $ \s -> 
793        throwErrnoIfMinus1Retry_ "setCurrentDirectory" (c_chdir s)
794         -- ToDo: add path to error
795
796 {- |The operation 'doesDirectoryExist' returns 'True' if the argument file
797 exists and is a directory, and 'False' otherwise.
798 -}
799
800 doesDirectoryExist :: FilePath -> IO Bool
801 doesDirectoryExist name = 
802  catch
803    (withFileStatus "doesDirectoryExist" name $ \st -> isDirectory st)
804    (\ _ -> return False)
805
806 {- |The operation 'doesFileExist' returns 'True'
807 if the argument file exists and is not a directory, and 'False' otherwise.
808 -}
809
810 doesFileExist :: FilePath -> IO Bool
811 doesFileExist name = do 
812  catch
813    (withFileStatus "doesFileExist" name $ \st -> do b <- isDirectory st; return (not b))
814    (\ _ -> return False)
815
816 {- |The 'getModificationTime' operation returns the
817 clock time at which the file or directory was last modified.
818
819 The operation may fail with:
820
821 * 'isPermissionError' if the user is not permitted to access
822   the modification time; or
823
824 * 'isDoesNotExistError' if the file or directory does not exist.
825
826 -}
827
828 getModificationTime :: FilePath -> IO ClockTime
829 getModificationTime name =
830  withFileStatus "getModificationTime" name $ \ st ->
831  modificationTime st
832
833 withFileStatus :: String -> FilePath -> (Ptr CStat -> IO a) -> IO a
834 withFileStatus loc name f = do
835   modifyIOError (`ioeSetFileName` name) $
836     allocaBytes sizeof_stat $ \p ->
837       withCString (fileNameEndClean name) $ \s -> do
838         throwErrnoIfMinus1Retry_ loc (c_stat s p)
839         f p
840
841 withFileOrSymlinkStatus :: String -> FilePath -> (Ptr CStat -> IO a) -> IO a
842 withFileOrSymlinkStatus loc name f = do
843   modifyIOError (`ioeSetFileName` name) $
844     allocaBytes sizeof_stat $ \p ->
845       withCString name $ \s -> do
846         throwErrnoIfMinus1Retry_ loc (lstat s p)
847         f p
848
849 modificationTime :: Ptr CStat -> IO ClockTime
850 modificationTime stat = do
851     mtime <- st_mtime stat
852     let realToInteger = round . realToFrac :: Real a => a -> Integer
853     return (TOD (realToInteger (mtime :: CTime)) 0)
854     
855 isDirectory :: Ptr CStat -> IO Bool
856 isDirectory stat = do
857   mode <- st_mode stat
858   return (s_isdir mode)
859
860 fileNameEndClean :: String -> String
861 fileNameEndClean name = 
862   if i > 0 && (ec == '\\' || ec == '/') then 
863      fileNameEndClean (take i name)
864    else
865      name
866   where
867       i  = (length name) - 1
868       ec = name !! i
869
870 foreign import ccall unsafe "__hscore_long_path_size"
871   long_path_size :: Int
872
873 foreign import ccall unsafe "__hscore_R_OK" r_OK :: CMode
874 foreign import ccall unsafe "__hscore_W_OK" w_OK :: CMode
875 foreign import ccall unsafe "__hscore_X_OK" x_OK :: CMode
876
877 foreign import ccall unsafe "__hscore_S_IRUSR" s_IRUSR :: CMode
878 foreign import ccall unsafe "__hscore_S_IWUSR" s_IWUSR :: CMode
879 foreign import ccall unsafe "__hscore_S_IXUSR" s_IXUSR :: CMode
880
881 #endif /* __GLASGOW_HASKELL__ */
882
883 {- | Returns the current user's home directory.
884
885 The directory returned is expected to be writable by the current user,
886 but note that it isn't generally considered good practice to store
887 application-specific data here; use 'getAppUserDataDirectory'
888 instead.
889
890 On Unix, 'getHomeDirectory' returns the value of the @HOME@
891 environment variable.  On Windows, the system is queried for a
892 suitable path; a typical path might be 
893 @C:/Documents And Settings/user@.
894
895 The operation may fail with:
896
897 * 'UnsupportedOperation'
898 The operating system has no notion of home directory.
899
900 * 'isDoesNotExistError'
901 The home directory for the current user does not exist, or
902 cannot be found.
903 -}
904 getHomeDirectory :: IO FilePath
905 getHomeDirectory =
906 #if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
907   allocaBytes long_path_size $ \pPath -> do
908      r <- c_SHGetFolderPath nullPtr csidl_PROFILE nullPtr 0 pPath
909      if (r < 0)
910        then do
911           r <- c_SHGetFolderPath nullPtr csidl_WINDOWS nullPtr 0 pPath
912           when (r < 0) (raiseUnsupported "System.Directory.getHomeDirectory")
913        else return ()
914      peekCString pPath
915 #else
916   getEnv "HOME"
917 #endif
918
919 {- | Returns the pathname of a directory in which application-specific
920 data for the current user can be stored.  The result of
921 'getAppUserDataDirectory' for a given application is specific to
922 the current user.
923
924 The argument should be the name of the application, which will be used
925 to construct the pathname (so avoid using unusual characters that
926 might result in an invalid pathname).
927
928 Note: the directory may not actually exist, and may need to be created
929 first.  It is expected that the parent directory exists and is
930 writable.
931
932 On Unix, this function returns @$HOME\/.appName@.  On Windows, a
933 typical path might be 
934
935 > C:/Documents And Settings/user/Application Data/appName
936
937 The operation may fail with:
938
939 * 'UnsupportedOperation'
940 The operating system has no notion of application-specific data directory.
941
942 * 'isDoesNotExistError'
943 The home directory for the current user does not exist, or
944 cannot be found.
945 -}
946 getAppUserDataDirectory :: String -> IO FilePath
947 getAppUserDataDirectory appName = do
948 #if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
949   allocaBytes long_path_size $ \pPath -> do
950      r <- c_SHGetFolderPath nullPtr csidl_APPDATA nullPtr 0 pPath
951      when (r<0) (raiseUnsupported "System.Directory.getAppUserDataDirectory")
952      s <- peekCString pPath
953      return (s++'\\':appName)
954 #else
955   path <- getEnv "HOME"
956   return (path++'/':'.':appName)
957 #endif
958
959 {- | Returns the current user's document directory.
960
961 The directory returned is expected to be writable by the current user,
962 but note that it isn't generally considered good practice to store
963 application-specific data here; use 'getAppUserDataDirectory'
964 instead.
965
966 On Unix, 'getUserDocumentsDirectory' returns the value of the @HOME@
967 environment variable.  On Windows, the system is queried for a
968 suitable path; a typical path might be 
969 @C:\/Documents and Settings\/user\/My Documents@.
970
971 The operation may fail with:
972
973 * 'UnsupportedOperation'
974 The operating system has no notion of document directory.
975
976 * 'isDoesNotExistError'
977 The document directory for the current user does not exist, or
978 cannot be found.
979 -}
980 getUserDocumentsDirectory :: IO FilePath
981 getUserDocumentsDirectory = do
982 #if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
983   allocaBytes long_path_size $ \pPath -> do
984      r <- c_SHGetFolderPath nullPtr csidl_PERSONAL nullPtr 0 pPath
985      when (r<0) (raiseUnsupported "System.Directory.getUserDocumentsDirectory")
986      peekCString pPath
987 #else
988   getEnv "HOME"
989 #endif
990
991 {- | Returns the current directory for temporary files.
992
993 On Unix, 'getTemporaryDirectory' returns the value of the @TMPDIR@
994 environment variable or \"\/tmp\" if the variable isn\'t defined.
995 On Windows, the function checks for the existence of environment variables in 
996 the following order and uses the first path found:
997
998
999 TMP environment variable. 
1000
1001 *
1002 TEMP environment variable. 
1003
1004 *
1005 USERPROFILE environment variable. 
1006
1007 *
1008 The Windows directory
1009
1010 The operation may fail with:
1011
1012 * 'UnsupportedOperation'
1013 The operating system has no notion of temporary directory.
1014
1015 The function doesn\'t verify whether the path exists.
1016 -}
1017 getTemporaryDirectory :: IO FilePath
1018 getTemporaryDirectory = do
1019 #if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
1020   allocaBytes long_path_size $ \pPath -> do
1021      r <- c_GetTempPath (fromIntegral long_path_size) pPath
1022      peekCString pPath
1023 #else
1024   catch (getEnv "TMPDIR") (\ex -> return "/tmp")
1025 #endif
1026
1027 #if __GLASGOW_HASKELL__ && defined(mingw32_HOST_OS)
1028 foreign import ccall unsafe "__hscore_getFolderPath"
1029             c_SHGetFolderPath :: Ptr () 
1030                               -> CInt 
1031                               -> Ptr () 
1032                               -> CInt 
1033                               -> CString 
1034                               -> IO CInt
1035 foreign import ccall unsafe "__hscore_CSIDL_PROFILE"  csidl_PROFILE  :: CInt
1036 foreign import ccall unsafe "__hscore_CSIDL_APPDATA"  csidl_APPDATA  :: CInt
1037 foreign import ccall unsafe "__hscore_CSIDL_WINDOWS"  csidl_WINDOWS  :: CInt
1038 foreign import ccall unsafe "__hscore_CSIDL_PERSONAL" csidl_PERSONAL :: CInt
1039
1040 foreign import stdcall unsafe "GetTempPathA" c_GetTempPath :: CInt -> CString -> IO CInt
1041
1042 raiseUnsupported loc = 
1043    ioException (IOError Nothing UnsupportedOperation loc "unsupported operation" Nothing)
1044
1045 #endif