1{-# LANGUAGE Trustworthy #-}
2
3-----------------------------------------------------------------------------
4-- |
5-- Module      :  System.Posix.Files.Common
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#include "HsUnix.h"
28
29module System.Posix.Files.Common (
30    -- * File modes
31    -- FileMode exported by System.Posix.Types
32    unionFileModes, intersectFileModes,
33    nullFileMode,
34    ownerReadMode, ownerWriteMode, ownerExecuteMode, ownerModes,
35    groupReadMode, groupWriteMode, groupExecuteMode, groupModes,
36    otherReadMode, otherWriteMode, otherExecuteMode, otherModes,
37    setUserIDMode, setGroupIDMode,
38    stdFileMode,   accessModes,
39    fileTypeModes,
40    blockSpecialMode, characterSpecialMode, namedPipeMode, regularFileMode,
41    directoryMode, symbolicLinkMode, socketMode,
42
43    -- ** Setting file modes
44    setFdMode, setFileCreationMask,
45
46    -- * File status
47    FileStatus(..),
48    -- ** Obtaining file status
49    getFdStatus,
50    -- ** Querying file status
51    deviceID, fileID, fileMode, linkCount, fileOwner, fileGroup,
52    specialDeviceID, fileSize, accessTime, modificationTime,
53    statusChangeTime,
54    accessTimeHiRes, modificationTimeHiRes, statusChangeTimeHiRes,
55    setFdTimesHiRes, touchFd,
56    isBlockDevice, isCharacterDevice, isNamedPipe, isRegularFile,
57    isDirectory, isSymbolicLink, isSocket,
58
59    -- * Setting file sizes
60    setFdSize,
61
62    -- * Changing file ownership
63    setFdOwnerAndGroup,
64
65    -- * Find system-specific limits for a file
66    PathVar(..), getFdPathVar, pathVarConst,
67
68    -- * Low level types and functions
69#ifdef HAVE_UTIMENSAT
70    CTimeSpec(..),
71    toCTimeSpec,
72    c_utimensat,
73#endif
74    CTimeVal(..),
75    toCTimeVal,
76    c_utimes,
77#ifdef HAVE_LUTIMES
78    c_lutimes,
79#endif
80  ) where
81
82import System.Posix.Types
83import System.IO.Unsafe
84import Data.Bits
85import Data.Int
86import Data.Ratio
87import Data.Time.Clock.POSIX (POSIXTime)
88import System.Posix.Internals
89import Foreign.C
90import Foreign.ForeignPtr
91#if defined(HAVE_FUTIMES) || defined(HAVE_FUTIMENS)
92import Foreign.Marshal (withArray)
93#endif
94import Foreign.Ptr
95import Foreign.Storable
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.
104nullFileMode :: FileMode
105nullFileMode = 0
106
107-- | Owner has read permission.
108ownerReadMode :: FileMode
109ownerReadMode = (#const S_IRUSR)
110
111-- | Owner has write permission.
112ownerWriteMode :: FileMode
113ownerWriteMode = (#const S_IWUSR)
114
115-- | Owner has execute permission.
116ownerExecuteMode :: FileMode
117ownerExecuteMode = (#const S_IXUSR)
118
119-- | Group has read permission.
120groupReadMode :: FileMode
121groupReadMode = (#const S_IRGRP)
122
123-- | Group has write permission.
124groupWriteMode :: FileMode
125groupWriteMode = (#const S_IWGRP)
126
127-- | Group has execute permission.
128groupExecuteMode :: FileMode
129groupExecuteMode = (#const S_IXGRP)
130
131-- | Others have read permission.
132otherReadMode :: FileMode
133otherReadMode = (#const S_IROTH)
134
135-- | Others have write permission.
136otherWriteMode :: FileMode
137otherWriteMode = (#const S_IWOTH)
138
139-- | Others have execute permission.
140otherExecuteMode :: FileMode
141otherExecuteMode = (#const S_IXOTH)
142
143-- | Set user ID on execution.
144setUserIDMode :: FileMode
145setUserIDMode = (#const S_ISUID)
146
147-- | Set group ID on execution.
148setGroupIDMode :: FileMode
149setGroupIDMode = (#const S_ISGID)
150
151-- | Owner, group and others have read and write permission.
152stdFileMode :: FileMode
153stdFileMode = ownerReadMode  .|. ownerWriteMode .|.
154              groupReadMode  .|. groupWriteMode .|.
155              otherReadMode  .|. otherWriteMode
156
157-- | Owner has read, write and execute permission.
158ownerModes :: FileMode
159ownerModes = (#const S_IRWXU)
160
161-- | Group has read, write and execute permission.
162groupModes :: FileMode
163groupModes = (#const S_IRWXG)
164
165-- | Others have read, write and execute permission.
166otherModes :: FileMode
167otherModes = (#const S_IRWXO)
168
169-- | Owner, group and others have read, write and execute permission.
170accessModes :: FileMode
171accessModes = ownerModes .|. groupModes .|. otherModes
172
173-- | Combines the two file modes into one that contains modes that appear in
174-- either.
175unionFileModes :: FileMode -> FileMode -> FileMode
176unionFileModes m1 m2 = m1 .|. m2
177
178-- | Combines two file modes into one that only contains modes that appear in
179-- both.
180intersectFileModes :: FileMode -> FileMode -> FileMode
181intersectFileModes m1 m2 = m1 .&. m2
182
183fileTypeModes :: FileMode
184fileTypeModes = (#const S_IFMT)
185
186blockSpecialMode :: FileMode
187blockSpecialMode = (#const S_IFBLK)
188
189characterSpecialMode :: FileMode
190characterSpecialMode = (#const S_IFCHR)
191
192namedPipeMode :: FileMode
193namedPipeMode = (#const S_IFIFO)
194
195regularFileMode :: FileMode
196regularFileMode = (#const S_IFREG)
197
198directoryMode :: FileMode
199directoryMode = (#const S_IFDIR)
200
201symbolicLinkMode :: FileMode
202symbolicLinkMode = (#const S_IFLNK)
203
204socketMode :: FileMode
205socketMode = (#const S_IFSOCK)
206
207-- | @setFdMode fd mode@ acts like 'setFileMode' but uses a file descriptor
208-- @fd@ instead of a 'FilePath'.
209--
210-- Note: calls @fchmod@.
211setFdMode :: Fd -> FileMode -> IO ()
212setFdMode (Fd fd) m =
213  throwErrnoIfMinus1_ "setFdMode" (c_fchmod fd m)
214
215foreign import ccall unsafe "fchmod"
216  c_fchmod :: CInt -> CMode -> IO CInt
217
218-- | @setFileCreationMask mode@ sets the file mode creation mask to @mode@.
219-- Modes set by this operation are subtracted from files and directories upon
220-- creation. The previous file creation mask is returned.
221--
222-- Note: calls @umask@.
223setFileCreationMask :: FileMode -> IO FileMode
224setFileCreationMask mask = c_umask mask
225
226-- -----------------------------------------------------------------------------
227-- stat() support
228
229-- | POSIX defines operations to get information, such as owner, permissions,
230-- size and access times, about a file. This information is represented by the
231-- 'FileStatus' type.
232--
233-- Note: see @chmod@.
234newtype FileStatus = FileStatus (ForeignPtr CStat)
235
236-- | ID of the device on which this file resides.
237deviceID         :: FileStatus -> DeviceID
238-- | inode number
239fileID           :: FileStatus -> FileID
240-- | File mode (such as permissions).
241fileMode         :: FileStatus -> FileMode
242-- | Number of hard links to this file.
243linkCount        :: FileStatus -> LinkCount
244-- | ID of owner.
245fileOwner        :: FileStatus -> UserID
246-- | ID of group.
247fileGroup        :: FileStatus -> GroupID
248-- | Describes the device that this file represents.
249specialDeviceID  :: FileStatus -> DeviceID
250-- | Size of the file in bytes. If this file is a symbolic link the size is
251-- the length of the pathname it contains.
252fileSize         :: FileStatus -> FileOffset
253-- | Time of last access.
254accessTime       :: FileStatus -> EpochTime
255-- | Time of last access in sub-second resolution.
256accessTimeHiRes  :: FileStatus -> POSIXTime
257-- | Time of last modification.
258modificationTime :: FileStatus -> EpochTime
259-- | Time of last modification in sub-second resolution.
260modificationTimeHiRes :: FileStatus -> POSIXTime
261-- | Time of last status change (i.e. owner, group, link count, mode, etc.).
262statusChangeTime :: FileStatus -> EpochTime
263-- | Time of last status change (i.e. owner, group, link count, mode, etc.) in sub-second resolution.
264statusChangeTimeHiRes :: FileStatus -> POSIXTime
265
266deviceID (FileStatus stat) =
267  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_dev)
268fileID (FileStatus stat) =
269  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_ino)
270fileMode (FileStatus stat) =
271  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_mode)
272linkCount (FileStatus stat) =
273  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_nlink)
274fileOwner (FileStatus stat) =
275  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_uid)
276fileGroup (FileStatus stat) =
277  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_gid)
278specialDeviceID (FileStatus stat) =
279  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_rdev)
280fileSize (FileStatus stat) =
281  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_size)
282accessTime (FileStatus stat) =
283  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_atime)
284modificationTime (FileStatus stat) =
285  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_mtime)
286statusChangeTime (FileStatus stat) =
287  unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_ctime)
288
289accessTimeHiRes (FileStatus stat) =
290  unsafePerformIO $ withForeignPtr stat $ \stat_ptr -> do
291    sec  <- (#peek struct stat, st_atime) stat_ptr :: IO EpochTime
292#ifdef HAVE_STRUCT_STAT_ST_ATIM
293    nsec <- (#peek struct stat, st_atim.tv_nsec) stat_ptr :: IO (#type long)
294    let frac = toInteger nsec % 10^(9::Int)
295#elif HAVE_STRUCT_STAT_ST_ATIMESPEC
296    nsec <- (#peek struct stat, st_atimespec.tv_nsec) stat_ptr :: IO (#type long)
297    let frac = toInteger nsec % 10^(9::Int)
298#elif HAVE_STRUCT_STAT_ST_ATIMENSEC
299    nsec <- (#peek struct stat, st_atimensec) stat_ptr :: IO (#type long)
300    let frac = toInteger nsec % 10^(9::Int)
301#elif HAVE_STRUCT_STAT_ST_ATIME_N
302    nsec <- (#peek struct stat, st_atime_n) stat_ptr :: IO (#type int)
303    let frac = toInteger nsec % 10^(9::Int)
304#elif HAVE_STRUCT_STAT_ST_UATIME
305    usec <- (#peek struct stat, st_uatime) stat_ptr :: IO (#type int)
306    let frac = toInteger usec % 10^(6::Int)
307#else
308    let frac = 0
309#endif
310    return $ fromRational $ toRational sec + frac
311
312modificationTimeHiRes (FileStatus stat) =
313  unsafePerformIO $ withForeignPtr stat $ \stat_ptr -> do
314    sec  <- (#peek struct stat, st_mtime) stat_ptr :: IO EpochTime
315#ifdef HAVE_STRUCT_STAT_ST_MTIM
316    nsec <- (#peek struct stat, st_mtim.tv_nsec) stat_ptr :: IO (#type long)
317    let frac = toInteger nsec % 10^(9::Int)
318#elif HAVE_STRUCT_STAT_ST_MTIMESPEC
319    nsec <- (#peek struct stat, st_mtimespec.tv_nsec) stat_ptr :: IO (#type long)
320    let frac = toInteger nsec % 10^(9::Int)
321#elif HAVE_STRUCT_STAT_ST_MTIMENSEC
322    nsec <- (#peek struct stat, st_mtimensec) stat_ptr :: IO (#type long)
323    let frac = toInteger nsec % 10^(9::Int)
324#elif HAVE_STRUCT_STAT_ST_MTIME_N
325    nsec <- (#peek struct stat, st_mtime_n) stat_ptr :: IO (#type int)
326    let frac = toInteger nsec % 10^(9::Int)
327#elif HAVE_STRUCT_STAT_ST_UMTIME
328    usec <- (#peek struct stat, st_umtime) stat_ptr :: IO (#type int)
329    let frac = toInteger usec % 10^(6::Int)
330#else
331    let frac = 0
332#endif
333    return $ fromRational $ toRational sec + frac
334
335statusChangeTimeHiRes (FileStatus stat) =
336  unsafePerformIO $ withForeignPtr stat $ \stat_ptr -> do
337    sec  <- (#peek struct stat, st_ctime) stat_ptr :: IO EpochTime
338#ifdef HAVE_STRUCT_STAT_ST_CTIM
339    nsec <- (#peek struct stat, st_ctim.tv_nsec) stat_ptr :: IO (#type long)
340    let frac = toInteger nsec % 10^(9::Int)
341#elif HAVE_STRUCT_STAT_ST_CTIMESPEC
342    nsec <- (#peek struct stat, st_ctimespec.tv_nsec) stat_ptr :: IO (#type long)
343    let frac = toInteger nsec % 10^(9::Int)
344#elif HAVE_STRUCT_STAT_ST_CTIMENSEC
345    nsec <- (#peek struct stat, st_ctimensec) stat_ptr :: IO (#type long)
346    let frac = toInteger nsec % 10^(9::Int)
347#elif HAVE_STRUCT_STAT_ST_CTIME_N
348    nsec <- (#peek struct stat, st_ctime_n) stat_ptr :: IO (#type int)
349    let frac = toInteger nsec % 10^(9::Int)
350#elif HAVE_STRUCT_STAT_ST_UCTIME
351    usec <- (#peek struct stat, st_uctime) stat_ptr :: IO (#type int)
352    let frac = toInteger usec % 10^(6::Int)
353#else
354    let frac = 0
355#endif
356    return $ fromRational $ toRational sec + frac
357
358-- | Checks if this file is a block device.
359isBlockDevice     :: FileStatus -> Bool
360-- | Checks if this file is a character device.
361isCharacterDevice :: FileStatus -> Bool
362-- | Checks if this file is a named pipe device.
363isNamedPipe       :: FileStatus -> Bool
364-- | Checks if this file is a regular file device.
365isRegularFile     :: FileStatus -> Bool
366-- | Checks if this file is a directory device.
367isDirectory       :: FileStatus -> Bool
368-- | Checks if this file is a symbolic link device.
369isSymbolicLink    :: FileStatus -> Bool
370-- | Checks if this file is a socket device.
371isSocket          :: FileStatus -> Bool
372
373isBlockDevice stat =
374  (fileMode stat `intersectFileModes` fileTypeModes) == blockSpecialMode
375isCharacterDevice stat =
376  (fileMode stat `intersectFileModes` fileTypeModes) == characterSpecialMode
377isNamedPipe stat =
378  (fileMode stat `intersectFileModes` fileTypeModes) == namedPipeMode
379isRegularFile stat =
380  (fileMode stat `intersectFileModes` fileTypeModes) == regularFileMode
381isDirectory stat =
382  (fileMode stat `intersectFileModes` fileTypeModes) == directoryMode
383isSymbolicLink stat =
384  (fileMode stat `intersectFileModes` fileTypeModes) == symbolicLinkMode
385isSocket stat =
386  (fileMode stat `intersectFileModes` fileTypeModes) == socketMode
387
388-- | @getFdStatus fd@ acts as 'getFileStatus' but uses a file descriptor @fd@.
389--
390-- Note: calls @fstat@.
391getFdStatus :: Fd -> IO FileStatus
392getFdStatus (Fd fd) = do
393  fp <- mallocForeignPtrBytes (#const sizeof(struct stat))
394  withForeignPtr fp $ \p ->
395    throwErrnoIfMinus1_ "getFdStatus" (c_fstat fd p)
396  return (FileStatus fp)
397
398-- -----------------------------------------------------------------------------
399-- Setting file times
400
401#if HAVE_UTIMENSAT || HAVE_FUTIMENS
402data CTimeSpec = CTimeSpec EpochTime CLong
403
404instance Storable CTimeSpec where
405    sizeOf    _ = #size struct timespec
406    alignment _ = alignment (undefined :: CInt)
407    poke p (CTimeSpec sec nsec) = do
408        (#poke struct timespec, tv_sec ) p sec
409        (#poke struct timespec, tv_nsec) p nsec
410    peek p = do
411        sec  <- #{peek struct timespec, tv_sec } p
412        nsec <- #{peek struct timespec, tv_nsec} p
413        return $ CTimeSpec sec nsec
414
415toCTimeSpec :: POSIXTime -> CTimeSpec
416toCTimeSpec t = CTimeSpec (CTime sec) (truncate $ 10^(9::Int) * frac)
417  where
418    (sec, frac) = if (frac' < 0) then (sec' - 1, frac' + 1) else (sec', frac')
419    (sec', frac') = properFraction $ toRational t
420#endif
421
422#ifdef HAVE_UTIMENSAT
423foreign import ccall unsafe "utimensat"
424    c_utimensat :: CInt -> CString -> Ptr CTimeSpec -> CInt -> IO CInt
425#endif
426
427#if HAVE_FUTIMENS
428foreign import ccall unsafe "futimens"
429    c_futimens :: CInt -> Ptr CTimeSpec -> IO CInt
430#endif
431
432data CTimeVal = CTimeVal CLong CLong
433
434instance Storable CTimeVal where
435    sizeOf    _ = #size struct timeval
436    alignment _ = alignment (undefined :: CInt)
437    poke p (CTimeVal sec usec) = do
438        (#poke struct timeval, tv_sec ) p sec
439        (#poke struct timeval, tv_usec) p usec
440    peek p = do
441        sec  <- #{peek struct timeval, tv_sec } p
442        usec <- #{peek struct timeval, tv_usec} p
443        return $ CTimeVal sec usec
444
445toCTimeVal :: POSIXTime -> CTimeVal
446toCTimeVal t = CTimeVal sec (truncate $ 10^(6::Int) * frac)
447  where
448    (sec, frac) = if (frac' < 0) then (sec' - 1, frac' + 1) else (sec', frac')
449    (sec', frac') = properFraction $ toRational t
450
451foreign import ccall unsafe "utimes"
452    c_utimes :: CString -> Ptr CTimeVal -> IO CInt
453
454#ifdef HAVE_LUTIMES
455foreign import ccall unsafe "lutimes"
456    c_lutimes :: CString -> Ptr CTimeVal -> IO CInt
457#endif
458
459#if HAVE_FUTIMES
460foreign import ccall unsafe "futimes"
461    c_futimes :: CInt -> Ptr CTimeVal -> IO CInt
462#endif
463
464-- | Like 'setFileTimesHiRes' but uses a file descriptor instead of a path.
465-- This operation is not supported on all platforms. On these platforms,
466-- this function will raise an exception.
467--
468-- Note: calls @futimens@ or @futimes@.
469--
470-- @since 2.7.0.0
471setFdTimesHiRes :: Fd -> POSIXTime -> POSIXTime -> IO ()
472#if HAVE_FUTIMENS
473setFdTimesHiRes (Fd fd) atime mtime =
474  withArray [toCTimeSpec atime, toCTimeSpec mtime] $ \times ->
475    throwErrnoIfMinus1_ "setFdTimesHiRes" (c_futimens fd times)
476#elif HAVE_FUTIMES
477setFdTimesHiRes (Fd fd) atime mtime =
478  withArray [toCTimeVal atime, toCTimeVal mtime] $ \times ->
479    throwErrnoIfMinus1_ "setFdTimesHiRes" (c_futimes fd times)
480#else
481setFdTimesHiRes =
482  error "setSymbolicLinkTimesHiRes: not available on this platform"
483#endif
484
485-- | Like 'touchFile' but uses a file descriptor instead of a path.
486-- This operation is not supported on all platforms. On these platforms,
487-- this function will raise an exception.
488--
489-- Note: calls @futimes@.
490--
491-- @since 2.7.0.0
492touchFd :: Fd -> IO ()
493#if HAVE_FUTIMES
494touchFd (Fd fd) =
495  throwErrnoIfMinus1_ "touchFd" (c_futimes fd nullPtr)
496#else
497touchFd =
498  error "touchFd: not available on this platform"
499#endif
500
501-- -----------------------------------------------------------------------------
502-- fchown()
503
504-- | Acts as 'setOwnerAndGroup' but uses a file descriptor instead of a
505-- 'FilePath'.
506--
507-- Note: calls @fchown@.
508setFdOwnerAndGroup :: Fd -> UserID -> GroupID -> IO ()
509setFdOwnerAndGroup (Fd fd) uid gid =
510  throwErrnoIfMinus1_ "setFdOwnerAndGroup" (c_fchown fd uid gid)
511
512foreign import ccall unsafe "fchown"
513  c_fchown :: CInt -> CUid -> CGid -> IO CInt
514
515-- -----------------------------------------------------------------------------
516-- ftruncate()
517
518-- | Acts as 'setFileSize' but uses a file descriptor instead of a 'FilePath'.
519--
520-- Note: calls @ftruncate@.
521setFdSize :: Fd -> FileOffset -> IO ()
522setFdSize (Fd fd) off =
523  throwErrnoIfMinus1_ "setFdSize" (c_ftruncate fd off)
524
525-- -----------------------------------------------------------------------------
526-- pathconf()/fpathconf() support
527
528data PathVar
529  = FileSizeBits                  {- _PC_FILESIZEBITS     -}
530  | LinkLimit                     {- _PC_LINK_MAX         -}
531  | InputLineLimit                {- _PC_MAX_CANON        -}
532  | InputQueueLimit               {- _PC_MAX_INPUT        -}
533  | FileNameLimit                 {- _PC_NAME_MAX         -}
534  | PathNameLimit                 {- _PC_PATH_MAX         -}
535  | PipeBufferLimit               {- _PC_PIPE_BUF         -}
536                                  -- These are described as optional in POSIX:
537                                  {- _PC_ALLOC_SIZE_MIN     -}
538                                  {- _PC_REC_INCR_XFER_SIZE -}
539                                  {- _PC_REC_MAX_XFER_SIZE  -}
540                                  {- _PC_REC_MIN_XFER_SIZE  -}
541                                  {- _PC_REC_XFER_ALIGN     -}
542  | SymbolicLinkLimit             {- _PC_SYMLINK_MAX      -}
543  | SetOwnerAndGroupIsRestricted  {- _PC_CHOWN_RESTRICTED -}
544  | FileNamesAreNotTruncated      {- _PC_NO_TRUNC         -}
545  | VDisableChar                  {- _PC_VDISABLE         -}
546  | AsyncIOAvailable              {- _PC_ASYNC_IO         -}
547  | PrioIOAvailable               {- _PC_PRIO_IO          -}
548  | SyncIOAvailable               {- _PC_SYNC_IO          -}
549
550pathVarConst :: PathVar -> CInt
551pathVarConst v = case v of
552        LinkLimit                       -> (#const _PC_LINK_MAX)
553        InputLineLimit                  -> (#const _PC_MAX_CANON)
554        InputQueueLimit                 -> (#const _PC_MAX_INPUT)
555        FileNameLimit                   -> (#const _PC_NAME_MAX)
556        PathNameLimit                   -> (#const _PC_PATH_MAX)
557        PipeBufferLimit                 -> (#const _PC_PIPE_BUF)
558        SetOwnerAndGroupIsRestricted    -> (#const _PC_CHOWN_RESTRICTED)
559        FileNamesAreNotTruncated        -> (#const _PC_NO_TRUNC)
560        VDisableChar                    -> (#const _PC_VDISABLE)
561
562#ifdef _PC_SYNC_IO
563        SyncIOAvailable         -> (#const _PC_SYNC_IO)
564#else
565        SyncIOAvailable         -> error "_PC_SYNC_IO not available"
566#endif
567
568#ifdef _PC_ASYNC_IO
569        AsyncIOAvailable        -> (#const _PC_ASYNC_IO)
570#else
571        AsyncIOAvailable        -> error "_PC_ASYNC_IO not available"
572#endif
573
574#ifdef _PC_PRIO_IO
575        PrioIOAvailable         -> (#const _PC_PRIO_IO)
576#else
577        PrioIOAvailable         -> error "_PC_PRIO_IO not available"
578#endif
579
580#if _PC_FILESIZEBITS
581        FileSizeBits            -> (#const _PC_FILESIZEBITS)
582#else
583        FileSizeBits            -> error "_PC_FILESIZEBITS not available"
584#endif
585
586#if _PC_SYMLINK_MAX
587        SymbolicLinkLimit       -> (#const _PC_SYMLINK_MAX)
588#else
589        SymbolicLinkLimit       -> error "_PC_SYMLINK_MAX not available"
590#endif
591
592-- | @getFdPathVar var fd@ obtains the dynamic value of the requested
593-- configurable file limit or option associated with the file or directory
594-- attached to the open channel @fd@. For defined file limits, @getFdPathVar@
595-- returns the associated value.  For defined file options, the result of
596-- @getFdPathVar@ is undefined, but not failure.
597--
598-- Note: calls @fpathconf@.
599getFdPathVar :: Fd -> PathVar -> IO Limit
600getFdPathVar (Fd fd) v =
601    throwErrnoIfMinus1 "getFdPathVar" $
602      c_fpathconf fd (pathVarConst v)
603
604foreign import ccall unsafe "fpathconf"
605  c_fpathconf :: CInt -> CInt -> IO CLong
606