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