non-GHC: fix canonicalizeFilePath
[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 import Foreign
83 import Foreign.C
84
85 {-# CFILES cbits/PrelIOUtils.c #-}
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 #else
627  do
628   path <- getEnv "PATH"
629   search (parseSearchPath path)
630   where
631     fileName = binary `joinFileExt` exeExtension
632
633     search :: [FilePath] -> IO (Maybe FilePath)
634     search [] = return Nothing
635     search (d:ds) = do
636         let path = d `joinFileName` fileName
637         b <- doesFileExist path
638         if b then return (Just path)
639              else search ds
640 #endif
641
642
643 #ifdef __GLASGOW_HASKELL__
644 {- |@'getDirectoryContents' dir@ returns a list of /all/ entries
645 in /dir/. 
646
647 The operation may fail with:
648
649 * 'HardwareFault'
650 A physical I\/O error has occurred.
651 @[EIO]@
652
653 * 'InvalidArgument'
654 The operand is not a valid directory name.
655 @[ENAMETOOLONG, ELOOP]@
656
657 * 'isDoesNotExistError' \/ 'NoSuchThing'
658 The directory does not exist.
659 @[ENOENT, ENOTDIR]@
660
661 * 'isPermissionError' \/ 'PermissionDenied'
662 The process has insufficient privileges to perform the operation.
663 @[EACCES]@
664
665 * 'ResourceExhausted'
666 Insufficient resources are available to perform the operation.
667 @[EMFILE, ENFILE]@
668
669 * 'InappropriateType'
670 The path refers to an existing non-directory object.
671 @[ENOTDIR]@
672
673 -}
674
675 getDirectoryContents :: FilePath -> IO [FilePath]
676 getDirectoryContents path = do
677   modifyIOError (`ioeSetFileName` path) $
678    alloca $ \ ptr_dEnt ->
679      bracket
680         (withCString path $ \s -> 
681            throwErrnoIfNullRetry desc (c_opendir s))
682         (\p -> throwErrnoIfMinus1_ desc (c_closedir p))
683         (\p -> loop ptr_dEnt p)
684   where
685     desc = "getDirectoryContents"
686
687     loop :: Ptr (Ptr CDirent) -> Ptr CDir -> IO [String]
688     loop ptr_dEnt dir = do
689       resetErrno
690       r <- readdir dir ptr_dEnt
691       if (r == 0)
692          then do
693                  dEnt    <- peek ptr_dEnt
694                  if (dEnt == nullPtr)
695                    then return []
696                    else do
697                     entry   <- (d_name dEnt >>= peekCString)
698                     freeDirEnt dEnt
699                     entries <- loop ptr_dEnt dir
700                     return (entry:entries)
701          else do errno <- getErrno
702                  if (errno == eINTR) then loop ptr_dEnt dir else do
703                  let (Errno eo) = errno
704                  if (eo == end_of_dir)
705                     then return []
706                     else throwErrno desc
707
708
709
710 {- |If the operating system has a notion of current directories,
711 'getCurrentDirectory' returns an absolute path to the
712 current directory of the calling process.
713
714 The operation may fail with:
715
716 * 'HardwareFault'
717 A physical I\/O error has occurred.
718 @[EIO]@
719
720 * 'isDoesNotExistError' \/ 'NoSuchThing'
721 There is no path referring to the current directory.
722 @[EPERM, ENOENT, ESTALE...]@
723
724 * 'isPermissionError' \/ 'PermissionDenied'
725 The process has insufficient privileges to perform the operation.
726 @[EACCES]@
727
728 * 'ResourceExhausted'
729 Insufficient resources are available to perform the operation.
730
731 * 'UnsupportedOperation'
732 The operating system has no notion of current directory.
733
734 -}
735
736 getCurrentDirectory :: IO FilePath
737 getCurrentDirectory = do
738   p <- mallocBytes long_path_size
739   go p long_path_size
740   where go p bytes = do
741           p' <- c_getcwd p (fromIntegral bytes)
742           if p' /= nullPtr 
743              then do s <- peekCString p'
744                      free p'
745                      return s
746              else do errno <- getErrno
747                      if errno == eRANGE
748                         then do let bytes' = bytes * 2
749                                 p' <- reallocBytes p bytes'
750                                 go p' bytes'
751                         else throwErrno "getCurrentDirectory"
752
753 {- |If the operating system has a notion of current directories,
754 @'setCurrentDirectory' dir@ changes the current
755 directory of the calling process to /dir/.
756
757 The operation may fail with:
758
759 * 'HardwareFault'
760 A physical I\/O error has occurred.
761 @[EIO]@
762
763 * 'InvalidArgument'
764 The operand is not a valid directory name.
765 @[ENAMETOOLONG, ELOOP]@
766
767 * 'isDoesNotExistError' \/ 'NoSuchThing'
768 The directory does not exist.
769 @[ENOENT, ENOTDIR]@
770
771 * 'isPermissionError' \/ 'PermissionDenied'
772 The process has insufficient privileges to perform the operation.
773 @[EACCES]@
774
775 * 'UnsupportedOperation'
776 The operating system has no notion of current directory, or the
777 current directory cannot be dynamically changed.
778
779 * 'InappropriateType'
780 The path refers to an existing non-directory object.
781 @[ENOTDIR]@
782
783 -}
784
785 setCurrentDirectory :: FilePath -> IO ()
786 setCurrentDirectory path = do
787   modifyIOError (`ioeSetFileName` path) $
788     withCString path $ \s -> 
789        throwErrnoIfMinus1Retry_ "setCurrentDirectory" (c_chdir s)
790         -- ToDo: add path to error
791
792 {- |The operation 'doesDirectoryExist' returns 'True' if the argument file
793 exists and is a directory, and 'False' otherwise.
794 -}
795
796 doesDirectoryExist :: FilePath -> IO Bool
797 doesDirectoryExist name = 
798  catch
799    (withFileStatus "doesDirectoryExist" name $ \st -> isDirectory st)
800    (\ _ -> return False)
801
802 {- |The operation 'doesFileExist' returns 'True'
803 if the argument file exists and is not a directory, and 'False' otherwise.
804 -}
805
806 doesFileExist :: FilePath -> IO Bool
807 doesFileExist name = do 
808  catch
809    (withFileStatus "doesFileExist" name $ \st -> do b <- isDirectory st; return (not b))
810    (\ _ -> return False)
811
812 {- |The 'getModificationTime' operation returns the
813 clock time at which the file or directory was last modified.
814
815 The operation may fail with:
816
817 * 'isPermissionError' if the user is not permitted to access
818   the modification time; or
819
820 * 'isDoesNotExistError' if the file or directory does not exist.
821
822 -}
823
824 getModificationTime :: FilePath -> IO ClockTime
825 getModificationTime name =
826  withFileStatus "getModificationTime" name $ \ st ->
827  modificationTime st
828
829 withFileStatus :: String -> FilePath -> (Ptr CStat -> IO a) -> IO a
830 withFileStatus loc name f = do
831   modifyIOError (`ioeSetFileName` name) $
832     allocaBytes sizeof_stat $ \p ->
833       withCString (fileNameEndClean name) $ \s -> do
834         throwErrnoIfMinus1Retry_ loc (c_stat s p)
835         f p
836
837 withFileOrSymlinkStatus :: String -> FilePath -> (Ptr CStat -> IO a) -> IO a
838 withFileOrSymlinkStatus loc name f = do
839   modifyIOError (`ioeSetFileName` name) $
840     allocaBytes sizeof_stat $ \p ->
841       withCString name $ \s -> do
842         throwErrnoIfMinus1Retry_ loc (lstat s p)
843         f p
844
845 modificationTime :: Ptr CStat -> IO ClockTime
846 modificationTime stat = do
847     mtime <- st_mtime stat
848     let realToInteger = round . realToFrac :: Real a => a -> Integer
849     return (TOD (realToInteger (mtime :: CTime)) 0)
850     
851 isDirectory :: Ptr CStat -> IO Bool
852 isDirectory stat = do
853   mode <- st_mode stat
854   return (s_isdir mode)
855
856 fileNameEndClean :: String -> String
857 fileNameEndClean name = 
858   if i > 0 && (ec == '\\' || ec == '/') then 
859      fileNameEndClean (take i name)
860    else
861      name
862   where
863       i  = (length name) - 1
864       ec = name !! i
865
866 foreign import ccall unsafe "__hscore_R_OK" r_OK :: CMode
867 foreign import ccall unsafe "__hscore_W_OK" w_OK :: CMode
868 foreign import ccall unsafe "__hscore_X_OK" x_OK :: CMode
869
870 foreign import ccall unsafe "__hscore_S_IRUSR" s_IRUSR :: CMode
871 foreign import ccall unsafe "__hscore_S_IWUSR" s_IWUSR :: CMode
872 foreign import ccall unsafe "__hscore_S_IXUSR" s_IXUSR :: CMode
873
874 #endif /* __GLASGOW_HASKELL__ */
875
876 foreign import ccall unsafe "__hscore_long_path_size"
877   long_path_size :: Int
878
879 {- | Returns the current user's home directory.
880
881 The directory returned is expected to be writable by the current user,
882 but note that it isn't generally considered good practice to store
883 application-specific data here; use 'getAppUserDataDirectory'
884 instead.
885
886 On Unix, 'getHomeDirectory' returns the value of the @HOME@
887 environment variable.  On Windows, the system is queried for a
888 suitable path; a typical path might be 
889 @C:/Documents And Settings/user@.
890
891 The operation may fail with:
892
893 * 'UnsupportedOperation'
894 The operating system has no notion of home directory.
895
896 * 'isDoesNotExistError'
897 The home directory for the current user does not exist, or
898 cannot be found.
899 -}
900 getHomeDirectory :: IO FilePath
901 getHomeDirectory =
902 #if defined(mingw32_HOST_OS)
903   allocaBytes long_path_size $ \pPath -> do
904      r <- c_SHGetFolderPath nullPtr csidl_PROFILE nullPtr 0 pPath
905      if (r < 0)
906        then do
907           r <- c_SHGetFolderPath nullPtr csidl_WINDOWS nullPtr 0 pPath
908           when (r < 0) (raiseUnsupported "System.Directory.getHomeDirectory")
909        else return ()
910      peekCString pPath
911 #else
912   getEnv "HOME"
913 #endif
914
915 {- | Returns the pathname of a directory in which application-specific
916 data for the current user can be stored.  The result of
917 'getAppUserDataDirectory' for a given application is specific to
918 the current user.
919
920 The argument should be the name of the application, which will be used
921 to construct the pathname (so avoid using unusual characters that
922 might result in an invalid pathname).
923
924 Note: the directory may not actually exist, and may need to be created
925 first.  It is expected that the parent directory exists and is
926 writable.
927
928 On Unix, this function returns @$HOME\/.appName@.  On Windows, a
929 typical path might be 
930
931 > C:/Documents And Settings/user/Application Data/appName
932
933 The operation may fail with:
934
935 * 'UnsupportedOperation'
936 The operating system has no notion of application-specific data directory.
937
938 * 'isDoesNotExistError'
939 The home directory for the current user does not exist, or
940 cannot be found.
941 -}
942 getAppUserDataDirectory :: String -> IO FilePath
943 getAppUserDataDirectory appName = do
944 #if defined(mingw32_HOST_OS)
945   allocaBytes long_path_size $ \pPath -> do
946      r <- c_SHGetFolderPath nullPtr csidl_APPDATA nullPtr 0 pPath
947      when (r<0) (raiseUnsupported "System.Directory.getAppUserDataDirectory")
948      s <- peekCString pPath
949      return (s++'\\':appName)
950 #else
951   path <- getEnv "HOME"
952   return (path++'/':'.':appName)
953 #endif
954
955 {- | Returns the current user's document directory.
956
957 The directory returned is expected to be writable by the current user,
958 but note that it isn't generally considered good practice to store
959 application-specific data here; use 'getAppUserDataDirectory'
960 instead.
961
962 On Unix, 'getUserDocumentsDirectory' returns the value of the @HOME@
963 environment variable.  On Windows, the system is queried for a
964 suitable path; a typical path might be 
965 @C:\/Documents and Settings\/user\/My Documents@.
966
967 The operation may fail with:
968
969 * 'UnsupportedOperation'
970 The operating system has no notion of document directory.
971
972 * 'isDoesNotExistError'
973 The document directory for the current user does not exist, or
974 cannot be found.
975 -}
976 getUserDocumentsDirectory :: IO FilePath
977 getUserDocumentsDirectory = do
978 #if defined(mingw32_HOST_OS)
979   allocaBytes long_path_size $ \pPath -> do
980      r <- c_SHGetFolderPath nullPtr csidl_PERSONAL nullPtr 0 pPath
981      when (r<0) (raiseUnsupported "System.Directory.getUserDocumentsDirectory")
982      peekCString pPath
983 #else
984   getEnv "HOME"
985 #endif
986
987 {- | Returns the current directory for temporary files.
988
989 On Unix, 'getTemporaryDirectory' returns the value of the @TMPDIR@
990 environment variable or \"\/tmp\" if the variable isn\'t defined.
991 On Windows, the function checks for the existence of environment variables in 
992 the following order and uses the first path found:
993
994
995 TMP environment variable. 
996
997 *
998 TEMP environment variable. 
999
1000 *
1001 USERPROFILE environment variable. 
1002
1003 *
1004 The Windows directory
1005
1006 The operation may fail with:
1007
1008 * 'UnsupportedOperation'
1009 The operating system has no notion of temporary directory.
1010
1011 The function doesn\'t verify whether the path exists.
1012 -}
1013 getTemporaryDirectory :: IO FilePath
1014 getTemporaryDirectory = do
1015 #if defined(mingw32_HOST_OS)
1016   allocaBytes long_path_size $ \pPath -> do
1017      r <- c_GetTempPath (fromIntegral long_path_size) pPath
1018      peekCString pPath
1019 #else
1020   catch (getEnv "TMPDIR") (\ex -> return "/tmp")
1021 #endif
1022
1023 #if defined(mingw32_HOST_OS)
1024 foreign import ccall unsafe "__hscore_getFolderPath"
1025             c_SHGetFolderPath :: Ptr () 
1026                               -> CInt 
1027                               -> Ptr () 
1028                               -> CInt 
1029                               -> CString 
1030                               -> IO CInt
1031 foreign import ccall unsafe "__hscore_CSIDL_PROFILE"  csidl_PROFILE  :: CInt
1032 foreign import ccall unsafe "__hscore_CSIDL_APPDATA"  csidl_APPDATA  :: CInt
1033 foreign import ccall unsafe "__hscore_CSIDL_WINDOWS"  csidl_WINDOWS  :: CInt
1034 foreign import ccall unsafe "__hscore_CSIDL_PERSONAL" csidl_PERSONAL :: CInt
1035
1036 foreign import stdcall unsafe "GetTempPathA" c_GetTempPath :: CInt -> CString -> IO CInt
1037
1038 raiseUnsupported loc = 
1039    ioException (IOError Nothing UnsupportedOperation loc "unsupported operation" Nothing)
1040
1041 #endif