aboutsummaryrefslogtreecommitdiffhomepage
path: root/System/Posix/Files
diff options
context:
space:
mode:
authorGravatar Simon Marlow <marlowsd@gmail.com>2011-11-11 16:18:48 +0000
committerGravatar Simon Marlow <marlowsd@gmail.com>2011-11-22 12:36:48 +0000
commit34c7bf896f19b182cf6fa104e057f1df9df1254a (patch)
treeabdb8264ae52c62263fc0fb4b395906a64acb104 /System/Posix/Files
parentc213ae2ec6d9c71266aebc8e5b2326a9625fba7a (diff)
Provide a raw ByteString version of FilePath and environment APIs
The new module System.Posix.ByteString provides exactly the same API as System.Posix, except that: - There is a new type: RawFilePath = ByteString - All functions mentioning FilePath in the System.Posix API use RawFilePath in the System.Posix.ByteString API - RawFilePaths are not subject to Unicode locale encoding and decoding, unlike FilePaths. They are the exact bytes passed to and returned from the underlying POSIX API. - Similarly for functions that deal in environment strings (System.Posix.Env): these use untranslated ByteStrings in System.Posix.Environment - There is a new function System.Posix.ByteString.getArgs :: [ByteString] returning the raw untranslated arguments as passed to exec() when the program was started.
Diffstat (limited to 'System/Posix/Files')
-rw-r--r--System/Posix/Files/ByteString.hsc382
-rw-r--r--System/Posix/Files/Common.hsc408
2 files changed, 790 insertions, 0 deletions
diff --git a/System/Posix/Files/ByteString.hsc b/System/Posix/Files/ByteString.hsc
new file mode 100644
index 0000000..5853ab9
--- /dev/null
+++ b/System/Posix/Files/ByteString.hsc
@@ -0,0 +1,382 @@
+#if __GLASGOW_HASKELL__ >= 701
+{-# LANGUAGE Trustworthy #-}
+#endif
+-----------------------------------------------------------------------------
+-- |
+-- Module : System.Posix.Files.ByteString
+-- Copyright : (c) The University of Glasgow 2002
+-- License : BSD-style (see the file libraries/base/LICENSE)
+--
+-- Maintainer : libraries@haskell.org
+-- Stability : provisional
+-- Portability : non-portable (requires POSIX)
+--
+-- Functions defined by the POSIX standards for manipulating and querying the
+-- file system. Names of underlying POSIX functions are indicated whenever
+-- possible. A more complete documentation of the POSIX functions together
+-- with a more detailed description of different error conditions are usually
+-- available in the system's manual pages or from
+-- <http://www.unix.org/version3/online.html> (free registration required).
+--
+-- When a function that calls an underlying POSIX function fails, the errno
+-- code is converted to an 'IOError' using 'Foreign.C.Error.errnoToIOError'.
+-- For a list of which errno codes may be generated, consult the POSIX
+-- documentation for the underlying function.
+--
+-----------------------------------------------------------------------------
+
+#include "HsUnix.h"
+
+module System.Posix.Files.ByteString (
+ -- * File modes
+ -- FileMode exported by System.Posix.Types
+ unionFileModes, intersectFileModes,
+ nullFileMode,
+ ownerReadMode, ownerWriteMode, ownerExecuteMode, ownerModes,
+ groupReadMode, groupWriteMode, groupExecuteMode, groupModes,
+ otherReadMode, otherWriteMode, otherExecuteMode, otherModes,
+ setUserIDMode, setGroupIDMode,
+ stdFileMode, accessModes,
+ fileTypeModes,
+ blockSpecialMode, characterSpecialMode, namedPipeMode, regularFileMode,
+ directoryMode, symbolicLinkMode, socketMode,
+
+ -- ** Setting file modes
+ setFileMode, setFdMode, setFileCreationMask,
+
+ -- ** Checking file existence and permissions
+ fileAccess, fileExist,
+
+ -- * File status
+ FileStatus,
+ -- ** Obtaining file status
+ getFileStatus, getFdStatus, getSymbolicLinkStatus,
+ -- ** Querying file status
+ deviceID, fileID, fileMode, linkCount, fileOwner, fileGroup,
+ specialDeviceID, fileSize, accessTime, modificationTime,
+ statusChangeTime,
+ isBlockDevice, isCharacterDevice, isNamedPipe, isRegularFile,
+ isDirectory, isSymbolicLink, isSocket,
+
+ -- * Creation
+ createNamedPipe,
+ createDevice,
+
+ -- * Hard links
+ createLink, removeLink,
+
+ -- * Symbolic links
+ createSymbolicLink, readSymbolicLink,
+
+ -- * Renaming files
+ rename,
+
+ -- * Changing file ownership
+ setOwnerAndGroup, setFdOwnerAndGroup,
+#if HAVE_LCHOWN
+ setSymbolicLinkOwnerAndGroup,
+#endif
+
+ -- * Changing file timestamps
+ setFileTimes, touchFile,
+
+ -- * Setting file sizes
+ setFileSize, setFdSize,
+
+ -- * Find system-specific limits for a file
+ PathVar(..), getPathVar, getFdPathVar,
+ ) where
+
+import System.Posix.Types
+import System.Posix.Internals hiding (withFilePath, peekFilePathLen)
+import Foreign
+import Foreign.C hiding (
+ throwErrnoPath,
+ throwErrnoPathIf,
+ throwErrnoPathIf_,
+ throwErrnoPathIfNull,
+ throwErrnoPathIfMinus1,
+ throwErrnoPathIfMinus1_ )
+
+import System.Posix.Files.Common
+import System.Posix.ByteString.FilePath
+
+-- -----------------------------------------------------------------------------
+-- chmod()
+
+-- | @setFileMode path mode@ changes permission of the file given by @path@
+-- to @mode@. This operation may fail with 'throwErrnoPathIfMinus1_' if @path@
+-- doesn't exist or if the effective user ID of the current process is not that
+-- of the file's owner.
+--
+-- Note: calls @chmod@.
+setFileMode :: RawFilePath -> FileMode -> IO ()
+setFileMode name m =
+ withFilePath name $ \s -> do
+ throwErrnoPathIfMinus1_ "setFileMode" name (c_chmod s m)
+
+-- -----------------------------------------------------------------------------
+-- access()
+
+-- | @fileAccess name read write exec@ checks if the file (or other file system
+-- object) @name@ can be accessed for reading, writing and\/or executing. To
+-- check a permission set the corresponding argument to 'True'.
+--
+-- Note: calls @access@.
+fileAccess :: RawFilePath -> Bool -> Bool -> Bool -> IO Bool
+fileAccess name readOK writeOK execOK = access name flags
+ where
+ flags = read_f .|. write_f .|. exec_f
+ read_f = if readOK then (#const R_OK) else 0
+ write_f = if writeOK then (#const W_OK) else 0
+ exec_f = if execOK then (#const X_OK) else 0
+
+-- | Checks for the existence of the file.
+--
+-- Note: calls @access@.
+fileExist :: RawFilePath -> IO Bool
+fileExist name =
+ withFilePath name $ \s -> do
+ r <- c_access s (#const F_OK)
+ if (r == 0)
+ then return True
+ else do err <- getErrno
+ if (err == eNOENT)
+ then return False
+ else throwErrnoPath "fileExist" name
+
+access :: RawFilePath -> CMode -> IO Bool
+access name flags =
+ withFilePath name $ \s -> do
+ r <- c_access s (fromIntegral flags)
+ if (r == 0)
+ then return True
+ else do err <- getErrno
+ if (err == eACCES)
+ then return False
+ else throwErrnoPath "fileAccess" name
+
+
+-- | @getFileStatus path@ calls gets the @FileStatus@ information (user ID,
+-- size, access times, etc.) for the file @path@.
+--
+-- Note: calls @stat@.
+getFileStatus :: RawFilePath -> IO FileStatus
+getFileStatus path = do
+ fp <- mallocForeignPtrBytes (#const sizeof(struct stat))
+ withForeignPtr fp $ \p ->
+ withFilePath path $ \s ->
+ throwErrnoPathIfMinus1_ "getFileStatus" path (c_stat s p)
+ return (FileStatus fp)
+
+-- | Acts as 'getFileStatus' except when the 'RawFilePath' refers to a symbolic
+-- link. In that case the @FileStatus@ information of the symbolic link itself
+-- is returned instead of that of the file it points to.
+--
+-- Note: calls @lstat@.
+getSymbolicLinkStatus :: RawFilePath -> IO FileStatus
+getSymbolicLinkStatus path = do
+ fp <- mallocForeignPtrBytes (#const sizeof(struct stat))
+ withForeignPtr fp $ \p ->
+ withFilePath path $ \s ->
+ throwErrnoPathIfMinus1_ "getSymbolicLinkStatus" path (c_lstat s p)
+ return (FileStatus fp)
+
+foreign import ccall unsafe "__hsunix_lstat"
+ c_lstat :: CString -> Ptr CStat -> IO CInt
+
+-- | @createNamedPipe fifo mode@
+-- creates a new named pipe, @fifo@, with permissions based on
+-- @mode@. May fail with 'throwErrnoPathIfMinus1_' if a file named @name@
+-- already exists or if the effective user ID of the current process doesn't
+-- have permission to create the pipe.
+--
+-- Note: calls @mkfifo@.
+createNamedPipe :: RawFilePath -> FileMode -> IO ()
+createNamedPipe name mode = do
+ withFilePath name $ \s ->
+ throwErrnoPathIfMinus1_ "createNamedPipe" name (c_mkfifo s mode)
+
+-- | @createDevice path mode dev@ creates either a regular or a special file
+-- depending on the value of @mode@ (and @dev@). @mode@ will normally be either
+-- 'blockSpecialMode' or 'characterSpecialMode'. May fail with
+-- 'throwErrnoPathIfMinus1_' if a file named @name@ already exists or if the
+-- effective user ID of the current process doesn't have permission to create
+-- the file.
+--
+-- Note: calls @mknod@.
+createDevice :: RawFilePath -> FileMode -> DeviceID -> IO ()
+createDevice path mode dev =
+ withFilePath path $ \s ->
+ throwErrnoPathIfMinus1_ "createDevice" path (c_mknod s mode dev)
+
+foreign import ccall unsafe "__hsunix_mknod"
+ c_mknod :: CString -> CMode -> CDev -> IO CInt
+
+-- -----------------------------------------------------------------------------
+-- Hard links
+
+-- | @createLink old new@ creates a new path, @new@, linked to an existing file,
+-- @old@.
+--
+-- Note: calls @link@.
+createLink :: RawFilePath -> RawFilePath -> IO ()
+createLink name1 name2 =
+ withFilePath name1 $ \s1 ->
+ withFilePath name2 $ \s2 ->
+ throwErrnoPathIfMinus1_ "createLink" name1 (c_link s1 s2)
+
+-- | @removeLink path@ removes the link named @path@.
+--
+-- Note: calls @unlink@.
+removeLink :: RawFilePath -> IO ()
+removeLink name =
+ withFilePath name $ \s ->
+ throwErrnoPathIfMinus1_ "removeLink" name (c_unlink s)
+
+-- -----------------------------------------------------------------------------
+-- Symbolic Links
+
+-- | @createSymbolicLink file1 file2@ creates a symbolic link named @file2@
+-- which points to the file @file1@.
+--
+-- Symbolic links are interpreted at run-time as if the contents of the link
+-- had been substituted into the path being followed to find a file or directory.
+--
+-- Note: calls @symlink@.
+createSymbolicLink :: RawFilePath -> RawFilePath -> IO ()
+createSymbolicLink file1 file2 =
+ withFilePath file1 $ \s1 ->
+ withFilePath file2 $ \s2 ->
+ throwErrnoPathIfMinus1_ "createSymbolicLink" file1 (c_symlink s1 s2)
+
+foreign import ccall unsafe "symlink"
+ c_symlink :: CString -> CString -> IO CInt
+
+-- ToDo: should really use SYMLINK_MAX, but not everyone supports it yet,
+-- and it seems that the intention is that SYMLINK_MAX is no larger than
+-- PATH_MAX.
+#if !defined(PATH_MAX)
+-- PATH_MAX is not defined on systems with unlimited path length.
+-- Ugly. Fix this.
+#define PATH_MAX 4096
+#endif
+
+-- | Reads the @RawFilePath@ pointed to by the symbolic link and returns it.
+--
+-- Note: calls @readlink@.
+readSymbolicLink :: RawFilePath -> IO RawFilePath
+readSymbolicLink file =
+ allocaArray0 (#const PATH_MAX) $ \buf -> do
+ withFilePath file $ \s -> do
+ len <- throwErrnoPathIfMinus1 "readSymbolicLink" file $
+ c_readlink s buf (#const PATH_MAX)
+ peekFilePathLen (buf,fromIntegral len)
+
+foreign import ccall unsafe "readlink"
+ c_readlink :: CString -> CString -> CSize -> IO CInt
+
+-- -----------------------------------------------------------------------------
+-- Renaming files
+
+-- | @rename old new@ renames a file or directory from @old@ to @new@.
+--
+-- Note: calls @rename@.
+rename :: RawFilePath -> RawFilePath -> IO ()
+rename name1 name2 =
+ withFilePath name1 $ \s1 ->
+ withFilePath name2 $ \s2 ->
+ throwErrnoPathIfMinus1_ "rename" name1 (c_rename s1 s2)
+
+foreign import ccall unsafe "rename"
+ c_rename :: CString -> CString -> IO CInt
+
+-- -----------------------------------------------------------------------------
+-- chown()
+
+-- | @setOwnerAndGroup path uid gid@ changes the owner and group of @path@ to
+-- @uid@ and @gid@, respectively.
+--
+-- If @uid@ or @gid@ is specified as -1, then that ID is not changed.
+--
+-- Note: calls @chown@.
+setOwnerAndGroup :: RawFilePath -> UserID -> GroupID -> IO ()
+setOwnerAndGroup name uid gid = do
+ withFilePath name $ \s ->
+ throwErrnoPathIfMinus1_ "setOwnerAndGroup" name (c_chown s uid gid)
+
+foreign import ccall unsafe "chown"
+ c_chown :: CString -> CUid -> CGid -> IO CInt
+
+#if HAVE_LCHOWN
+-- | Acts as 'setOwnerAndGroup' but does not follow symlinks (and thus
+-- changes permissions on the link itself).
+--
+-- Note: calls @lchown@.
+setSymbolicLinkOwnerAndGroup :: RawFilePath -> UserID -> GroupID -> IO ()
+setSymbolicLinkOwnerAndGroup name uid gid = do
+ withFilePath name $ \s ->
+ throwErrnoPathIfMinus1_ "setSymbolicLinkOwnerAndGroup" name
+ (c_lchown s uid gid)
+
+foreign import ccall unsafe "lchown"
+ c_lchown :: CString -> CUid -> CGid -> IO CInt
+#endif
+
+-- -----------------------------------------------------------------------------
+-- utime()
+
+-- | @setFileTimes path atime mtime@ sets the access and modification times
+-- associated with file @path@ to @atime@ and @mtime@, respectively.
+--
+-- Note: calls @utime@.
+setFileTimes :: RawFilePath -> EpochTime -> EpochTime -> IO ()
+setFileTimes name atime mtime = do
+ withFilePath name $ \s ->
+ allocaBytes (#const sizeof(struct utimbuf)) $ \p -> do
+ (#poke struct utimbuf, actime) p atime
+ (#poke struct utimbuf, modtime) p mtime
+ throwErrnoPathIfMinus1_ "setFileTimes" name (c_utime s p)
+
+-- | @touchFile path@ sets the access and modification times associated with
+-- file @path@ to the current time.
+--
+-- Note: calls @utime@.
+touchFile :: RawFilePath -> IO ()
+touchFile name = do
+ withFilePath name $ \s ->
+ throwErrnoPathIfMinus1_ "touchFile" name (c_utime s nullPtr)
+
+-- -----------------------------------------------------------------------------
+-- Setting file sizes
+
+-- | Truncates the file down to the specified length. If the file was larger
+-- than the given length before this operation was performed the extra is lost.
+--
+-- Note: calls @truncate@.
+setFileSize :: RawFilePath -> FileOffset -> IO ()
+setFileSize file off =
+ withFilePath file $ \s ->
+ throwErrnoPathIfMinus1_ "setFileSize" file (c_truncate s off)
+
+foreign import ccall unsafe "truncate"
+ c_truncate :: CString -> COff -> IO CInt
+
+-- -----------------------------------------------------------------------------
+-- pathconf()/fpathconf() support
+
+-- | @getPathVar var path@ obtains the dynamic value of the requested
+-- configurable file limit or option associated with file or directory @path@.
+-- For defined file limits, @getPathVar@ returns the associated
+-- value. For defined file options, the result of @getPathVar@
+-- is undefined, but not failure.
+--
+-- Note: calls @pathconf@.
+getPathVar :: RawFilePath -> PathVar -> IO Limit
+getPathVar name v = do
+ withFilePath name $ \ nameP ->
+ throwErrnoPathIfMinus1 "getPathVar" name $
+ c_pathconf nameP (pathVarConst v)
+
+foreign import ccall unsafe "pathconf"
+ c_pathconf :: CString -> CInt -> IO CLong
diff --git a/System/Posix/Files/Common.hsc b/System/Posix/Files/Common.hsc
new file mode 100644
index 0000000..2894244
--- /dev/null
+++ b/System/Posix/Files/Common.hsc
@@ -0,0 +1,408 @@
+{-# LANGUAGE ForeignFunctionInterface #-}
+{-# OPTIONS_GHC -fno-warn-unused-imports #-}
+#if __GLASGOW_HASKELL__ >= 701
+{-# LANGUAGE Trustworthy #-}
+#endif
+-----------------------------------------------------------------------------
+-- |
+-- Module : System.Posix.Files.Common
+-- Copyright : (c) The University of Glasgow 2002
+-- License : BSD-style (see the file libraries/base/LICENSE)
+--
+-- Maintainer : libraries@haskell.org
+-- Stability : provisional
+-- Portability : non-portable (requires POSIX)
+--
+-- Functions defined by the POSIX standards for manipulating and querying the
+-- file system. Names of underlying POSIX functions are indicated whenever
+-- possible. A more complete documentation of the POSIX functions together
+-- with a more detailed description of different error conditions are usually
+-- available in the system's manual pages or from
+-- <http://www.unix.org/version3/online.html> (free registration required).
+--
+-- When a function that calls an underlying POSIX function fails, the errno
+-- code is converted to an 'IOError' using 'Foreign.C.Error.errnoToIOError'.
+-- For a list of which errno codes may be generated, consult the POSIX
+-- documentation for the underlying function.
+--
+-----------------------------------------------------------------------------
+
+#include "HsUnix.h"
+
+module System.Posix.Files.Common (
+ -- * File modes
+ -- FileMode exported by System.Posix.Types
+ unionFileModes, intersectFileModes,
+ nullFileMode,
+ ownerReadMode, ownerWriteMode, ownerExecuteMode, ownerModes,
+ groupReadMode, groupWriteMode, groupExecuteMode, groupModes,
+ otherReadMode, otherWriteMode, otherExecuteMode, otherModes,
+ setUserIDMode, setGroupIDMode,
+ stdFileMode, accessModes,
+ fileTypeModes,
+ blockSpecialMode, characterSpecialMode, namedPipeMode, regularFileMode,
+ directoryMode, symbolicLinkMode, socketMode,
+
+ -- ** Setting file modes
+ setFdMode, setFileCreationMask,
+
+ -- * File status
+ FileStatus(..),
+ -- ** Obtaining file status
+ getFdStatus,
+ -- ** Querying file status
+ deviceID, fileID, fileMode, linkCount, fileOwner, fileGroup,
+ specialDeviceID, fileSize, accessTime, modificationTime,
+ statusChangeTime,
+ isBlockDevice, isCharacterDevice, isNamedPipe, isRegularFile,
+ isDirectory, isSymbolicLink, isSocket,
+
+ -- * Setting file sizes
+ setFdSize,
+
+ -- * Changing file ownership
+ setFdOwnerAndGroup,
+
+ -- * Find system-specific limits for a file
+ PathVar(..), getFdPathVar, pathVarConst,
+ ) where
+
+import System.Posix.Error
+import System.Posix.Types
+import System.IO.Unsafe
+import Data.Bits
+import System.Posix.Internals
+import Foreign hiding (unsafePerformIO)
+import Foreign.C
+
+-- -----------------------------------------------------------------------------
+-- POSIX file modes
+
+-- The abstract type 'FileMode', constants and operators for
+-- manipulating the file modes defined by POSIX.
+
+-- | No permissions.
+nullFileMode :: FileMode
+nullFileMode = 0
+
+-- | Owner has read permission.
+ownerReadMode :: FileMode
+ownerReadMode = (#const S_IRUSR)
+
+-- | Owner has write permission.
+ownerWriteMode :: FileMode
+ownerWriteMode = (#const S_IWUSR)
+
+-- | Owner has execute permission.
+ownerExecuteMode :: FileMode
+ownerExecuteMode = (#const S_IXUSR)
+
+-- | Group has read permission.
+groupReadMode :: FileMode
+groupReadMode = (#const S_IRGRP)
+
+-- | Group has write permission.
+groupWriteMode :: FileMode
+groupWriteMode = (#const S_IWGRP)
+
+-- | Group has execute permission.
+groupExecuteMode :: FileMode
+groupExecuteMode = (#const S_IXGRP)
+
+-- | Others have read permission.
+otherReadMode :: FileMode
+otherReadMode = (#const S_IROTH)
+
+-- | Others have write permission.
+otherWriteMode :: FileMode
+otherWriteMode = (#const S_IWOTH)
+
+-- | Others have execute permission.
+otherExecuteMode :: FileMode
+otherExecuteMode = (#const S_IXOTH)
+
+-- | Set user ID on execution.
+setUserIDMode :: FileMode
+setUserIDMode = (#const S_ISUID)
+
+-- | Set group ID on execution.
+setGroupIDMode :: FileMode
+setGroupIDMode = (#const S_ISGID)
+
+-- | Owner, group and others have read and write permission.
+stdFileMode :: FileMode
+stdFileMode = ownerReadMode .|. ownerWriteMode .|.
+ groupReadMode .|. groupWriteMode .|.
+ otherReadMode .|. otherWriteMode
+
+-- | Owner has read, write and execute permission.
+ownerModes :: FileMode
+ownerModes = (#const S_IRWXU)
+
+-- | Group has read, write and execute permission.
+groupModes :: FileMode
+groupModes = (#const S_IRWXG)
+
+-- | Others have read, write and execute permission.
+otherModes :: FileMode
+otherModes = (#const S_IRWXO)
+
+-- | Owner, group and others have read, write and execute permission.
+accessModes :: FileMode
+accessModes = ownerModes .|. groupModes .|. otherModes
+
+-- | Combines the two file modes into one that contains modes that appear in
+-- either.
+unionFileModes :: FileMode -> FileMode -> FileMode
+unionFileModes m1 m2 = m1 .|. m2
+
+-- | Combines two file modes into one that only contains modes that appear in
+-- both.
+intersectFileModes :: FileMode -> FileMode -> FileMode
+intersectFileModes m1 m2 = m1 .&. m2
+
+fileTypeModes :: FileMode
+fileTypeModes = (#const S_IFMT)
+
+blockSpecialMode :: FileMode
+blockSpecialMode = (#const S_IFBLK)
+
+characterSpecialMode :: FileMode
+characterSpecialMode = (#const S_IFCHR)
+
+namedPipeMode :: FileMode
+namedPipeMode = (#const S_IFIFO)
+
+regularFileMode :: FileMode
+regularFileMode = (#const S_IFREG)
+
+directoryMode :: FileMode
+directoryMode = (#const S_IFDIR)
+
+symbolicLinkMode :: FileMode
+symbolicLinkMode = (#const S_IFLNK)
+
+socketMode :: FileMode
+socketMode = (#const S_IFSOCK)
+
+-- | @setFdMode fd mode@ acts like 'setFileMode' but uses a file descriptor
+-- @fd@ instead of a 'FilePath'.
+--
+-- Note: calls @fchmod@.
+setFdMode :: Fd -> FileMode -> IO ()
+setFdMode (Fd fd) m =
+ throwErrnoIfMinus1_ "setFdMode" (c_fchmod fd m)
+
+foreign import ccall unsafe "fchmod"
+ c_fchmod :: CInt -> CMode -> IO CInt
+
+-- | @setFileCreationMask mode@ sets the file mode creation mask to @mode@.
+-- Modes set by this operation are subtracted from files and directories upon
+-- creation. The previous file creation mask is returned.
+--
+-- Note: calls @umask@.
+setFileCreationMask :: FileMode -> IO FileMode
+setFileCreationMask mask = c_umask mask
+
+-- -----------------------------------------------------------------------------
+-- stat() support
+
+-- | POSIX defines operations to get information, such as owner, permissions,
+-- size and access times, about a file. This information is represented by the
+-- 'FileStatus' type.
+--
+-- Note: see @chmod@.
+newtype FileStatus = FileStatus (ForeignPtr CStat)
+
+-- | ID of the device on which this file resides.
+deviceID :: FileStatus -> DeviceID
+-- | inode number
+fileID :: FileStatus -> FileID
+-- | File mode (such as permissions).
+fileMode :: FileStatus -> FileMode
+-- | Number of hard links to this file.
+linkCount :: FileStatus -> LinkCount
+-- | ID of owner.
+fileOwner :: FileStatus -> UserID
+-- | ID of group.
+fileGroup :: FileStatus -> GroupID
+-- | Describes the device that this file represents.
+specialDeviceID :: FileStatus -> DeviceID
+-- | Size of the file in bytes. If this file is a symbolic link the size is
+-- the length of the pathname it contains.
+fileSize :: FileStatus -> FileOffset
+-- | Time of last access.
+accessTime :: FileStatus -> EpochTime
+-- | Time of last modification.
+modificationTime :: FileStatus -> EpochTime
+-- | Time of last status change (i.e. owner, group, link count, mode, etc.).
+statusChangeTime :: FileStatus -> EpochTime
+
+deviceID (FileStatus stat) =
+ unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_dev)
+fileID (FileStatus stat) =
+ unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_ino)
+fileMode (FileStatus stat) =
+ unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_mode)
+linkCount (FileStatus stat) =
+ unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_nlink)
+fileOwner (FileStatus stat) =
+ unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_uid)
+fileGroup (FileStatus stat) =
+ unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_gid)
+specialDeviceID (FileStatus stat) =
+ unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_rdev)
+fileSize (FileStatus stat) =
+ unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_size)
+accessTime (FileStatus stat) =
+ unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_atime)
+modificationTime (FileStatus stat) =
+ unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_mtime)
+statusChangeTime (FileStatus stat) =
+ unsafePerformIO $ withForeignPtr stat $ (#peek struct stat, st_ctime)
+
+-- | Checks if this file is a block device.
+isBlockDevice :: FileStatus -> Bool
+-- | Checks if this file is a character device.
+isCharacterDevice :: FileStatus -> Bool
+-- | Checks if this file is a named pipe device.
+isNamedPipe :: FileStatus -> Bool
+-- | Checks if this file is a regular file device.
+isRegularFile :: FileStatus -> Bool
+-- | Checks if this file is a directory device.
+isDirectory :: FileStatus -> Bool
+-- | Checks if this file is a symbolic link device.
+isSymbolicLink :: FileStatus -> Bool
+-- | Checks if this file is a socket device.
+isSocket :: FileStatus -> Bool
+
+isBlockDevice stat =
+ (fileMode stat `intersectFileModes` fileTypeModes) == blockSpecialMode
+isCharacterDevice stat =
+ (fileMode stat `intersectFileModes` fileTypeModes) == characterSpecialMode
+isNamedPipe stat =
+ (fileMode stat `intersectFileModes` fileTypeModes) == namedPipeMode
+isRegularFile stat =
+ (fileMode stat `intersectFileModes` fileTypeModes) == regularFileMode
+isDirectory stat =
+ (fileMode stat `intersectFileModes` fileTypeModes) == directoryMode
+isSymbolicLink stat =
+ (fileMode stat `intersectFileModes` fileTypeModes) == symbolicLinkMode
+isSocket stat =
+ (fileMode stat `intersectFileModes` fileTypeModes) == socketMode
+
+-- | @getFdStatus fd@ acts as 'getFileStatus' but uses a file descriptor @fd@.
+--
+-- Note: calls @fstat@.
+getFdStatus :: Fd -> IO FileStatus
+getFdStatus (Fd fd) = do
+ fp <- mallocForeignPtrBytes (#const sizeof(struct stat))
+ withForeignPtr fp $ \p ->
+ throwErrnoIfMinus1_ "getFdStatus" (c_fstat fd p)
+ return (FileStatus fp)
+
+-- -----------------------------------------------------------------------------
+-- fchown()
+
+-- | Acts as 'setOwnerAndGroup' but uses a file descriptor instead of a
+-- 'FilePath'.
+--
+-- Note: calls @fchown@.
+setFdOwnerAndGroup :: Fd -> UserID -> GroupID -> IO ()
+setFdOwnerAndGroup (Fd fd) uid gid =
+ throwErrnoIfMinus1_ "setFdOwnerAndGroup" (c_fchown fd uid gid)
+
+foreign import ccall unsafe "fchown"
+ c_fchown :: CInt -> CUid -> CGid -> IO CInt
+
+-- -----------------------------------------------------------------------------
+-- ftruncate()
+
+-- | Acts as 'setFileSize' but uses a file descriptor instead of a 'FilePath'.
+--
+-- Note: calls @ftruncate@.
+setFdSize :: Fd -> FileOffset -> IO ()
+setFdSize (Fd fd) off =
+ throwErrnoIfMinus1_ "setFdSize" (c_ftruncate fd off)
+
+-- -----------------------------------------------------------------------------
+-- pathconf()/fpathconf() support
+
+data PathVar
+ = FileSizeBits {- _PC_FILESIZEBITS -}
+ | LinkLimit {- _PC_LINK_MAX -}
+ | InputLineLimit {- _PC_MAX_CANON -}
+ | InputQueueLimit {- _PC_MAX_INPUT -}
+ | FileNameLimit {- _PC_NAME_MAX -}
+ | PathNameLimit {- _PC_PATH_MAX -}
+ | PipeBufferLimit {- _PC_PIPE_BUF -}
+ -- These are described as optional in POSIX:
+ {- _PC_ALLOC_SIZE_MIN -}
+ {- _PC_REC_INCR_XFER_SIZE -}
+ {- _PC_REC_MAX_XFER_SIZE -}
+ {- _PC_REC_MIN_XFER_SIZE -}
+ {- _PC_REC_XFER_ALIGN -}
+ | SymbolicLinkLimit {- _PC_SYMLINK_MAX -}
+ | SetOwnerAndGroupIsRestricted {- _PC_CHOWN_RESTRICTED -}
+ | FileNamesAreNotTruncated {- _PC_NO_TRUNC -}
+ | VDisableChar {- _PC_VDISABLE -}
+ | AsyncIOAvailable {- _PC_ASYNC_IO -}
+ | PrioIOAvailable {- _PC_PRIO_IO -}
+ | SyncIOAvailable {- _PC_SYNC_IO -}
+
+pathVarConst :: PathVar -> CInt
+pathVarConst v = case v of
+ LinkLimit -> (#const _PC_LINK_MAX)
+ InputLineLimit -> (#const _PC_MAX_CANON)
+ InputQueueLimit -> (#const _PC_MAX_INPUT)
+ FileNameLimit -> (#const _PC_NAME_MAX)
+ PathNameLimit -> (#const _PC_PATH_MAX)
+ PipeBufferLimit -> (#const _PC_PIPE_BUF)
+ SetOwnerAndGroupIsRestricted -> (#const _PC_CHOWN_RESTRICTED)
+ FileNamesAreNotTruncated -> (#const _PC_NO_TRUNC)
+ VDisableChar -> (#const _PC_VDISABLE)
+
+#ifdef _PC_SYNC_IO
+ SyncIOAvailable -> (#const _PC_SYNC_IO)
+#else
+ SyncIOAvailable -> error "_PC_SYNC_IO not available"
+#endif
+
+#ifdef _PC_ASYNC_IO
+ AsyncIOAvailable -> (#const _PC_ASYNC_IO)
+#else
+ AsyncIOAvailable -> error "_PC_ASYNC_IO not available"
+#endif
+
+#ifdef _PC_PRIO_IO
+ PrioIOAvailable -> (#const _PC_PRIO_IO)
+#else
+ PrioIOAvailable -> error "_PC_PRIO_IO not available"
+#endif
+
+#if _PC_FILESIZEBITS
+ FileSizeBits -> (#const _PC_FILESIZEBITS)
+#else
+ FileSizeBits -> error "_PC_FILESIZEBITS not available"
+#endif
+
+#if _PC_SYMLINK_MAX
+ SymbolicLinkLimit -> (#const _PC_SYMLINK_MAX)
+#else
+ SymbolicLinkLimit -> error "_PC_SYMLINK_MAX not available"
+#endif
+
+-- | @getFdPathVar var fd@ obtains the dynamic value of the requested
+-- configurable file limit or option associated with the file or directory
+-- attached to the open channel @fd@. For defined file limits, @getFdPathVar@
+-- returns the associated value. For defined file options, the result of
+-- @getFdPathVar@ is undefined, but not failure.
+--
+-- Note: calls @fpathconf@.
+getFdPathVar :: Fd -> PathVar -> IO Limit
+getFdPathVar (Fd fd) v =
+ throwErrnoIfMinus1 "getFdPathVar" $
+ c_fpathconf fd (pathVarConst v)
+
+foreign import ccall unsafe "fpathconf"
+ c_fpathconf :: CInt -> CInt -> IO CLong