6e77569995b0f91a7f82b676382001759c391316
[ghc-hetmet.git] / ghc / lib / std / Directory.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1999
3 %
4 \section[Directory]{Directory interface}
5
6 A directory contains a series of entries, each of which is a named
7 reference to a file system object (file, directory etc.).  Some
8 entries may be hidden, inaccessible, or have some administrative
9 function (e.g. "." or ".." under POSIX), but in this standard all such
10 entries are considered to form part of the directory contents.
11 Entries in sub-directories are not, however, considered to form part
12 of the directory contents.
13
14 Each file system object is referenced by a {\em path}.  There is
15 normally at least one absolute path to each file system object.  In
16 some operating systems, it may also be possible to have paths which
17 are relative to the current directory.
18
19 \begin{code}
20 {-# OPTIONS -#include <sys/stat.h> -#include <dirent.h> -#include "cbits/stgio.h" #-}
21 module Directory 
22    ( 
23       Permissions               -- abstract
24       
25     , readable                  -- :: Permissions -> Bool
26     , writable                  -- :: Permissions -> Bool
27     , executable                -- :: Permissions -> Bool
28     , searchable                -- :: Permissions -> Bool
29
30     , createDirectory           -- :: FilePath -> IO ()
31     , removeDirectory           -- :: FilePath -> IO ()
32     , renameDirectory           -- :: FilePath -> FilePath -> IO ()
33
34     , getDirectoryContents      -- :: FilePath -> IO [FilePath]
35     , getCurrentDirectory       -- :: IO FilePath
36     , setCurrentDirectory       -- :: FilePath -> IO ()
37
38     , removeFile                -- :: FilePath -> IO ()
39     , renameFile                -- :: FilePath -> FilePath -> IO ()
40
41     , doesFileExist             -- :: FilePath -> IO Bool
42     , doesDirectoryExist        -- :: FilePath -> IO Bool
43
44     , getPermissions            -- :: FilePath -> IO Permissions
45     , setPermissions            -- :: FilePath -> Permissions -> IO ()
46
47
48 #ifndef __HUGS__
49     , getModificationTime       -- :: FilePath -> IO ClockTime
50 #endif
51    ) where
52
53 #ifdef __HUGS__
54 --import PreludeBuiltin
55 #else
56
57 import Prelude          -- Just to get it in the dependencies
58
59 import PrelGHC          ( RealWorld, or#, and# )
60 import PrelByteArr      ( ByteArray, MutableByteArray,
61                           newWordArray, readWordArray, newCharArray )
62 import PrelArrExtra     ( unsafeFreezeByteArray )
63 import PrelPack         ( unpackNBytesST, packString, unpackCStringST )
64 import PrelIOBase       ( stToIO,
65                           constructErrorAndFail, constructErrorAndFailWithInfo,
66                           IOError(IOError), IOErrorType(SystemError) )
67 import Time             ( ClockTime(..) )
68 import PrelAddr         ( Addr, nullAddr, Word(..), wordToInt, intToWord )
69 #endif
70
71 \end{code}
72
73 %*********************************************************
74 %*                                                      *
75 \subsection{Permissions}
76 %*                                                      *
77 %*********************************************************
78
79 The @Permissions@ type is used to record whether certain
80 operations are permissible on a file/directory:
81 [to whom? - owner/group/world - the Report don't say much]
82
83 \begin{code}
84 data Permissions
85  = Permissions {
86     readable,   writable, 
87     executable, searchable :: Bool 
88    } deriving (Eq, Ord, Read, Show)
89 \end{code}
90
91 %*********************************************************
92 %*                                                      *
93 \subsection{Implementation}
94 %*                                                      *
95 %*********************************************************
96
97 @createDirectory dir@ creates a new directory {\em dir} which is
98 initially empty, or as near to empty as the operating system
99 allows.
100
101 The operation may fail with:
102
103 \begin{itemize}
104 \item @isPermissionError@ / @PermissionDenied@
105 The process has insufficient privileges to perform the operation.
106 @[EROFS, EACCES]@
107 \item @isAlreadyExistsError@ / @AlreadyExists@
108 The operand refers to a directory that already exists.  
109 @ [EEXIST]@
110 \item @HardwareFault@
111 A physical I/O error has occurred.
112 @ [EIO]@
113 \item @InvalidArgument@
114 The operand is not a valid directory name.
115 @[ENAMETOOLONG, ELOOP]@
116 \item @NoSuchThing@
117 There is no path to the directory. 
118 @[ENOENT, ENOTDIR]@
119 \item @ResourceExhausted@
120 Insufficient resources (virtual memory, process file descriptors,
121 physical disk space, etc.) are available to perform the operation.
122 @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
123 \item @InappropriateType@
124 The path refers to an existing non-directory object.
125 @[EEXIST]@
126 \end{itemize}
127
128 \begin{code}
129 createDirectory :: FilePath -> IO ()
130 createDirectory path = do
131     rc <- primCreateDirectory (primPackString path)
132     if rc == 0 then return () else
133         constructErrorAndFailWithInfo "createDirectory" path
134 \end{code}
135
136 @removeDirectory dir@ removes an existing directory {\em dir}.  The
137 implementation may specify additional constraints which must be
138 satisfied before a directory can be removed (e.g. the directory has to
139 be empty, or may not be in use by other processes).  It is not legal
140 for an implementation to partially remove a directory unless the
141 entire directory is removed. A conformant implementation need not
142 support directory removal in all situations (e.g. removal of the root
143 directory).
144
145 The operation may fail with:
146 \begin{itemize}
147 \item @HardwareFault@
148 A physical I/O error has occurred.
149 [@EIO@]
150 \item @InvalidArgument@
151 The operand is not a valid directory name.
152 @[ENAMETOOLONG, ELOOP]@
153 \item @isDoesNotExist@ / @NoSuchThing@
154 The directory does not exist. 
155 @[ENOENT, ENOTDIR]@
156 \item @isPermissionError@ / @PermissionDenied@
157 The process has insufficient privileges to perform the operation.
158 @[EROFS, EACCES, EPERM]@
159 \item @UnsatisfiedConstraints@
160 Implementation-dependent constraints are not satisfied.  
161 @[EBUSY, ENOTEMPTY, EEXIST]@
162 \item @UnsupportedOperation@
163 The implementation does not support removal in this situation.
164 @[EINVAL]@
165 \item @InappropriateType@
166 The operand refers to an existing non-directory object.
167 @[ENOTDIR]@
168 \end{itemize}
169
170 \begin{code}
171 removeDirectory :: FilePath -> IO ()
172 removeDirectory path = do
173     rc <- primRemoveDirectory (primPackString path)
174     if rc == 0 then 
175         return ()
176      else 
177         constructErrorAndFailWithInfo "removeDirectory" path
178 \end{code}
179
180 @removeFile file@ removes the directory entry for an existing file
181 {\em file}, where {\em file} is not itself a directory. The
182 implementation may specify additional constraints which must be
183 satisfied before a file can be removed (e.g. the file may not be in
184 use by other processes).
185
186 The operation may fail with:
187 \begin{itemize}
188 \item @HardwareFault@
189 A physical I/O error has occurred.
190 @[EIO]@
191 \item @InvalidArgument@
192 The operand is not a valid file name.
193 @[ENAMETOOLONG, ELOOP]@
194 \item @isDoesNotExist@ / @NoSuchThing@
195 The file does not exist. 
196 @[ENOENT, ENOTDIR]@
197 \item @isPermissionError@ / @PermissionDenied@
198 The process has insufficient privileges to perform the operation.
199 @[EROFS, EACCES, EPERM]@
200 \item @UnsatisfiedConstraints@
201 Implementation-dependent constraints are not satisfied.  
202 @[EBUSY]@
203 \item @InappropriateType@
204 The operand refers to an existing directory.
205 @[EPERM, EINVAL]@
206 \end{itemize}
207
208 \begin{code}
209 removeFile :: FilePath -> IO ()
210 removeFile path = do
211     rc <- primRemoveFile (primPackString path)
212     if rc == 0 then
213         return ()
214      else
215         constructErrorAndFailWithInfo "removeFile" path
216 \end{code}
217
218 @renameDirectory old@ {\em new} changes the name of an existing
219 directory from {\em old} to {\em new}.  If the {\em new} directory
220 already exists, it is atomically replaced by the {\em old} directory.
221 If the {\em new} directory is neither the {\em old} directory nor an
222 alias of the {\em old} directory, it is removed as if by
223 $removeDirectory$.  A conformant implementation need not support
224 renaming directories in all situations (e.g. renaming to an existing
225 directory, or across different physical devices), but the constraints
226 must be documented.
227
228 The operation may fail with:
229 \begin{itemize}
230 \item @HardwareFault@
231 A physical I/O error has occurred.
232 @[EIO]@
233 \item @InvalidArgument@
234 Either operand is not a valid directory name.
235 @[ENAMETOOLONG, ELOOP]@
236 \item @isDoesNotExistError@ / @NoSuchThing@
237 The original directory does not exist, or there is no path to the target.
238 @[ENOENT, ENOTDIR]@
239 \item @isPermissionError@ / @PermissionDenied@
240 The process has insufficient privileges to perform the operation.
241 @[EROFS, EACCES, EPERM]@
242 \item @ResourceExhausted@
243 Insufficient resources are available to perform the operation.  
244 @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
245 \item @UnsatisfiedConstraints@
246 Implementation-dependent constraints are not satisfied.
247 @[EBUSY, ENOTEMPTY, EEXIST]@
248 \item @UnsupportedOperation@
249 The implementation does not support renaming in this situation.
250 @[EINVAL, EXDEV]@
251 \item @InappropriateType@
252 Either path refers to an existing non-directory object.
253 @[ENOTDIR, EISDIR]@
254 \end{itemize}
255
256 \begin{code}
257 renameDirectory :: FilePath -> FilePath -> IO ()
258 renameDirectory opath npath = do
259     rc <- primRenameDirectory (primPackString opath) (primPackString npath)
260     if rc == 0 then
261         return ()
262      else
263         constructErrorAndFailWithInfo "renameDirectory" ("old: " ++ opath ++ ",new: " ++ npath)
264 \end{code}
265
266 @renameFile old@ {\em new} changes the name of an existing file system
267 object from {\em old} to {\em new}.  If the {\em new} object already
268 exists, it is atomically replaced by the {\em old} object.  Neither
269 path may refer to an existing directory.  A conformant implementation
270 need not support renaming files in all situations (e.g. renaming
271 across different physical devices), but the constraints must be
272 documented.
273
274 The operation may fail with:
275 \begin{itemize}
276 \item @HardwareFault@
277 A physical I/O error has occurred.
278 @[EIO]@
279 \item @InvalidArgument@
280 Either operand is not a valid file name.
281 @[ENAMETOOLONG, ELOOP]@
282 \item @isDoesNotExistError@ / @NoSuchThing@
283 The original file does not exist, or there is no path to the target.
284 @[ENOENT, ENOTDIR]@
285 \item @isPermissionError@ / @PermissionDenied@
286 The process has insufficient privileges to perform the operation.
287 @[EROFS, EACCES, EPERM]@
288 \item @ResourceExhausted@
289 Insufficient resources are available to perform the operation.  
290 @[EDQUOT, ENOSPC, ENOMEM, EMLINK]@
291 \item @UnsatisfiedConstraints@
292 Implementation-dependent constraints are not satisfied.
293 @[EBUSY]@
294 \item @UnsupportedOperation@
295 The implementation does not support renaming in this situation.
296 @[EXDEV]@
297 \item @InappropriateType@
298 Either path refers to an existing directory.
299 @[ENOTDIR, EISDIR, EINVAL, EEXIST, ENOTEMPTY]@
300 \end{itemize}
301
302 \begin{code}
303 renameFile :: FilePath -> FilePath -> IO ()
304 renameFile opath npath = do
305     rc <- primRenameFile (primPackString opath) (primPackString npath)
306     if rc == 0 then
307         return ()
308      else
309         constructErrorAndFailWithInfo   "renameFile" opath
310 \end{code}
311
312 @getDirectoryContents dir@ returns a list of {\em all} entries
313 in {\em dir}. 
314
315 The operation may fail with:
316 \begin{itemize}
317 \item @HardwareFault@
318 A physical I/O error has occurred.
319 @[EIO]@
320 \item @InvalidArgument@
321 The operand is not a valid directory name.
322 @[ENAMETOOLONG, ELOOP]@
323 \item @isDoesNotExistError@ / @NoSuchThing@
324 The directory does not exist.
325 @[ENOENT, ENOTDIR]@
326 \item @isPermissionError@ / @PermissionDenied@
327 The process has insufficient privileges to perform the operation.
328 @[EACCES]@
329 \item @ResourceExhausted@
330 Insufficient resources are available to perform the operation.
331 @[EMFILE, ENFILE]@
332 \item @InappropriateType@
333 The path refers to an existing non-directory object.
334 @[ENOTDIR]@
335 \end{itemize}
336
337 \begin{code}
338 getDirectoryContents :: FilePath -> IO [FilePath]
339 getDirectoryContents path = do
340     dir <- primOpenDir (primPackString path)
341     if dir == nullAddr
342         then constructErrorAndFailWithInfo "getDirectoryContents" path
343         else loop dir
344   where
345     loop :: Addr -> IO [String]
346     loop dir  = do
347       dirent_ptr <- primReadDir dir
348       if dirent_ptr == nullAddr
349        then do
350           -- readDir__ implicitly performs closedir() when the
351           -- end is reached.
352           return [] 
353        else do
354           str     <- primGetDirentDName dirent_ptr
355           entry   <- primUnpackCString str
356           entries <- loop dir
357           return (entry:entries)
358 \end{code}
359
360 If the operating system has a notion of current directories,
361 @getCurrentDirectory@ returns an absolute path to the
362 current directory of the calling process.
363
364 The operation may fail with:
365 \begin{itemize}
366 \item @HardwareFault@
367 A physical I/O error has occurred.
368 @[EIO]@
369 \item @isDoesNotExistError@ / @NoSuchThing@
370 There is no path referring to the current directory.
371 @[EPERM, ENOENT, ESTALE...]@
372 \item @isPermissionError@ / @PermissionDenied@
373 The process has insufficient privileges to perform the operation.
374 @[EACCES]@
375 \item @ResourceExhausted@
376 Insufficient resources are available to perform the operation.
377 \item @UnsupportedOperation@
378 The operating system has no notion of current directory.
379 \end{itemize}
380
381 \begin{code}
382 getCurrentDirectory :: IO FilePath
383 getCurrentDirectory = do
384     str <- primGetCurrentDirectory
385     if str /= nullAddr
386         then do
387             pwd <- primUnpackCString str
388             primFree str
389             return pwd
390         else
391             constructErrorAndFail "getCurrentDirectory"
392 \end{code}
393
394 If the operating system has a notion of current directories,
395 @setCurrentDirectory dir@ changes the current
396 directory of the calling process to {\em dir}.
397
398 The operation may fail with:
399 \begin{itemize}
400 \item @HardwareFault@
401 A physical I/O error has occurred.
402 @[EIO]@
403 \item @InvalidArgument@
404 The operand is not a valid directory name.
405 @[ENAMETOOLONG, ELOOP]@
406 \item @isDoesNotExistError@ / @NoSuchThing@
407 The directory does not exist.
408 @[ENOENT, ENOTDIR]@
409 \item @isPermissionError@ / @PermissionDenied@
410 The process has insufficient privileges to perform the operation.
411 @[EACCES]@
412 \item @UnsupportedOperation@
413 The operating system has no notion of current directory, or the
414 current directory cannot be dynamically changed.
415 \item @InappropriateType@
416 The path refers to an existing non-directory object.
417 @[ENOTDIR]@
418 \end{itemize}
419
420 \begin{code}
421 setCurrentDirectory :: FilePath -> IO ()
422 setCurrentDirectory path = do
423     rc <- primSetCurrentDirectory (primPackString path)
424     if rc == 0 
425         then return ()
426         else constructErrorAndFailWithInfo "setCurrentDirectory" path
427 \end{code}
428
429 To clarify, @doesDirectoryExist@ returns True if a file system object
430 exist, and it's a directory. @doesFileExist@ returns True if the file
431 system object exist, but it's not a directory (i.e., for every other 
432 file system object that is not a directory.) 
433
434 \begin{code}
435 doesDirectoryExist :: FilePath -> IO Bool
436 doesDirectoryExist name = 
437  catch
438    (getFileStatus name >>= \ st -> return (isDirectory st))
439    (\ _ -> return False)
440
441 doesFileExist :: FilePath -> IO Bool
442 doesFileExist name = do 
443  catch
444    (getFileStatus name >>= \ st -> return (not (isDirectory st)))
445    (\ _ -> return False)
446
447 foreign import ccall "libHS_cbits" "const_F_OK" unsafe const_F_OK  :: Int
448
449 #ifndef __HUGS__
450 getModificationTime :: FilePath -> IO ClockTime
451 getModificationTime name =
452  getFileStatus name >>= \ st ->
453  modificationTime st
454 #endif
455
456 getPermissions :: FilePath -> IO Permissions
457 getPermissions name = do
458   st <- getFileStatus name
459   let
460    fm = fileMode st
461    isect v = intersectFileMode v fm == v
462
463   return (
464     Permissions {
465       readable   = isect ownerReadMode,
466       writable   = isect ownerWriteMode,
467       executable = not (isDirectory st)   && isect ownerExecuteMode,
468       searchable = not (isRegularFile st) && isect ownerExecuteMode
469     }
470    )
471
472 setPermissions :: FilePath -> Permissions -> IO ()
473 setPermissions name (Permissions r w e s) = do
474     let
475      read  = if r      then ownerReadMode    else emptyFileMode
476      write = if w      then ownerWriteMode   else emptyFileMode
477      exec  = if e || s then ownerExecuteMode else emptyFileMode
478
479      mode  = read `unionFileMode` (write `unionFileMode` exec)
480
481     rc <- primChmod (primPackString name) mode
482     if rc == 0
483         then return ()
484         else ioError (IOError Nothing SystemError "setPermissions" "insufficient permissions")
485 \end{code}
486
487 (Sigh)..copied from Posix.Files to avoid dep. on posix library
488
489 \begin{code}
490 type FileStatus = PrimByteArray
491
492 getFileStatus :: FilePath -> IO FileStatus
493 getFileStatus name = do
494     bytes <- primNewByteArray sizeof_stat
495     rc <- primStat (primPackString name) bytes
496     if rc == 0 
497 #ifdef __HUGS__
498         then primUnsafeFreezeByteArray bytes
499 #else
500         then stToIO (unsafeFreezeByteArray bytes)
501 #endif
502         else ioError (IOError Nothing SystemError "getFileStatus" "")
503
504 #ifndef __HUGS__
505 modificationTime :: FileStatus -> IO ClockTime
506 modificationTime stat = do
507     i1 <- stToIO (newWordArray (0,1))
508     setFileMode i1 stat
509     secs <- stToIO (readWordArray i1 0)
510     return (TOD (toInteger (wordToInt secs)) 0)
511
512 foreign import ccall "libHS_cbits" "set_stat_st_mtime" unsafe
513    setFileMode :: PrimMutableByteArray RealWorld -> FileStatus -> IO ()
514 #endif
515
516 isDirectory :: FileStatus -> Bool
517 isDirectory stat = prim_S_ISDIR (fileMode stat) /= 0
518
519 isRegularFile :: FileStatus -> Bool
520 isRegularFile stat = prim_S_ISREG (fileMode stat) /= 0
521
522 foreign import ccall "libHS_cbits" "sizeof_stat" unsafe sizeof_stat :: Int
523 foreign import ccall "libHS_cbits" "prim_stat"   unsafe
524   primStat :: PrimByteArray -> PrimMutableByteArray RealWorld -> IO Int
525
526 foreign import ccall "libHS_cbits" "get_stat_st_mode" unsafe fileMode     :: FileStatus -> FileMode
527 foreign import ccall "libHS_cbits" "prim_S_ISDIR"     unsafe prim_S_ISDIR :: FileMode -> Int
528 foreign import ccall "libHS_cbits" "prim_S_ISREG"     unsafe prim_S_ISREG :: FileMode -> Int
529 \end{code}
530
531 \begin{code}
532 type FileMode = Word
533
534 emptyFileMode     :: FileMode
535 unionFileMode     :: FileMode -> FileMode -> FileMode
536 intersectFileMode :: FileMode -> FileMode -> FileMode
537
538 foreign import ccall "libHS_cbits" "const_S_IRUSR" unsafe ownerReadMode    :: FileMode
539 foreign import ccall "libHS_cbits" "const_S_IWUSR" unsafe ownerWriteMode   :: FileMode
540 foreign import ccall "libHS_cbits" "const_S_IXUSR" unsafe ownerExecuteMode :: FileMode
541
542 #ifdef __HUGS__
543 emptyFileMode     = primIntToWord 0
544 unionFileMode     = primOrWord
545 intersectFileMode = primAndWord
546 #else
547 emptyFileMode     = intToWord 0
548 unionFileMode     = orWord
549 intersectFileMode = andWord
550 #endif
551
552 \end{code}
553
554 Some defns. to allow us to share code.
555
556 \begin{code}
557 #ifndef __HUGS__
558
559 primPackString :: [Char] -> ByteArray Int
560 primPackString    = packString
561 --ToDo: fix.
562 primUnpackCString :: Addr -> IO String
563 primUnpackCString a = stToIO (unpackCStringST a)
564
565 type PrimByteArray = ByteArray Int
566 type PrimMutableByteArray s = MutableByteArray RealWorld Int
567 type CString = PrimByteArray
568
569 orWord, andWord :: Word -> Word -> Word
570 orWord (W# x#) (W# y#) = W# (x# `or#` y#)
571 andWord (W# x#) (W# y#) = W# (x# `and#` y#)
572
573 primNewByteArray :: Int -> IO (PrimMutableByteArray s)
574 primNewByteArray sz_in_bytes = stToIO (newCharArray (0,sz_in_bytes))
575 #endif
576
577 foreign import ccall "libHS_cbits" "createDirectory"    unsafe primCreateDirectory     :: CString -> IO Int
578 foreign import ccall "libHS_cbits" "removeDirectory"    unsafe primRemoveDirectory     :: CString -> IO Int
579 foreign import ccall "libHS_cbits" "removeFile"         unsafe primRemoveFile          :: CString -> IO Int
580 foreign import ccall "libHS_cbits" "renameDirectory"    unsafe primRenameDirectory     :: CString -> CString -> IO Int
581 foreign import ccall "libHS_cbits" "renameFile"         unsafe primRenameFile          :: CString -> CString -> IO Int
582 foreign import ccall "libHS_cbits" "openDir__"          unsafe primOpenDir      :: CString -> IO Addr
583 foreign import ccall "libHS_cbits" "readDir__"          unsafe primReadDir      :: Addr -> IO Addr
584 foreign import ccall "libHS_cbits" "get_dirent_d_name"   unsafe primGetDirentDName      :: Addr -> IO Addr
585 foreign import ccall "libHS_cbits" "setCurrentDirectory" unsafe primSetCurrentDirectory :: CString -> IO Int
586 foreign import ccall "libHS_cbits" "getCurrentDirectory" unsafe primGetCurrentDirectory :: IO Addr
587 foreign import ccall "libc"        "free"                unsafe primFree                :: Addr -> IO ()
588 foreign import ccall "libc"        "malloc"              unsafe primMalloc              :: Word -> IO Addr
589 foreign import ccall "libc"        "chmod"               unsafe primChmod               :: CString -> Word -> IO Int
590 \end{code}
591