~ubuntu-branches/ubuntu/precise/ghc/precise

« back to all changes in this revision

Viewing changes to libraries/unix/System/Posix/Files.hsc

  • Committer: Bazaar Package Importer
  • Author(s): Joachim Breitner
  • Date: 2011-01-17 12:49:24 UTC
  • Revision ID: james.westby@ubuntu.com-20110117124924-do1pym1jlf5o636m
Tags: upstream-7.0.1
ImportĀ upstreamĀ versionĀ 7.0.1

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
{-# LANGUAGE ForeignFunctionInterface #-}
 
2
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
 
3
-----------------------------------------------------------------------------
 
4
-- |
 
5
-- Module      :  System.Posix.Files
 
6
-- Copyright   :  (c) The University of Glasgow 2002
 
7
-- License     :  BSD-style (see the file libraries/base/LICENSE)
 
8
-- 
 
9
-- Maintainer  :  libraries@haskell.org
 
10
-- Stability   :  provisional
 
11
-- Portability :  non-portable (requires POSIX)
 
12
--
 
13
-- Functions defined by the POSIX standards for manipulating and querying the
 
14
-- file system. Names of underlying POSIX functions are indicated whenever
 
15
-- possible. A more complete documentation of the POSIX functions together
 
16
-- with a more detailed description of different error conditions are usually
 
17
-- available in the system's manual pages or from
 
18
-- <http://www.unix.org/version3/online.html> (free registration required).
 
19
--
 
20
-- When a function that calls an underlying POSIX function fails, the errno
 
21
-- code is converted to an 'IOError' using 'Foreign.C.Error.errnoToIOError'.
 
22
-- For a list of which errno codes may be generated, consult the POSIX
 
23
-- documentation for the underlying function.
 
24
--
 
25
-----------------------------------------------------------------------------
 
26
 
 
27
module System.Posix.Files (
 
28
    -- * File modes
 
29
    -- FileMode exported by System.Posix.Types
 
30
    unionFileModes, intersectFileModes,
 
31
    nullFileMode,
 
32
    ownerReadMode, ownerWriteMode, ownerExecuteMode, ownerModes,
 
33
    groupReadMode, groupWriteMode, groupExecuteMode, groupModes,
 
34
    otherReadMode, otherWriteMode, otherExecuteMode, otherModes,
 
35
    setUserIDMode, setGroupIDMode,
 
36
    stdFileMode,   accessModes,
 
37
    fileTypeModes,
 
38
    blockSpecialMode, characterSpecialMode, namedPipeMode, regularFileMode,
 
39
    directoryMode, symbolicLinkMode, socketMode,
 
40
 
 
41
    -- ** Setting file modes
 
42
    setFileMode, setFdMode, setFileCreationMask,
 
43
 
 
44
    -- ** Checking file existence and permissions
 
45
    fileAccess, fileExist,
 
46
 
 
47
    -- * File status
 
48
    FileStatus,
 
49
    -- ** Obtaining file status
 
50
    getFileStatus, getFdStatus, getSymbolicLinkStatus,
 
51
    -- ** Querying file status
 
52
    deviceID, fileID, fileMode, linkCount, fileOwner, fileGroup,
 
53
    specialDeviceID, fileSize, accessTime, modificationTime,
 
54
    statusChangeTime,
 
55
    isBlockDevice, isCharacterDevice, isNamedPipe, isRegularFile,
 
56
    isDirectory, isSymbolicLink, isSocket,
 
57
 
 
58
    -- * Creation
 
59
    createNamedPipe, 
 
60
    createDevice,
 
61
 
 
62
    -- * Hard links
 
63
    createLink, removeLink,
 
64
 
 
65
    -- * Symbolic links
 
66
    createSymbolicLink, readSymbolicLink,
 
67
 
 
68
    -- * Renaming files
 
69
    rename,
 
70
 
 
71
    -- * Changing file ownership
 
72
    setOwnerAndGroup,  setFdOwnerAndGroup,
 
73
#if HAVE_LCHOWN
 
74
    setSymbolicLinkOwnerAndGroup,
 
75
#endif
 
76
 
 
77
    -- * Changing file timestamps
 
78
    setFileTimes, touchFile,
 
79
 
 
80
    -- * Setting file sizes
 
81
    setFileSize, setFdSize,
 
82
 
 
83
    -- * Find system-specific limits for a file
 
84
    PathVar(..), getPathVar, getFdPathVar,
 
85
  ) where
 
86
 
 
87
#include "HsUnix.h"
 
88
 
 
89
import System.Posix.Error
 
90
import System.Posix.Types
 
91
import System.IO.Unsafe
 
92
import Data.Bits
 
93
import System.Posix.Internals
 
94
import Foreign hiding (unsafePerformIO)
 
95
import Foreign.C
 
96
 
 
97
-- -----------------------------------------------------------------------------
 
98
-- POSIX file modes
 
99
 
 
100
-- The abstract type 'FileMode', constants and operators for
 
101
-- manipulating the file modes defined by POSIX.
 
102
 
 
103
-- | No permissions.
 
104
nullFileMode :: FileMode
 
105
nullFileMode = 0
 
106
 
 
107
-- | Owner has read permission.
 
108
ownerReadMode :: FileMode
 
109
ownerReadMode = (#const S_IRUSR)
 
110
 
 
111
-- | Owner has write permission.
 
112
ownerWriteMode :: FileMode
 
113
ownerWriteMode = (#const S_IWUSR)
 
114
 
 
115
-- | Owner has execute permission.
 
116
ownerExecuteMode :: FileMode
 
117
ownerExecuteMode = (#const S_IXUSR)
 
118
 
 
119
-- | Group has read permission.
 
120
groupReadMode :: FileMode
 
121
groupReadMode = (#const S_IRGRP)
 
122
 
 
123
-- | Group has write permission.
 
124
groupWriteMode :: FileMode
 
125
groupWriteMode = (#const S_IWGRP)
 
126
 
 
127
-- | Group has execute permission.
 
128
groupExecuteMode :: FileMode
 
129
groupExecuteMode = (#const S_IXGRP)
 
130
 
 
131
-- | Others have read permission.
 
132
otherReadMode :: FileMode
 
133
otherReadMode = (#const S_IROTH)
 
134
 
 
135
-- | Others have write permission.
 
136
otherWriteMode :: FileMode
 
137
otherWriteMode = (#const S_IWOTH)
 
138
 
 
139
-- | Others have execute permission.
 
140
otherExecuteMode :: FileMode
 
141
otherExecuteMode = (#const S_IXOTH)
 
142
 
 
143
-- | Set user ID on execution.
 
144
setUserIDMode :: FileMode
 
145
setUserIDMode = (#const S_ISUID)
 
146
 
 
147
-- | Set group ID on execution.
 
148
setGroupIDMode :: FileMode
 
149
setGroupIDMode = (#const S_ISGID)
 
150
 
 
151
-- | Owner, group and others have read and write permission.
 
152
stdFileMode :: FileMode
 
153
stdFileMode = ownerReadMode  .|. ownerWriteMode .|. 
 
154
              groupReadMode  .|. groupWriteMode .|. 
 
155
              otherReadMode  .|. otherWriteMode
 
156
 
 
157
-- | Owner has read, write and execute permission.
 
158
ownerModes :: FileMode
 
159
ownerModes = (#const S_IRWXU)
 
160
 
 
161
-- | Group has read, write and execute permission.
 
162
groupModes :: FileMode
 
163
groupModes = (#const S_IRWXG)
 
164
 
 
165
-- | Others have read, write and execute permission.
 
166
otherModes :: FileMode
 
167
otherModes = (#const S_IRWXO)
 
168
 
 
169
-- | Owner, group and others have read, write and execute permission.
 
170
accessModes :: FileMode
 
171
accessModes = ownerModes .|. groupModes .|. otherModes
 
172
 
 
173
-- | Combines the two file modes into one that contains modes that appear in
 
174
-- either.
 
175
unionFileModes :: FileMode -> FileMode -> FileMode
 
176
unionFileModes m1 m2 = m1 .|. m2
 
177
 
 
178
-- | Combines two file modes into one that only contains modes that appear in
 
179
-- both.
 
180
intersectFileModes :: FileMode -> FileMode -> FileMode
 
181
intersectFileModes m1 m2 = m1 .&. m2
 
182
 
 
183
fileTypeModes :: FileMode
 
184
fileTypeModes = (#const S_IFMT)
 
185
 
 
186
blockSpecialMode :: FileMode
 
187
blockSpecialMode = (#const S_IFBLK)
 
188
 
 
189
characterSpecialMode :: FileMode
 
190
characterSpecialMode = (#const S_IFCHR)
 
191
 
 
192
namedPipeMode :: FileMode
 
193
namedPipeMode = (#const S_IFIFO)
 
194
 
 
195
regularFileMode :: FileMode
 
196
regularFileMode = (#const S_IFREG)
 
197
 
 
198
directoryMode :: FileMode
 
199
directoryMode = (#const S_IFDIR)
 
200
 
 
201
symbolicLinkMode :: FileMode
 
202
symbolicLinkMode = (#const S_IFLNK)
 
203
 
 
204
socketMode :: FileMode
 
205
socketMode = (#const S_IFSOCK)
 
206
 
 
207
-- | @setFileMode path mode@ changes permission of the file given by @path@
 
208
-- to @mode@. This operation may fail with 'throwErrnoPathIfMinus1_' if @path@
 
209
-- doesn't exist or if the effective user ID of the current process is not that
 
210
-- of the file's owner.
 
211
--
 
212
-- Note: calls @chmod@.
 
213
setFileMode :: FilePath -> FileMode -> IO ()
 
214
setFileMode name m =
 
215
  withCString name $ \s -> do
 
216
    throwErrnoPathIfMinus1_ "setFileMode" name (c_chmod s m)
 
217
 
 
218
-- | @setFdMode fd mode@ acts like 'setFileMode' but uses a file descriptor
 
219
-- @fd@ instead of a 'FilePath'.
 
220
--
 
221
-- Note: calls @fchmod@.
 
222
setFdMode :: Fd -> FileMode -> IO ()
 
223
setFdMode (Fd fd) m =
 
224
  throwErrnoIfMinus1_ "setFdMode" (c_fchmod fd m)
 
225
 
 
226
foreign import ccall unsafe "fchmod" 
 
227
  c_fchmod :: CInt -> CMode -> IO CInt
 
228
 
 
229
-- | @setFileCreationMask mode@ sets the file mode creation mask to @mode@.
 
230
-- Modes set by this operation are subtracted from files and directories upon
 
231
-- creation. The previous file creation mask is returned.
 
232
--
 
233
-- Note: calls @umask@.
 
234
setFileCreationMask :: FileMode -> IO FileMode
 
235
setFileCreationMask mask = c_umask mask
 
236
 
 
237
-- -----------------------------------------------------------------------------
 
238
-- access()
 
239
 
 
240
-- | @fileAccess name read write exec@ checks if the file (or other file system
 
241
-- object) @name@ can be accessed for reading, writing and\/or executing. To
 
242
-- check a permission set the corresponding argument to 'True'.
 
243
--
 
244
-- Note: calls @access@.
 
245
fileAccess :: FilePath -> Bool -> Bool -> Bool -> IO Bool
 
246
fileAccess name readOK writeOK execOK = access name flags
 
247
  where
 
248
   flags   = read_f .|. write_f .|. exec_f
 
249
   read_f  = if readOK  then (#const R_OK) else 0
 
250
   write_f = if writeOK then (#const W_OK) else 0
 
251
   exec_f  = if execOK  then (#const X_OK) else 0
 
252
 
 
253
-- | Checks for the existence of the file.
 
254
--
 
255
-- Note: calls @access@.
 
256
fileExist :: FilePath -> IO Bool
 
257
fileExist name = 
 
258
  withCString name $ \s -> do
 
259
    r <- c_access s (#const F_OK)
 
260
    if (r == 0)
 
261
        then return True
 
262
        else do err <- getErrno
 
263
                if (err == eNOENT)
 
264
                   then return False
 
265
                   else throwErrnoPath "fileExist" name
 
266
 
 
267
access :: FilePath -> CMode -> IO Bool
 
268
access name flags = 
 
269
  withCString name $ \s -> do
 
270
    r <- c_access s (fromIntegral flags)
 
271
    if (r == 0)
 
272
        then return True
 
273
        else do err <- getErrno
 
274
                if (err == eACCES)
 
275
                   then return False
 
276
                   else throwErrnoPath "fileAccess" name
 
277
 
 
278
-- -----------------------------------------------------------------------------
 
279
-- stat() support
 
280
 
 
281
-- | POSIX defines operations to get information, such as owner, permissions,
 
282
-- size and access times, about a file. This information is represented by the
 
283
-- 'FileStatus' type.
 
284
--
 
285
-- Note: see @chmod@.
 
286
newtype FileStatus = FileStatus (ForeignPtr CStat)
 
287
 
 
288
-- | ID of the device on which this file resides.
 
289
deviceID         :: FileStatus -> DeviceID
 
290
-- | inode number
 
291
fileID           :: FileStatus -> FileID
 
292
-- | File mode (such as permissions).
 
293
fileMode         :: FileStatus -> FileMode
 
294
-- | Number of hard links to this file.
 
295
linkCount        :: FileStatus -> LinkCount
 
296
-- | ID of owner.
 
297
fileOwner        :: FileStatus -> UserID
 
298
-- | ID of group.
 
299
fileGroup        :: FileStatus -> GroupID
 
300
-- | Describes the device that this file represents.
 
301
specialDeviceID  :: FileStatus -> DeviceID
 
302
-- | Size of the file in bytes. If this file is a symbolic link the size is
 
303
-- the length of the pathname it contains.
 
304
fileSize         :: FileStatus -> FileOffset
 
305
-- | Time of last access.
 
306
accessTime       :: FileStatus -> EpochTime
 
307
-- | Time of last modification.
 
308
modificationTime :: FileStatus -> EpochTime
 
309
-- | Time of last status change (i.e. owner, group, link count, mode, etc.).
 
310
statusChangeTime :: FileStatus -> EpochTime
 
311
 
 
312
deviceID (FileStatus stat) = 
 
313
  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_dev)
 
314
fileID (FileStatus stat) = 
 
315
  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_ino)
 
316
fileMode (FileStatus stat) =
 
317
  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_mode)
 
318
linkCount (FileStatus stat) =
 
319
  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_nlink)
 
320
fileOwner (FileStatus stat) =
 
321
  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_uid)
 
322
fileGroup (FileStatus stat) =
 
323
  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_gid)
 
324
specialDeviceID (FileStatus stat) =
 
325
  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_rdev)
 
326
fileSize (FileStatus stat) =
 
327
  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_size)
 
328
accessTime (FileStatus stat) =
 
329
  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_atime)
 
330
modificationTime (FileStatus stat) =
 
331
  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_mtime)
 
332
statusChangeTime (FileStatus stat) =
 
333
  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_ctime)
 
334
 
 
335
-- | Checks if this file is a block device.
 
336
isBlockDevice     :: FileStatus -> Bool
 
337
-- | Checks if this file is a character device.
 
338
isCharacterDevice :: FileStatus -> Bool
 
339
-- | Checks if this file is a named pipe device.
 
340
isNamedPipe       :: FileStatus -> Bool
 
341
-- | Checks if this file is a regular file device.
 
342
isRegularFile     :: FileStatus -> Bool
 
343
-- | Checks if this file is a directory device.
 
344
isDirectory       :: FileStatus -> Bool
 
345
-- | Checks if this file is a symbolic link device.
 
346
isSymbolicLink    :: FileStatus -> Bool
 
347
-- | Checks if this file is a socket device.
 
348
isSocket          :: FileStatus -> Bool
 
349
 
 
350
isBlockDevice stat = 
 
351
  (fileMode stat `intersectFileModes` fileTypeModes) == blockSpecialMode
 
352
isCharacterDevice stat = 
 
353
  (fileMode stat `intersectFileModes` fileTypeModes) == characterSpecialMode
 
354
isNamedPipe stat = 
 
355
  (fileMode stat `intersectFileModes` fileTypeModes) == namedPipeMode
 
356
isRegularFile stat = 
 
357
  (fileMode stat `intersectFileModes` fileTypeModes) == regularFileMode
 
358
isDirectory stat = 
 
359
  (fileMode stat `intersectFileModes` fileTypeModes) == directoryMode
 
360
isSymbolicLink stat = 
 
361
  (fileMode stat `intersectFileModes` fileTypeModes) == symbolicLinkMode
 
362
isSocket stat = 
 
363
  (fileMode stat `intersectFileModes` fileTypeModes) == socketMode
 
364
 
 
365
-- | @getFileStatus path@ calls gets the @FileStatus@ information (user ID,
 
366
-- size, access times, etc.) for the file @path@.
 
367
--
 
368
-- Note: calls @stat@.
 
369
getFileStatus :: FilePath -> IO FileStatus
 
370
getFileStatus path = do
 
371
  fp <- mallocForeignPtrBytes (#const sizeof(struct stat)) 
 
372
  withForeignPtr fp $ \p ->
 
373
    withCString path $ \s -> 
 
374
      throwErrnoPathIfMinus1_ "getFileStatus" path (c_stat s p)
 
375
  return (FileStatus fp)
 
376
 
 
377
-- | @getFdStatus fd@ acts as 'getFileStatus' but uses a file descriptor @fd@.
 
378
--
 
379
-- Note: calls @fstat@.
 
380
getFdStatus :: Fd -> IO FileStatus
 
381
getFdStatus (Fd fd) = do
 
382
  fp <- mallocForeignPtrBytes (#const sizeof(struct stat)) 
 
383
  withForeignPtr fp $ \p ->
 
384
    throwErrnoIfMinus1_ "getFdStatus" (c_fstat fd p)
 
385
  return (FileStatus fp)
 
386
 
 
387
-- | Acts as 'getFileStatus' except when the 'FilePath' refers to a symbolic
 
388
-- link. In that case the @FileStatus@ information of the symbolic link itself
 
389
-- is returned instead of that of the file it points to.
 
390
--
 
391
-- Note: calls @lstat@.
 
392
getSymbolicLinkStatus :: FilePath -> IO FileStatus
 
393
getSymbolicLinkStatus path = do
 
394
  fp <- mallocForeignPtrBytes (#const sizeof(struct stat)) 
 
395
  withForeignPtr fp $ \p ->
 
396
    withCString path $ \s -> 
 
397
      throwErrnoPathIfMinus1_ "getSymbolicLinkStatus" path (c_lstat s p)
 
398
  return (FileStatus fp)
 
399
 
 
400
foreign import ccall unsafe "__hsunix_lstat" 
 
401
  c_lstat :: CString -> Ptr CStat -> IO CInt
 
402
 
 
403
-- | @createNamedPipe fifo mode@  
 
404
-- creates a new named pipe, @fifo@, with permissions based on
 
405
-- @mode@. May fail with 'throwErrnoPathIfMinus1_' if a file named @name@
 
406
-- already exists or if the effective user ID of the current process doesn't
 
407
-- have permission to create the pipe.
 
408
--
 
409
-- Note: calls @mkfifo@.
 
410
createNamedPipe :: FilePath -> FileMode -> IO ()
 
411
createNamedPipe name mode = do
 
412
  withCString name $ \s -> 
 
413
    throwErrnoPathIfMinus1_ "createNamedPipe" name (c_mkfifo s mode)
 
414
 
 
415
-- | @createDevice path mode dev@ creates either a regular or a special file
 
416
-- depending on the value of @mode@ (and @dev@).  @mode@ will normally be either
 
417
-- 'blockSpecialMode' or 'characterSpecialMode'.  May fail with
 
418
-- 'throwErrnoPathIfMinus1_' if a file named @name@ already exists or if the
 
419
-- effective user ID of the current process doesn't have permission to create
 
420
-- the file.
 
421
--
 
422
-- Note: calls @mknod@.
 
423
createDevice :: FilePath -> FileMode -> DeviceID -> IO ()
 
424
createDevice path mode dev =
 
425
  withCString path $ \s ->
 
426
    throwErrnoPathIfMinus1_ "createDevice" path (c_mknod s mode dev)
 
427
 
 
428
foreign import ccall unsafe "__hsunix_mknod" 
 
429
  c_mknod :: CString -> CMode -> CDev -> IO CInt
 
430
 
 
431
-- -----------------------------------------------------------------------------
 
432
-- Hard links
 
433
 
 
434
-- | @createLink old new@ creates a new path, @new@, linked to an existing file,
 
435
-- @old@.
 
436
--
 
437
-- Note: calls @link@.
 
438
createLink :: FilePath -> FilePath -> IO ()
 
439
createLink name1 name2 =
 
440
  withCString name1 $ \s1 ->
 
441
  withCString name2 $ \s2 ->
 
442
  throwErrnoPathIfMinus1_ "createLink" name1 (c_link s1 s2)
 
443
 
 
444
-- | @removeLink path@ removes the link named @path@.
 
445
--
 
446
-- Note: calls @unlink@.
 
447
removeLink :: FilePath -> IO ()
 
448
removeLink name =
 
449
  withCString name $ \s ->
 
450
  throwErrnoPathIfMinus1_ "removeLink" name (c_unlink s)
 
451
 
 
452
-- -----------------------------------------------------------------------------
 
453
-- Symbolic Links
 
454
 
 
455
-- | @createSymbolicLink file1 file2@ creates a symbolic link named @file2@
 
456
-- which points to the file @file1@.
 
457
--
 
458
-- Symbolic links are interpreted at run-time as if the contents of the link
 
459
-- had been substituted into the path being followed to find a file or directory.
 
460
--
 
461
-- Note: calls @symlink@.
 
462
createSymbolicLink :: FilePath -> FilePath -> IO ()
 
463
createSymbolicLink file1 file2 =
 
464
  withCString file1 $ \s1 ->
 
465
  withCString file2 $ \s2 ->
 
466
  throwErrnoPathIfMinus1_ "createSymbolicLink" file1 (c_symlink s1 s2)
 
467
 
 
468
foreign import ccall unsafe "symlink"
 
469
  c_symlink :: CString -> CString -> IO CInt
 
470
 
 
471
-- ToDo: should really use SYMLINK_MAX, but not everyone supports it yet,
 
472
-- and it seems that the intention is that SYMLINK_MAX is no larger than
 
473
-- PATH_MAX.
 
474
#if !defined(PATH_MAX)
 
475
-- PATH_MAX is not defined on systems with unlimited path length.
 
476
-- Ugly.  Fix this.
 
477
#define PATH_MAX 4096
 
478
#endif
 
479
 
 
480
-- | Reads the @FilePath@ pointed to by the symbolic link and returns it.
 
481
--
 
482
-- Note: calls @readlink@.
 
483
readSymbolicLink :: FilePath -> IO FilePath
 
484
readSymbolicLink file =
 
485
  allocaArray0 (#const PATH_MAX) $ \buf -> do
 
486
    withCString file $ \s -> do
 
487
      len <- throwErrnoPathIfMinus1 "readSymbolicLink" file $ 
 
488
        c_readlink s buf (#const PATH_MAX)
 
489
      peekCStringLen (buf,fromIntegral len)
 
490
 
 
491
foreign import ccall unsafe "readlink"
 
492
  c_readlink :: CString -> CString -> CSize -> IO CInt
 
493
 
 
494
-- -----------------------------------------------------------------------------
 
495
-- Renaming files
 
496
 
 
497
-- | @rename old new@ renames a file or directory from @old@ to @new@.
 
498
--
 
499
-- Note: calls @rename@.
 
500
rename :: FilePath -> FilePath -> IO ()
 
501
rename name1 name2 =
 
502
  withCString name1 $ \s1 ->
 
503
  withCString name2 $ \s2 ->
 
504
  throwErrnoPathIfMinus1_ "rename" name1 (c_rename s1 s2)
 
505
 
 
506
foreign import ccall unsafe "rename"
 
507
   c_rename :: CString -> CString -> IO CInt
 
508
 
 
509
-- -----------------------------------------------------------------------------
 
510
-- chown()
 
511
 
 
512
-- | @setOwnerAndGroup path uid gid@ changes the owner and group of @path@ to
 
513
-- @uid@ and @gid@, respectively.
 
514
--
 
515
-- If @uid@ or @gid@ is specified as -1, then that ID is not changed.
 
516
--
 
517
-- Note: calls @chown@.
 
518
setOwnerAndGroup :: FilePath -> UserID -> GroupID -> IO ()
 
519
setOwnerAndGroup name uid gid = do
 
520
  withCString name $ \s ->
 
521
    throwErrnoPathIfMinus1_ "setOwnerAndGroup" name (c_chown s uid gid)
 
522
 
 
523
foreign import ccall unsafe "chown"
 
524
  c_chown :: CString -> CUid -> CGid -> IO CInt
 
525
 
 
526
-- | Acts as 'setOwnerAndGroup' but uses a file descriptor instead of a
 
527
-- 'FilePath'.
 
528
--
 
529
-- Note: calls @fchown@.
 
530
setFdOwnerAndGroup :: Fd -> UserID -> GroupID -> IO ()
 
531
setFdOwnerAndGroup (Fd fd) uid gid = 
 
532
  throwErrnoIfMinus1_ "setFdOwnerAndGroup" (c_fchown fd uid gid)
 
533
 
 
534
foreign import ccall unsafe "fchown"
 
535
  c_fchown :: CInt -> CUid -> CGid -> IO CInt
 
536
 
 
537
#if HAVE_LCHOWN
 
538
-- | Acts as 'setOwnerAndGroup' but does not follow symlinks (and thus
 
539
-- changes permissions on the link itself).
 
540
--
 
541
-- Note: calls @lchown@.
 
542
setSymbolicLinkOwnerAndGroup :: FilePath -> UserID -> GroupID -> IO ()
 
543
setSymbolicLinkOwnerAndGroup name uid gid = do
 
544
  withCString name $ \s ->
 
545
    throwErrnoPathIfMinus1_ "setSymbolicLinkOwnerAndGroup" name
 
546
        (c_lchown s uid gid)
 
547
 
 
548
foreign import ccall unsafe "lchown"
 
549
  c_lchown :: CString -> CUid -> CGid -> IO CInt
 
550
#endif
 
551
 
 
552
-- -----------------------------------------------------------------------------
 
553
-- utime()
 
554
 
 
555
-- | @setFileTimes path atime mtime@ sets the access and modification times
 
556
-- associated with file @path@ to @atime@ and @mtime@, respectively.
 
557
--
 
558
-- Note: calls @utime@.
 
559
setFileTimes :: FilePath -> EpochTime -> EpochTime -> IO ()
 
560
setFileTimes name atime mtime = do
 
561
  withCString name $ \s ->
 
562
   allocaBytes (#const sizeof(struct utimbuf)) $ \p -> do
 
563
     (#poke struct utimbuf, actime)  p atime
 
564
     (#poke struct utimbuf, modtime) p mtime
 
565
     throwErrnoPathIfMinus1_ "setFileTimes" name (c_utime s p)
 
566
 
 
567
-- | @touchFile path@ sets the access and modification times associated with
 
568
-- file @path@ to the current time.
 
569
--
 
570
-- Note: calls @utime@.
 
571
touchFile :: FilePath -> IO ()
 
572
touchFile name = do
 
573
  withCString name $ \s ->
 
574
   throwErrnoPathIfMinus1_ "touchFile" name (c_utime s nullPtr)
 
575
 
 
576
-- -----------------------------------------------------------------------------
 
577
-- Setting file sizes
 
578
 
 
579
-- | Truncates the file down to the specified length. If the file was larger
 
580
-- than the given length before this operation was performed the extra is lost.
 
581
--
 
582
-- Note: calls @truncate@.
 
583
setFileSize :: FilePath -> FileOffset -> IO ()
 
584
setFileSize file off = 
 
585
  withCString file $ \s ->
 
586
    throwErrnoPathIfMinus1_ "setFileSize" file (c_truncate s off)
 
587
 
 
588
foreign import ccall unsafe "truncate"
 
589
  c_truncate :: CString -> COff -> IO CInt
 
590
 
 
591
-- | Acts as 'setFileSize' but uses a file descriptor instead of a 'FilePath'.
 
592
--
 
593
-- Note: calls @ftruncate@.
 
594
setFdSize :: Fd -> FileOffset -> IO ()
 
595
setFdSize (Fd fd) off =
 
596
  throwErrnoIfMinus1_ "setFdSize" (c_ftruncate fd off)
 
597
 
 
598
-- -----------------------------------------------------------------------------
 
599
-- pathconf()/fpathconf() support
 
600
 
 
601
data PathVar
 
602
  = FileSizeBits                  {- _PC_FILESIZEBITS     -}
 
603
  | LinkLimit                     {- _PC_LINK_MAX         -}
 
604
  | InputLineLimit                {- _PC_MAX_CANON        -}
 
605
  | InputQueueLimit               {- _PC_MAX_INPUT        -}
 
606
  | FileNameLimit                 {- _PC_NAME_MAX         -}
 
607
  | PathNameLimit                 {- _PC_PATH_MAX         -}
 
608
  | PipeBufferLimit               {- _PC_PIPE_BUF         -}
 
609
                                  -- These are described as optional in POSIX:
 
610
                                  {- _PC_ALLOC_SIZE_MIN     -}
 
611
                                  {- _PC_REC_INCR_XFER_SIZE -}
 
612
                                  {- _PC_REC_MAX_XFER_SIZE  -}
 
613
                                  {- _PC_REC_MIN_XFER_SIZE  -}
 
614
                                  {- _PC_REC_XFER_ALIGN     -}
 
615
  | SymbolicLinkLimit             {- _PC_SYMLINK_MAX      -}
 
616
  | SetOwnerAndGroupIsRestricted  {- _PC_CHOWN_RESTRICTED -}
 
617
  | FileNamesAreNotTruncated      {- _PC_NO_TRUNC         -}
 
618
  | VDisableChar                  {- _PC_VDISABLE         -}
 
619
  | AsyncIOAvailable              {- _PC_ASYNC_IO         -}
 
620
  | PrioIOAvailable               {- _PC_PRIO_IO          -}
 
621
  | SyncIOAvailable               {- _PC_SYNC_IO          -}
 
622
 
 
623
pathVarConst :: PathVar -> CInt
 
624
pathVarConst v = case v of
 
625
        LinkLimit                       -> (#const _PC_LINK_MAX)
 
626
        InputLineLimit                  -> (#const _PC_MAX_CANON)
 
627
        InputQueueLimit                 -> (#const _PC_MAX_INPUT)
 
628
        FileNameLimit                   -> (#const _PC_NAME_MAX)
 
629
        PathNameLimit                   -> (#const _PC_PATH_MAX)
 
630
        PipeBufferLimit                 -> (#const _PC_PIPE_BUF)
 
631
        SetOwnerAndGroupIsRestricted    -> (#const _PC_CHOWN_RESTRICTED)
 
632
        FileNamesAreNotTruncated        -> (#const _PC_NO_TRUNC)
 
633
        VDisableChar                    -> (#const _PC_VDISABLE)
 
634
 
 
635
#ifdef _PC_SYNC_IO
 
636
        SyncIOAvailable         -> (#const _PC_SYNC_IO)
 
637
#else
 
638
        SyncIOAvailable         -> error "_PC_SYNC_IO not available"
 
639
#endif
 
640
 
 
641
#ifdef _PC_ASYNC_IO
 
642
        AsyncIOAvailable        -> (#const _PC_ASYNC_IO)
 
643
#else
 
644
        AsyncIOAvailable        -> error "_PC_ASYNC_IO not available"
 
645
#endif
 
646
 
 
647
#ifdef _PC_PRIO_IO
 
648
        PrioIOAvailable         -> (#const _PC_PRIO_IO)
 
649
#else
 
650
        PrioIOAvailable         -> error "_PC_PRIO_IO not available"
 
651
#endif
 
652
 
 
653
#if _PC_FILESIZEBITS
 
654
        FileSizeBits            -> (#const _PC_FILESIZEBITS)
 
655
#else
 
656
        FileSizeBits            -> error "_PC_FILESIZEBITS not available"
 
657
#endif
 
658
 
 
659
#if _PC_SYMLINK_MAX
 
660
        SymbolicLinkLimit       -> (#const _PC_SYMLINK_MAX)
 
661
#else
 
662
        SymbolicLinkLimit       -> error "_PC_SYMLINK_MAX not available"
 
663
#endif
 
664
 
 
665
 
 
666
-- | @getPathVar var path@ obtains the dynamic value of the requested
 
667
-- configurable file limit or option associated with file or directory @path@.
 
668
-- For defined file limits, @getPathVar@ returns the associated
 
669
-- value.  For defined file options, the result of @getPathVar@
 
670
-- is undefined, but not failure.
 
671
--
 
672
-- Note: calls @pathconf@.
 
673
getPathVar :: FilePath -> PathVar -> IO Limit
 
674
getPathVar name v = do
 
675
  withCString name $ \ nameP -> 
 
676
    throwErrnoPathIfMinus1 "getPathVar" name $ 
 
677
      c_pathconf nameP (pathVarConst v)
 
678
 
 
679
foreign import ccall unsafe "pathconf" 
 
680
  c_pathconf :: CString -> CInt -> IO CLong
 
681
 
 
682
 
 
683
-- | @getFdPathVar var fd@ obtains the dynamic value of the requested
 
684
-- configurable file limit or option associated with the file or directory
 
685
-- attached to the open channel @fd@. For defined file limits, @getFdPathVar@
 
686
-- returns the associated value.  For defined file options, the result of
 
687
-- @getFdPathVar@ is undefined, but not failure.
 
688
--
 
689
-- Note: calls @fpathconf@.
 
690
getFdPathVar :: Fd -> PathVar -> IO Limit
 
691
getFdPathVar (Fd fd) v =
 
692
    throwErrnoIfMinus1 "getFdPathVar" $ 
 
693
      c_fpathconf fd (pathVarConst v)
 
694
 
 
695
foreign import ccall unsafe "fpathconf" 
 
696
  c_fpathconf :: CInt -> CInt -> IO CLong