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