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