84effa4db6725634a2cc28d31dfaddc974358037
[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    alloca $ \ ptr_dEnt -> do
338     p <- withCString path $ \s ->
339           throwErrnoIfNullRetry "getDirectoryContents" (opendir s)
340     loop ptr_dEnt p
341   where
342     loop :: Ptr (Ptr CDirent) -> Ptr CDir -> IO [String]
343     loop ptr_dEnt dir = do
344       resetErrno
345       r <- readdir dir ptr_dEnt
346       if (r == 0) 
347          then do
348                  dEnt    <- peek ptr_dEnt
349                  if (dEnt == nullPtr) 
350                    then return []
351                    else do
352                     entry   <- (d_name dEnt >>= peekCString)
353                     freeDirEnt dEnt
354                     entries <- loop ptr_dEnt dir
355                     return (entry:entries)
356          else do errno <- getErrno
357                  if (errno == eINTR) then loop ptr_dEnt dir else do
358                  throwErrnoIfMinus1_ "getDirectoryContents" $ closedir dir
359                  let (Errno eo) = errno
360                  if (eo == end_of_dir)
361                     then return []
362                     else throwErrno "getDirectoryContents"
363
364 foreign import ccall "prel_end_of_dir" unsafe end_of_dir :: CInt
365 foreign import ccall "prel_d_name" unsafe d_name :: Ptr CDirent -> IO CString
366
367 \end{code}
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 \begin{code}
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' <- 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 foreign import ccall "prel_path_max" unsafe path_max :: Int
409
410 \end{code}
411
412 If the operating system has a notion of current directories,
413 @setCurrentDirectory dir@ changes the current
414 directory of the calling process to {\em dir}.
415
416 The operation may fail with:
417 \begin{itemize}
418 \item @HardwareFault@
419 A physical I/O error has occurred.
420 @[EIO]@
421 \item @InvalidArgument@
422 The operand is not a valid directory name.
423 @[ENAMETOOLONG, ELOOP]@
424 \item @isDoesNotExistError@ / @NoSuchThing@
425 The directory does not exist.
426 @[ENOENT, ENOTDIR]@
427 \item @isPermissionError@ / @PermissionDenied@
428 The process has insufficient privileges to perform the operation.
429 @[EACCES]@
430 \item @UnsupportedOperation@
431 The operating system has no notion of current directory, or the
432 current directory cannot be dynamically changed.
433 \item @InappropriateType@
434 The path refers to an existing non-directory object.
435 @[ENOTDIR]@
436 \end{itemize}
437
438 \begin{code}
439 setCurrentDirectory :: FilePath -> IO ()
440 setCurrentDirectory path = do
441     withCString path $ \s -> 
442        throwErrnoIfMinus1Retry_ "setCurrentDirectory" (chdir s)
443         -- ToDo: add path to error
444
445 \end{code}
446
447 To clarify, @doesDirectoryExist@ returns True if a file system object
448 exist, and it's a directory. @doesFileExist@ returns True if the file
449 system object exist, but it's not a directory (i.e., for every other 
450 file system object that is not a directory.) 
451
452 \begin{code}
453 doesDirectoryExist :: FilePath -> IO Bool
454 doesDirectoryExist name = 
455  catch
456    (withFileStatus name $ \st -> isDirectory st)
457    (\ _ -> return False)
458
459 doesFileExist :: FilePath -> IO Bool
460 doesFileExist name = do 
461  catch
462    (withFileStatus name $ \st -> do b <- isDirectory st; return (not b))
463    (\ _ -> return False)
464
465 getModificationTime :: FilePath -> IO ClockTime
466 getModificationTime name =
467  withFileStatus name $ \ st ->
468  modificationTime st
469
470 getPermissions :: FilePath -> IO Permissions
471 getPermissions name = do
472   withCString name $ \s -> do
473   read  <- access s r_OK
474   write <- access s w_OK
475   exec  <- access s x_OK
476   withFileStatus name $ \st -> do
477   is_dir <- isDirectory st
478   is_reg <- isRegularFile st
479   return (
480     Permissions {
481       readable   = read  == 0,
482       writable   = write == 0,
483       executable = not is_dir && exec == 0,
484       searchable = not is_reg && exec == 0
485     }
486    )
487    
488 foreign import ccall "prel_R_OK" unsafe r_OK :: CMode
489 foreign import ccall "prel_W_OK" unsafe w_OK :: CMode
490 foreign import ccall "prel_X_OK" unsafe x_OK :: CMode
491
492 setPermissions :: FilePath -> Permissions -> IO ()
493 setPermissions name (Permissions r w e s) = do
494     let
495      read  = if r      then s_IRUSR else emptyCMode
496      write = if w      then s_IWUSR else emptyCMode
497      exec  = if e || s then s_IXUSR else emptyCMode
498
499      mode  = read `unionCMode` (write `unionCMode` exec)
500
501     withCString name $ \s ->
502       throwErrnoIfMinus1_ "setPermissions" $ chmod s mode
503
504 foreign import ccall "prel_S_IRUSR" unsafe s_IRUSR :: CMode
505 foreign import ccall "prel_S_IWUSR" unsafe s_IWUSR :: CMode
506 foreign import ccall "prel_S_IXUSR" unsafe s_IXUSR :: CMode
507
508 withFileStatus :: FilePath -> (Ptr CStat -> IO a) -> IO a
509 withFileStatus name f = do
510     allocaBytes sizeof_stat $ \p ->
511       withCString name $ \s -> do
512         throwErrnoIfMinus1Retry_ "withFileStatus" (stat s p)
513         f p
514
515 withFileOrSymlinkStatus :: FilePath -> (Ptr CStat -> IO a) -> IO a
516 withFileOrSymlinkStatus name f = do
517     allocaBytes sizeof_stat $ \p ->
518       withCString name $ \s -> do
519         throwErrnoIfMinus1Retry_ "withFileOrSymlinkStatus" (lstat s p)
520         f p
521
522 modificationTime :: Ptr CStat -> IO ClockTime
523 modificationTime stat = do
524     mtime <- st_mtime stat
525     return (TOD (toInteger (mtime :: CTime)) 0)
526     
527 isDirectory :: Ptr CStat -> IO Bool
528 isDirectory stat = do
529   mode <- st_mode stat
530   return (s_ISDIR mode /= 0)
531
532 isRegularFile :: Ptr CStat -> IO Bool
533 isRegularFile stat = do
534   mode <- st_mode stat
535   return (s_ISREG mode /= 0)
536
537 foreign import ccall "prel_s_ISDIR" unsafe s_ISDIR :: CMode -> Int
538 foreign import ccall "prel_s_ISREG" unsafe s_ISREG :: CMode -> Int
539
540 emptyCMode     :: CMode
541 emptyCMode     = 0
542
543 unionCMode     :: CMode -> CMode -> CMode
544 unionCMode     = (+)
545
546 foreign import ccall "prel_mkdir" unsafe mkdir    :: CString -> CInt -> IO CInt
547
548 foreign import ccall unsafe chmod    :: CString -> CMode -> IO CInt
549 foreign import ccall unsafe access   :: CString -> CMode -> IO CInt
550 foreign import ccall unsafe rmdir    :: CString -> IO CInt
551 foreign import ccall unsafe chdir    :: CString -> IO CInt
552 foreign import ccall unsafe getcwd   :: Ptr CChar -> CInt -> IO (Ptr CChar)
553 foreign import ccall unsafe unlink   :: CString -> IO CInt
554 foreign import ccall unsafe rename   :: CString -> CString -> IO CInt
555                      
556 foreign import ccall unsafe opendir  :: CString  -> IO (Ptr CDir)
557 foreign import ccall unsafe closedir :: Ptr CDir -> IO CInt
558
559 foreign import ccall unsafe stat     :: CString -> Ptr CStat -> IO CInt
560
561 foreign import ccall "prel_lstat" unsafe lstat :: CString -> Ptr CStat -> IO CInt
562 foreign import ccall "prel_readdir" unsafe readdir  :: Ptr CDir -> Ptr (Ptr CDirent) -> IO CInt
563 foreign import ccall "prel_free_dirent" unsafe freeDirEnt  :: Ptr CDirent -> IO ()
564
565
566 type CDirent = ()
567
568 \end{code}