[project @ 2002-07-15 16:15:14 by simonmar]
[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   :  provisional
9 -- Portability :  portable
10 --
11 -- System-independent interface to directory manipulation.
12 --
13 -----------------------------------------------------------------------------
14
15 {-
16 A directory contains a series of entries, each of which is a named
17 reference to a file system object (file, directory etc.).  Some
18 entries may be hidden, inaccessible, or have some administrative
19 function (e.g. "." or ".." under POSIX), but in this standard all such
20 entries are considered to form part of the directory contents.
21 Entries in sub-directories are not, however, considered to form part
22 of the directory contents.
23
24 Each file system object is referenced by a {\em path}.  There is
25 normally at least one absolute path to each file system object.  In
26 some operating systems, it may also be possible to have paths which
27 are relative to the current directory.
28 -}
29
30 module System.Directory 
31    ( 
32       Permissions(
33         Permissions,
34         readable,               -- :: Permissions -> Bool 
35         writable,               -- :: Permissions -> Bool
36         executable,             -- :: Permissions -> Bool
37         searchable              -- :: Permissions -> Bool
38      )
39
40     , createDirectory           -- :: FilePath -> IO ()
41     , removeDirectory           -- :: FilePath -> IO ()
42     , renameDirectory           -- :: FilePath -> FilePath -> IO ()
43
44     , getDirectoryContents      -- :: FilePath -> IO [FilePath]
45     , getCurrentDirectory       -- :: IO FilePath
46     , setCurrentDirectory       -- :: FilePath -> IO ()
47
48     , removeFile                -- :: FilePath -> IO ()
49     , renameFile                -- :: FilePath -> FilePath -> IO ()
50
51     , doesFileExist             -- :: FilePath -> IO Bool
52     , doesDirectoryExist        -- :: FilePath -> IO Bool
53
54     , getPermissions            -- :: FilePath -> IO Permissions
55     , setPermissions            -- :: FilePath -> Permissions -> IO ()
56
57     , getModificationTime       -- :: FilePath -> IO ClockTime
58    ) where
59
60 import Prelude
61
62 import System.Time             ( ClockTime(..) )
63 import System.IO
64 import Foreign
65 import Foreign.C
66
67 #ifdef __GLASGOW_HASKELL__
68 import GHC.Posix
69 import GHC.IOBase       ( IOException(..), IOErrorType(..), ioException )
70 #endif
71
72 -----------------------------------------------------------------------------
73 -- Permissions
74
75 -- The Permissions type is used to record whether certain
76 -- operations are permissible on a file/directory:
77 -- [to whom? - presumably the "current user"]
78
79 data Permissions
80  = Permissions {
81     readable,   writable, 
82     executable, searchable :: Bool 
83    } deriving (Eq, Ord, Read, Show)
84
85 -----------------------------------------------------------------------------
86 -- Implementation
87
88 -- `createDirectory dir' creates a new directory dir which is
89 -- initially empty, or as near to empty as the operating system
90 -- allows.
91
92 -- The operation may fail with:
93
94 {-
95 \begin{itemize}
96 \item @isPermissionError@ / @PermissionDenied@
97 The process has insufficient privileges to perform the operation.
98 @[EROFS, EACCES]@
99 \item @isAlreadyExistsError@ / @AlreadyExists@
100 The operand refers to a directory that already exists.  
101 @ [EEXIST]@
102 \item @HardwareFault@
103 A physical I/O error has occurred.
104 @ [EIO]@
105 \item @InvalidArgument@
106 The operand is not a valid directory name.
107 @[ENAMETOOLONG, ELOOP]@
108 \item @NoSuchThing@
109 There is no path to the directory. 
110 @[ENOENT, ENOTDIR]@
111 \item @ResourceExhausted@
112 Insufficient resources (virtual memory, process file descriptors,
113 physical disk space, etc.) are available to perform the operation.
114 @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
115 \item @InappropriateType@
116 The path refers to an existing non-directory object.
117 @[EEXIST]@
118 \end{itemize}
119 -}
120
121 createDirectory :: FilePath -> IO ()
122 createDirectory path = do
123     withCString path $ \s -> do
124       throwErrnoIfMinus1Retry_ "createDirectory" $
125         mkdir s 0o777
126
127 {-
128 @removeDirectory dir@ removes an existing directory {\em dir}.  The
129 implementation may specify additional constraints which must be
130 satisfied before a directory can be removed (e.g. the directory has to
131 be empty, or may not be in use by other processes).  It is not legal
132 for an implementation to partially remove a directory unless the
133 entire directory is removed. A conformant implementation need not
134 support directory removal in all situations (e.g. removal of the root
135 directory).
136
137 The operation may fail with:
138 \begin{itemize}
139 \item @HardwareFault@
140 A physical I/O error has occurred.
141 [@EIO@]
142 \item @InvalidArgument@
143 The operand is not a valid directory name.
144 @[ENAMETOOLONG, ELOOP]@
145 \item @isDoesNotExist@ / @NoSuchThing@
146 The directory does not exist. 
147 @[ENOENT, ENOTDIR]@
148 \item @isPermissionError@ / @PermissionDenied@
149 The process has insufficient privileges to perform the operation.
150 @[EROFS, EACCES, EPERM]@
151 \item @UnsatisfiedConstraints@
152 Implementation-dependent constraints are not satisfied.  
153 @[EBUSY, ENOTEMPTY, EEXIST]@
154 \item @UnsupportedOperation@
155 The implementation does not support removal in this situation.
156 @[EINVAL]@
157 \item @InappropriateType@
158 The operand refers to an existing non-directory object.
159 @[ENOTDIR]@
160 \end{itemize}
161 -}
162
163 removeDirectory :: FilePath -> IO ()
164 removeDirectory path = do
165     withCString path $ \s ->
166        throwErrnoIfMinus1Retry_ "removeDirectory" (c_rmdir s)
167
168 {-
169 @Removefile file@ removes the directory entry for an existing file
170 {\em file}, where {\em file} is not itself a directory. The
171 implementation may specify additional constraints which must be
172 satisfied before a file can be removed (e.g. the file may not be in
173 use by other processes).
174
175 The operation may fail with:
176 \begin{itemize}
177 \item @HardwareFault@
178 A physical I/O error has occurred.
179 @[EIO]@
180 \item @InvalidArgument@
181 The operand is not a valid file name.
182 @[ENAMETOOLONG, ELOOP]@
183 \item @isDoesNotExist@ / @NoSuchThing@
184 The file does not exist. 
185 @[ENOENT, ENOTDIR]@
186 \item @isPermissionError@ / @PermissionDenied@
187 The process has insufficient privileges to perform the operation.
188 @[EROFS, EACCES, EPERM]@
189 \item @UnsatisfiedConstraints@
190 Implementation-dependent constraints are not satisfied.  
191 @[EBUSY]@
192 \item @InappropriateType@
193 The operand refers to an existing directory.
194 @[EPERM, EINVAL]@
195 \end{itemize}
196 -}
197
198 removeFile :: FilePath -> IO ()
199 removeFile path = do
200     withCString path $ \s ->
201       throwErrnoIfMinus1Retry_ "removeFile" (c_unlink s)
202
203 {-
204 @renameDirectory@ {\em old} {\em new} changes the name of an existing
205 directory from {\em old} to {\em new}.  If the {\em new} directory
206 already exists, it is atomically replaced by the {\em old} directory.
207 If the {\em new} directory is neither the {\em old} directory nor an
208 alias of the {\em old} directory, it is removed as if by
209 $removeDirectory$.  A conformant implementation need not support
210 renaming directories in all situations (e.g. renaming to an existing
211 directory, or across different physical devices), but the constraints
212 must be documented.
213
214 The operation may fail with:
215 \begin{itemize}
216 \item @HardwareFault@
217 A physical I/O error has occurred.
218 @[EIO]@
219 \item @InvalidArgument@
220 Either operand is not a valid directory name.
221 @[ENAMETOOLONG, ELOOP]@
222 \item @isDoesNotExistError@ / @NoSuchThing@
223 The original directory does not exist, or there is no path to the target.
224 @[ENOENT, ENOTDIR]@
225 \item @isPermissionError@ / @PermissionDenied@
226 The process has insufficient privileges to perform the operation.
227 @[EROFS, EACCES, EPERM]@
228 \item @ResourceExhausted@
229 Insufficient resources are available to perform the operation.  
230 @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
231 \item @UnsatisfiedConstraints@
232 Implementation-dependent constraints are not satisfied.
233 @[EBUSY, ENOTEMPTY, EEXIST]@
234 \item @UnsupportedOperation@
235 The implementation does not support renaming in this situation.
236 @[EINVAL, EXDEV]@
237 \item @InappropriateType@
238 Either path refers to an existing non-directory object.
239 @[ENOTDIR, EISDIR]@
240 \end{itemize}
241 -}
242
243 renameDirectory :: FilePath -> FilePath -> IO ()
244 renameDirectory opath npath =
245    withFileStatus opath $ \st -> do
246    is_dir <- isDirectory st
247    if (not is_dir)
248         then ioException (IOError Nothing InappropriateType "renameDirectory"
249                             ("not a directory") (Just opath))
250         else do
251
252    withCString opath $ \s1 ->
253      withCString npath $ \s2 ->
254         throwErrnoIfMinus1Retry_ "renameDirectory" (c_rename s1 s2)
255
256 {-
257 @renameFile@ {\em old} {\em new} changes the name of an existing file system
258 object from {\em old} to {\em new}.  If the {\em new} object already
259 exists, it is atomically replaced by the {\em old} object.  Neither
260 path may refer to an existing directory.  A conformant implementation
261 need not support renaming files in all situations (e.g. renaming
262 across different physical devices), but the constraints must be
263 documented.
264
265 The operation may fail with:
266 \begin{itemize}
267 \item @HardwareFault@
268 A physical I/O error has occurred.
269 @[EIO]@
270 \item @InvalidArgument@
271 Either operand is not a valid file name.
272 @[ENAMETOOLONG, ELOOP]@
273 \item @isDoesNotExistError@ / @NoSuchThing@
274 The original file does not exist, or there is no path to the target.
275 @[ENOENT, ENOTDIR]@
276 \item @isPermissionError@ / @PermissionDenied@
277 The process has insufficient privileges to perform the operation.
278 @[EROFS, EACCES, EPERM]@
279 \item @ResourceExhausted@
280 Insufficient resources are available to perform the operation.  
281 @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
282 \item @UnsatisfiedConstraints@
283 Implementation-dependent constraints are not satisfied.
284 @[EBUSY]@
285 \item @UnsupportedOperation@
286 The implementation does not support renaming in this situation.
287 @[EXDEV]@
288 \item @InappropriateType@
289 Either path refers to an existing directory.
290 @[ENOTDIR, EISDIR, EINVAL, EEXIST, ENOTEMPTY]@
291 \end{itemize}
292 -}
293
294 renameFile :: FilePath -> FilePath -> IO ()
295 renameFile opath npath =
296    withFileOrSymlinkStatus opath $ \st -> do
297    is_dir <- isDirectory st
298    if is_dir
299         then ioException (IOError Nothing InappropriateType "renameFile"
300                            "is a directory" (Just opath))
301         else do
302
303     withCString opath $ \s1 ->
304       withCString npath $ \s2 ->
305          throwErrnoIfMinus1Retry_ "renameFile" (c_rename s1 s2)
306
307 {-
308 @getDirectoryContents dir@ returns a list of {\em all} entries
309 in {\em dir}. 
310
311 The operation may fail with:
312 \begin{itemize}
313 \item @HardwareFault@
314 A physical I/O error has occurred.
315 @[EIO]@
316 \item @InvalidArgument@
317 The operand is not a valid directory name.
318 @[ENAMETOOLONG, ELOOP]@
319 \item @isDoesNotExistError@ / @NoSuchThing@
320 The directory does not exist.
321 @[ENOENT, ENOTDIR]@
322 \item @isPermissionError@ / @PermissionDenied@
323 The process has insufficient privileges to perform the operation.
324 @[EACCES]@
325 \item @ResourceExhausted@
326 Insufficient resources are available to perform the operation.
327 @[EMFILE, ENFILE]@
328 \item @InappropriateType@
329 The path refers to an existing non-directory object.
330 @[ENOTDIR]@
331 \end{itemize}
332 -}
333
334 getDirectoryContents :: FilePath -> IO [FilePath]
335 getDirectoryContents path = do
336    alloca $ \ ptr_dEnt ->
337      bracket
338         (withCString path $ \s -> 
339            throwErrnoIfNullRetry desc (c_opendir s))
340         (\p -> throwErrnoIfMinus1_ desc (c_closedir p))
341         (\p -> loop ptr_dEnt p)
342   where
343     desc = "getDirectoryContents"
344
345     loop :: Ptr (Ptr CDirent) -> Ptr CDir -> IO [String]
346     loop ptr_dEnt dir = do
347       resetErrno
348       r <- readdir dir ptr_dEnt
349       if (r == 0)
350          then do
351                  dEnt    <- peek ptr_dEnt
352                  if (dEnt == nullPtr)
353                    then return []
354                    else do
355                     entry   <- (d_name dEnt >>= peekCString)
356                     freeDirEnt dEnt
357                     entries <- loop ptr_dEnt dir
358                     return (entry:entries)
359          else do errno <- getErrno
360                  if (errno == eINTR) then loop ptr_dEnt dir else do
361                  let (Errno eo) = errno
362                  if (eo == end_of_dir)
363                     then return []
364                     else throwErrno desc
365
366
367
368 {-
369 If the operating system has a notion of current directories,
370 @getCurrentDirectory@ returns an absolute path to the
371 current directory of the calling process.
372
373 The operation may fail with:
374 \begin{itemize}
375 \item @HardwareFault@
376 A physical I/O error has occurred.
377 @[EIO]@
378 \item @isDoesNotExistError@ / @NoSuchThing@
379 There is no path referring to the current directory.
380 @[EPERM, ENOENT, ESTALE...]@
381 \item @isPermissionError@ / @PermissionDenied@
382 The process has insufficient privileges to perform the operation.
383 @[EACCES]@
384 \item @ResourceExhausted@
385 Insufficient resources are available to perform the operation.
386 \item @UnsupportedOperation@
387 The operating system has no notion of current directory.
388 \end{itemize}
389 -}
390
391 getCurrentDirectory :: IO FilePath
392 getCurrentDirectory = do
393   p <- mallocBytes path_max
394   go p path_max
395   where go p bytes = do
396           p' <- c_getcwd p (fromIntegral bytes)
397           if p' /= nullPtr 
398              then do s <- peekCString p'
399                      free p'
400                      return s
401              else do errno <- getErrno
402                      if errno == eRANGE
403                         then do let bytes' = bytes * 2
404                                 p' <- reallocBytes p bytes'
405                                 go p' bytes'
406                         else throwErrno "getCurrentDirectory"
407
408 {-
409 If the operating system has a notion of current directories,
410 @setCurrentDirectory dir@ changes the current
411 directory of the calling process to {\em dir}.
412
413 The operation may fail with:
414 \begin{itemize}
415 \item @HardwareFault@
416 A physical I/O error has occurred.
417 @[EIO]@
418 \item @InvalidArgument@
419 The operand is not a valid directory name.
420 @[ENAMETOOLONG, ELOOP]@
421 \item @isDoesNotExistError@ / @NoSuchThing@
422 The directory does not exist.
423 @[ENOENT, ENOTDIR]@
424 \item @isPermissionError@ / @PermissionDenied@
425 The process has insufficient privileges to perform the operation.
426 @[EACCES]@
427 \item @UnsupportedOperation@
428 The operating system has no notion of current directory, or the
429 current directory cannot be dynamically changed.
430 \item @InappropriateType@
431 The path refers to an existing non-directory object.
432 @[ENOTDIR]@
433 \end{itemize}
434 -}
435
436 setCurrentDirectory :: FilePath -> IO ()
437 setCurrentDirectory path = do
438     withCString path $ \s -> 
439        throwErrnoIfMinus1Retry_ "setCurrentDirectory" (c_chdir s)
440         -- ToDo: add path to error
441
442 {-
443 To clarify, @doesDirectoryExist@ returns True if a file system object
444 exist, and it's a directory. @doesFileExist@ returns True if the file
445 system object exist, but it's not a directory (i.e., for every other 
446 file system object that is not a directory.) 
447 -}
448
449 doesDirectoryExist :: FilePath -> IO Bool
450 doesDirectoryExist name = 
451  catch
452    (withFileStatus name $ \st -> isDirectory st)
453    (\ _ -> return False)
454
455 doesFileExist :: FilePath -> IO Bool
456 doesFileExist name = do 
457  catch
458    (withFileStatus name $ \st -> do b <- isDirectory st; return (not b))
459    (\ _ -> return False)
460
461 getModificationTime :: FilePath -> IO ClockTime
462 getModificationTime name =
463  withFileStatus name $ \ st ->
464  modificationTime st
465
466 getPermissions :: FilePath -> IO Permissions
467 getPermissions name = do
468   withCString name $ \s -> do
469   read  <- c_access s r_OK
470   write <- c_access s w_OK
471   exec  <- c_access s x_OK
472   withFileStatus name $ \st -> do
473   is_dir <- isDirectory st
474   return (
475     Permissions {
476       readable   = read  == 0,
477       writable   = write == 0,
478       executable = not is_dir && exec == 0,
479       searchable = is_dir && exec == 0
480     }
481    )
482
483 setPermissions :: FilePath -> Permissions -> IO ()
484 setPermissions name (Permissions r w e s) = do
485     let
486      read  = if r      then s_IRUSR else emptyCMode
487      write = if w      then s_IWUSR else emptyCMode
488      exec  = if e || s then s_IXUSR else emptyCMode
489
490      mode  = read `unionCMode` (write `unionCMode` exec)
491
492     withCString name $ \s ->
493       throwErrnoIfMinus1_ "setPermissions" $ c_chmod s mode
494
495 withFileStatus :: FilePath -> (Ptr CStat -> IO a) -> IO a
496 withFileStatus name f = do
497     allocaBytes sizeof_stat $ \p ->
498       withCString name $ \s -> do
499         throwErrnoIfMinus1Retry_ "withFileStatus" (c_stat s p)
500         f p
501
502 withFileOrSymlinkStatus :: FilePath -> (Ptr CStat -> IO a) -> IO a
503 withFileOrSymlinkStatus name f = do
504     allocaBytes sizeof_stat $ \p ->
505       withCString name $ \s -> do
506         throwErrnoIfMinus1Retry_ "withFileOrSymlinkStatus" (lstat s p)
507         f p
508
509 modificationTime :: Ptr CStat -> IO ClockTime
510 modificationTime stat = do
511     mtime <- st_mtime stat
512     return (TOD (toInteger (mtime :: CTime)) 0)
513     
514 isDirectory :: Ptr CStat -> IO Bool
515 isDirectory stat = do
516   mode <- st_mode stat
517   return (s_isdir mode)
518
519 emptyCMode     :: CMode
520 emptyCMode     = 0
521
522 unionCMode     :: CMode -> CMode -> CMode
523 unionCMode     = (+)
524
525
526 foreign import ccall unsafe "__hscore_path_max"
527   path_max :: Int
528
529 foreign import ccall unsafe "__hscore_readdir"
530   readdir  :: Ptr CDir -> Ptr (Ptr CDirent) -> IO CInt
531
532 foreign import ccall unsafe "__hscore_free_dirent"
533   freeDirEnt  :: Ptr CDirent -> IO ()
534
535 foreign import ccall unsafe "__hscore_end_of_dir"
536   end_of_dir :: CInt
537
538 foreign import ccall unsafe "__hscore_d_name"
539   d_name :: Ptr CDirent -> IO CString
540
541 foreign import ccall unsafe "__hscore_R_OK" r_OK :: CMode
542 foreign import ccall unsafe "__hscore_W_OK" w_OK :: CMode
543 foreign import ccall unsafe "__hscore_X_OK" x_OK :: CMode
544
545 foreign import ccall unsafe "__hscore_S_IRUSR" s_IRUSR :: CMode
546 foreign import ccall unsafe "__hscore_S_IWUSR" s_IWUSR :: CMode
547 foreign import ccall unsafe "__hscore_S_IXUSR" s_IXUSR :: CMode