{-# LINE 1 "System/Posix/Files/PosixString.hsc" #-}{-# LANGUAGE CApiFFI #-}{-# LANGUAGE PatternSynonyms #-}------------------------------------------------------------------------------- |-- Module : System.Posix.Files.PosixString-- 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.-------------------------------------------------------------------------------moduleSystem.Posix.Files.PosixString(-- * File modes-- FileMode exported by System.Posix.TypesunionFileModes ,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 modessetFileMode ,setFdMode ,setFileCreationMask ,-- ** Checking file existence and permissionsfileAccess ,fileExist ,-- * File statusFileStatus ,-- ** Obtaining file statusgetFileStatus ,getFdStatus ,getSymbolicLinkStatus ,-- ** Querying file statusdeviceID ,fileID ,fileMode ,linkCount ,fileOwner ,fileGroup ,specialDeviceID ,fileSize ,accessTime ,modificationTime ,statusChangeTime ,accessTimeHiRes ,modificationTimeHiRes ,statusChangeTimeHiRes ,isBlockDevice ,isCharacterDevice ,isNamedPipe ,isRegularFile ,isDirectory ,isSymbolicLink ,isSocket ,-- * Extended file statusExtendedFileStatus (..),CAttributes (..),haveStatx ,-- ** Obtaining extended file statusgetExtendedFileStatus ,-- ** FlagsStatxFlags (..),defaultStatxFlags ,patternEmptyPath ,patternNoAutoMount ,patternSymlinkNoFollow ,patternSyncAsStat ,patternForceSync ,patternDontSync ,-- ** MaskStatxMask (..),defaultStatxMask ,patternStatxType ,patternStatxMode ,patternStatxNlink ,patternStatxUid ,patternStatxGid ,patternStatxAtime ,patternStatxMtime ,patternStatxCtime ,patternStatxIno ,patternStatxSize ,patternStatxBlocks ,patternStatxBasicStats ,patternStatxBtime ,patternStatxMntId ,patternStatxAll ,-- ** Querying extended file statusfileBlockSizeX ,linkCountX ,fileOwnerX ,fileGroupX ,fileModeX ,fileIDX ,fileSizeX ,fileBlocksX ,accessTimeHiResX ,creationTimeHiResX ,statusChangeTimeHiResX ,modificationTimeHiResX ,deviceIDX ,specialDeviceIDX ,mountIDX ,fileCompressedX ,fileImmutableX ,fileAppendX ,fileNoDumpX ,fileEncryptedX ,fileVerityX ,fileDaxX ,isBlockDeviceX ,isCharacterDeviceX ,isNamedPipeX ,isRegularFileX ,isDirectoryX ,isSymbolicLinkX ,isSocketX ,-- * CreationcreateNamedPipe ,createDevice ,-- * Hard linkscreateLink ,removeLink ,-- * Symbolic linkscreateSymbolicLink ,readSymbolicLink ,-- * Renaming filesrename ,-- * Changing file ownershipsetOwnerAndGroup ,setFdOwnerAndGroup ,{-# LINE 142 "System/Posix/Files/PosixString.hsc" #-}setSymbolicLinkOwnerAndGroup,{-# LINE 144 "System/Posix/Files/PosixString.hsc" #-}-- * Changing file timestampssetFileTimes ,setFileTimesHiRes ,setSymbolicLinkTimesHiRes ,touchFile ,touchFd ,touchSymbolicLink ,-- * Setting file sizessetFileSize ,setFdSize ,-- * Find system-specific limits for a filePathVar (..),getPathVar ,getFdPathVar ,)whereimportSystem.Posix.TypesimportSystem.Posix.Internalshiding(withFilePath,peekFilePathLen)importqualifiedSystem.Posix.Files.Common asCommonimportForeignimportForeign.Chiding(throwErrnoPath,throwErrnoPathIf,throwErrnoPathIf_,throwErrnoPathIfNull,throwErrnoPathIfMinus1,throwErrnoPathIfMinus1_)importSystem.OsPath.TypesimportSystem.Posix.Files hiding(getFileStatus ,getExtendedFileStatus ,getSymbolicLinkStatus ,createNamedPipe ,createDevice ,createLink ,removeLink ,createSymbolicLink ,readSymbolicLink ,rename ,setOwnerAndGroup ,setSymbolicLinkOwnerAndGroup ,setFileTimes ,setSymbolicLinkTimesHiRes ,touchFile ,touchSymbolicLink ,setFileSize ,getPathVar ,setFileMode ,fileAccess ,fileExist ,setFdTimesHiRes ,setFileTimesHiRes )importSystem.Posix.Files.Common (getExtendedFileStatus_ )importSystem.Posix.PosixPath.FilePath importData.Time.Clock.POSIX(POSIXTime){-# LINE 180 "System/Posix/Files/PosixString.hsc" #-}-- ------------------------------------------------------------------------------- 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 ::PosixPath->FileMode->IO()setFileMode :: PosixPath -> CMode -> IO ()
setFileMode PosixPath
name CMode
m =PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->doString -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"setFileMode"PosixPath
name (CString -> CMode -> IO CInt
c_chmodCString
s CMode
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 ::PosixPath->Bool->Bool->Bool->IOBoolfileAccess :: PosixPath -> Bool -> Bool -> Bool -> IO Bool
fileAccess PosixPath
name Bool
readOK Bool
writeOK Bool
execOK =PosixPath -> CMode -> IO Bool
access PosixPath
name CMode
flags whereflags :: CMode
flags =CMode
read_f CMode -> CMode -> CMode
forall a. Bits a => a -> a -> a
.|.CMode
write_f CMode -> CMode -> CMode
forall a. Bits a => a -> a -> a
.|.CMode
exec_f read_f :: CMode
read_f =ifBool
readOK then(CMode
4)elseCMode
0{-# LINE 209 "System/Posix/Files/PosixString.hsc" #-}write_f=ifwriteOKthen(2)else0{-# LINE 210 "System/Posix/Files/PosixString.hsc" #-}exec_f=ifexecOKthen(1)else0{-# LINE 211 "System/Posix/Files/PosixString.hsc" #-}-- | Checks for the existence of the file.---- Note: calls @access@.fileExist ::PosixPath->IOBoolfileExist :: PosixPath -> IO Bool
fileExist PosixPath
name =PosixPath -> (CString -> IO Bool) -> IO Bool
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name ((CString -> IO Bool) -> IO Bool)
-> (CString -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$\CString
s ->doCInt
r <-CString -> CInt -> IO CInt
c_accessCString
s (CInt
0){-# LINE 219 "System/Posix/Files/PosixString.hsc" #-}if(r==0)thenreturnTrueelsedoerr<-getErrnoif(err==eNOENT)thenreturnFalseelsethrowErrnoPath"fileExist"nameaccess ::PosixPath->CMode->IOBoolaccess :: PosixPath -> CMode -> IO Bool
access PosixPath
name CMode
flags =PosixPath -> (CString -> IO Bool) -> IO Bool
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name ((CString -> IO Bool) -> IO Bool)
-> (CString -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$\CString
s ->doCInt
r <-CString -> CInt -> IO CInt
c_accessCString
s (CMode -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegralCMode
flags )if(CInt
r CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
==CInt
0)thenBool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returnBool
TrueelsedoErrno
err <-IO Errno
getErrnoif(Errno
err Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
==Errno
eACCESBool -> Bool -> Bool
||Errno
err Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
==Errno
eROFSBool -> Bool -> Bool
||Errno
err Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
==Errno
eTXTBSYBool -> Bool -> Bool
||Errno
err Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
==Errno
ePERM)thenBool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returnBool
FalseelseString -> PosixPath -> IO Bool
forall a. String -> PosixPath -> IO a
throwErrnoPath String
"fileAccess"PosixPath
name -- | @getFileStatus path@ calls gets the @FileStatus@ information (user ID,-- size, access times, etc.) for the file @path@.---- Note: calls @stat@.getFileStatus ::PosixPath->IOFileStatus getFileStatus :: PosixPath -> IO FileStatus
getFileStatus PosixPath
path =doForeignPtr CStat
fp <-Int -> IO (ForeignPtr CStat)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes(Int
144){-# LINE 246 "System/Posix/Files/PosixString.hsc" #-}withForeignPtrfp$\p->withFilePathpath$\s->throwErrnoPathIfMinus1Retry_"getFileStatus"path(c_statsp)FileStatus -> IO FileStatus
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return(ForeignPtr CStat -> FileStatus
Common.FileStatus ForeignPtr CStat
fp )-- | Gets extended file status information.---- The target file to open is identified in one of the following ways:---- - If @pathname@ begins with a slash, then it is an absolute pathname that identifies the target file. In this case, @dirfd@ is ignored-- - If @pathname@ is a string that begins with a character other than a slash and @dirfd@ is a file descriptor that refers to a-- directory, then pathname is a relative pathname that is interpreted relative to the directory referred to by dirfd.-- (See @openat(2)@ for an explanation of why this is useful.)-- - If @pathname@ is an empty string and the 'EmptyPath' flag is specified in flags (see below), then the target file is-- the one referred to by the file descriptor @dirfd@.---- Note: calls @statx@.getExtendedFileStatus ::MaybeFd-- ^ Optional directory file descriptor (@dirfd@)->PosixPath-- ^ @pathname@ to open->StatxFlags -- ^ flags->StatxMask -- ^ mask->IOExtendedFileStatus getExtendedFileStatus :: Maybe Fd
-> PosixPath -> StatxFlags -> StatxMask -> IO ExtendedFileStatus
getExtendedFileStatus Maybe Fd
mfd PosixPath
path StatxFlags
flags StatxMask
masks =PosixPath
-> (CString -> IO ExtendedFileStatus) -> IO ExtendedFileStatus
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
path ((CString -> IO ExtendedFileStatus) -> IO ExtendedFileStatus)
-> (CString -> IO ExtendedFileStatus) -> IO ExtendedFileStatus
forall a b. (a -> b) -> a -> b
$\CString
s ->Maybe Fd
-> CString -> StatxFlags -> StatxMask -> IO ExtendedFileStatus
getExtendedFileStatus_ Maybe Fd
mfd CString
s StatxFlags
flags StatxMask
masks -- | Acts as 'getFileStatus' except when the 'PosixPath' 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 ::PosixPath->IOFileStatus getSymbolicLinkStatus :: PosixPath -> IO FileStatus
getSymbolicLinkStatus PosixPath
path =doForeignPtr CStat
fp <-Int -> IO (ForeignPtr CStat)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes(Int
144){-# LINE 278 "System/Posix/Files/PosixString.hsc" #-}withForeignPtrfp$\p->withFilePathpath$\s->throwErrnoPathIfMinus1_"getSymbolicLinkStatus"path(c_lstatsp)FileStatus -> IO FileStatus
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return(ForeignPtr CStat -> FileStatus
Common.FileStatus ForeignPtr CStat
fp )foreignimportcapiunsafe"HsUnix.h lstat"c_lstat ::CString->PtrCStat->IOCInt-- | @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 ::PosixPath->FileMode->IO()createNamedPipe :: PosixPath -> CMode -> IO ()
createNamedPipe PosixPath
name CMode
mode =doPosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->String -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"createNamedPipe"PosixPath
name (CString -> CMode -> IO CInt
c_mkfifoCString
s CMode
mode ){-# LINE 305 "System/Posix/Files/PosixString.hsc" #-}-- | @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 ::PosixPath->FileMode->DeviceID->IO()createDevice :: PosixPath -> CMode -> DeviceID -> IO ()
createDevice PosixPath
path CMode
mode DeviceID
dev =PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->String -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"createDevice"PosixPath
path (CString -> CMode -> DeviceID -> IO CInt
c_mknod CString
s CMode
mode DeviceID
dev )foreignimportcapiunsafe"HsUnix.h mknod"c_mknod ::CString->CMode->CDev->IOCInt{-# LINE 322 "System/Posix/Files/PosixString.hsc" #-}-- ------------------------------------------------------------------------------- Hard links-- | @createLink old new@ creates a new path, @new@, linked to an existing file,-- @old@.---- Note: calls @link@.createLink ::PosixPath->PosixPath->IO()createLink :: PosixPath -> PosixPath -> IO ()
createLink PosixPath
name1 PosixPath
name2 =PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name1 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s1 ->PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name2 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s2 ->String -> PosixPath -> PosixPath -> IO CInt -> IO ()
forall a.
(Eq a, Num a) =>
String -> PosixPath -> PosixPath -> IO a -> IO ()
throwErrnoTwoPathsIfMinus1_ String
"createLink"PosixPath
name1 PosixPath
name2 (CString -> CString -> IO CInt
c_linkCString
s1 CString
s2 )-- | @removeLink path@ removes the link named @path@.---- Note: calls @unlink@.removeLink ::PosixPath->IO()removeLink :: PosixPath -> IO ()
removeLink PosixPath
name =PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->String -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"removeLink"PosixPath
name (CString -> IO CInt
c_unlinkCString
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 ::PosixPath->PosixPath->IO()createSymbolicLink :: PosixPath -> PosixPath -> IO ()
createSymbolicLink PosixPath
name1 PosixPath
name2 =PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name1 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s1 ->PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name2 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s2 ->String -> PosixPath -> PosixPath -> IO CInt -> IO ()
forall a.
(Eq a, Num a) =>
String -> PosixPath -> PosixPath -> IO a -> IO ()
throwErrnoTwoPathsIfMinus1_ String
"createSymbolicLink"PosixPath
name1 PosixPath
name2 (CString -> CString -> IO CInt
c_symlink CString
s1 CString
s2 )foreignimportccallunsafe"symlink"c_symlink ::CString->CString->IOCInt-- 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.{-# LINE 371 "System/Posix/Files/PosixString.hsc" #-}-- | Reads the @PosixPath@ pointed to by the symbolic link and returns it.---- Note: calls @readlink@.readSymbolicLink ::PosixPath->IOPosixPathreadSymbolicLink :: PosixPath -> IO PosixPath
readSymbolicLink PosixPath
file =Int -> (CString -> IO PosixPath) -> IO PosixPath
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray0(Int
4096)((CString -> IO PosixPath) -> IO PosixPath)
-> (CString -> IO PosixPath) -> IO PosixPath
forall a b. (a -> b) -> a -> b
$\CString
buf ->do{-# LINE 378 "System/Posix/Files/PosixString.hsc" #-}withFilePathfile$\s->dolen<-throwErrnoPathIfMinus1"readSymbolicLink"file$c_readlinksbuf(4096){-# LINE 381 "System/Posix/Files/PosixString.hsc" #-}peekFilePathLen(buf,fromIntegrallen)foreignimportccallunsafe"readlink"c_readlink ::CString->CString->CSize->IOCInt-- ------------------------------------------------------------------------------- Renaming files-- | @rename old new@ renames a file or directory from @old@ to @new@.---- Note: calls @rename@.rename ::PosixPath->PosixPath->IO()rename :: PosixPath -> PosixPath -> IO ()
rename PosixPath
name1 PosixPath
name2 =PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name1 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s1 ->PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name2 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s2 ->String -> PosixPath -> PosixPath -> IO CInt -> IO ()
forall a.
(Eq a, Num a) =>
String -> PosixPath -> PosixPath -> IO a -> IO ()
throwErrnoTwoPathsIfMinus1_ String
"rename"PosixPath
name1 PosixPath
name2 (CString -> CString -> IO CInt
c_rename CString
s1 CString
s2 )foreignimportccallunsafe"rename"c_rename ::CString->CString->IOCInt-- ------------------------------------------------------------------------------- chown(){-# LINE 405 "System/Posix/Files/PosixString.hsc" #-}-- | @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 ::PosixPath->UserID->GroupID->IO()setOwnerAndGroup :: PosixPath -> UserID -> GroupID -> IO ()
setOwnerAndGroup PosixPath
name UserID
uid GroupID
gid =doPosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->String -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"setOwnerAndGroup"PosixPath
name (CString -> UserID -> GroupID -> IO CInt
c_chown CString
s UserID
uid GroupID
gid )foreignimportccallunsafe"chown"c_chown ::CString->CUid->CGid->IOCInt{-# LINE 427 "System/Posix/Files/PosixString.hsc" #-}{-# LINE 429 "System/Posix/Files/PosixString.hsc" #-}-- | Acts as 'setOwnerAndGroup' but does not follow symlinks (and thus-- changes permissions on the link itself).---- Note: calls @lchown@.setSymbolicLinkOwnerAndGroup ::PosixPath->UserID->GroupID->IO()setSymbolicLinkOwnerAndGroup :: PosixPath -> UserID -> GroupID -> IO ()
setSymbolicLinkOwnerAndGroup PosixPath
name UserID
uid GroupID
gid =doPosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->String -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"setSymbolicLinkOwnerAndGroup"PosixPath
name (CString -> UserID -> GroupID -> IO CInt
c_lchown CString
s UserID
uid GroupID
gid )foreignimportccallunsafe"lchown"c_lchown ::CString->CUid->CGid->IOCInt{-# LINE 442 "System/Posix/Files/PosixString.hsc" #-}-- ------------------------------------------------------------------------------- Setting file times-- | @setFileTimes path atime mtime@ sets the access and modification times-- associated with file @path@ to @atime@ and @mtime@, respectively.---- Note: calls @utime@.setFileTimes ::PosixPath->EpochTime->EpochTime->IO()setFileTimes :: PosixPath -> EpochTime -> EpochTime -> IO ()
setFileTimes PosixPath
name EpochTime
atime EpochTime
mtime =doPosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->Int -> (Ptr CUtimbuf -> IO ()) -> IO ()
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes(Int
16)((Ptr CUtimbuf -> IO ()) -> IO ())
-> (Ptr CUtimbuf -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\Ptr CUtimbuf
p ->do{-# LINE 454 "System/Posix/Files/PosixString.hsc" #-}((\hsc_ptr->pokeByteOffhsc_ptr0))patime{-# LINE 455 "System/Posix/Files/PosixString.hsc" #-}((\hsc_ptr->pokeByteOffhsc_ptr8))pmtime{-# LINE 456 "System/Posix/Files/PosixString.hsc" #-}throwErrnoPathIfMinus1_"setFileTimes"name(c_utimesp)-- | Like 'setFileTimes' but timestamps can have sub-second resolution.---- Note: calls @utimensat@ or @utimes@. Support for high resolution timestamps-- is filesystem dependent with the following limitations:---- - HFS+ volumes on OS X truncate the sub-second part of the timestamp.--setFileTimesHiRes ::PosixPath->POSIXTime->POSIXTime->IO(){-# LINE 472 "System/Posix/Files/PosixString.hsc" #-}setFileTimesHiRes :: PosixPath -> POSIXTime -> POSIXTime -> IO ()
setFileTimesHiRes PosixPath
name POSIXTime
atime POSIXTime
mtime =PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->[CTimeSpec] -> (Ptr CTimeSpec -> IO ()) -> IO ()
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray[POSIXTime -> CTimeSpec
Common.toCTimeSpec POSIXTime
atime ,POSIXTime -> CTimeSpec
Common.toCTimeSpec POSIXTime
mtime ]((Ptr CTimeSpec -> IO ()) -> IO ())
-> (Ptr CTimeSpec -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\Ptr CTimeSpec
times ->String -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"setFileTimesHiRes"PosixPath
name (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$CInt -> CString -> Ptr CTimeSpec -> CInt -> IO CInt
Common.c_utimensat (-CInt
100)CString
s Ptr CTimeSpec
times CInt
0{-# LINE 477 "System/Posix/Files/PosixString.hsc" #-}{-# LINE 483 "System/Posix/Files/PosixString.hsc" #-}-- | Like 'setFileTimesHiRes' but does not follow symbolic links.-- This operation is not supported on all platforms. On these platforms,-- this function will raise an exception.---- Note: calls @utimensat@ or @lutimes@. Support for high resolution timestamps-- is filesystem dependent with the following limitations:---- - HFS+ volumes on OS X truncate the sub-second part of the timestamp.--setSymbolicLinkTimesHiRes ::PosixPath->POSIXTime->POSIXTime->IO(){-# LINE 495 "System/Posix/Files/PosixString.hsc" #-}setSymbolicLinkTimesHiResnameatimemtime=withFilePathname$\s->withArray[Common.toCTimeSpecatime,Common.toCTimeSpecmtime]$\times->throwErrnoPathIfMinus1_"setSymbolicLinkTimesHiRes"name$Common.c_utimensat(-100)stimes(256){-# LINE 500 "System/Posix/Files/PosixString.hsc" #-}{-# LINE 510 "System/Posix/Files/PosixString.hsc" #-}-- | @touchFile path@ sets the access and modification times associated with-- file @path@ to the current time.---- Note: calls @utime@.touchFile ::PosixPath->IO()touchFile :: PosixPath -> IO ()
touchFile PosixPath
name =doPosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->String -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"touchFile"PosixPath
name (CString -> Ptr CUtimbuf -> IO CInt
c_utimeCString
s Ptr CUtimbuf
forall a. Ptr a
nullPtr)-- | Like 'touchFile' but does not follow symbolic links.-- This operation is not supported on all platforms. On these platforms,-- this function will raise an exception.---- Note: calls @lutimes@.touchSymbolicLink ::PosixPath->IO(){-# LINE 527 "System/Posix/Files/PosixString.hsc" #-}touchSymbolicLinkname=withFilePathname$\s->throwErrnoPathIfMinus1_"touchSymbolicLink"name(Common.c_lutimessnullPtr){-# LINE 534 "System/Posix/Files/PosixString.hsc" #-}-- ------------------------------------------------------------------------------- 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 ::PosixPath->FileOffset->IO()setFileSize :: PosixPath -> FileOffset -> IO ()
setFileSize PosixPath
file FileOffset
off =PosixPath -> (CString -> IO ()) -> IO ()
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
file ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\CString
s ->String -> PosixPath -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"setFileSize"PosixPath
file (CString -> FileOffset -> IO CInt
c_truncate CString
s FileOffset
off )foreignimportcapiunsafe"HsUnix.h truncate"c_truncate ::CString->COff->IOCInt-- ------------------------------------------------------------------------------- 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 ::PosixPath->PathVar ->IOLimitgetPathVar :: PosixPath -> PathVar -> IO CLong
getPathVar PosixPath
name PathVar
v =doPosixPath -> (CString -> IO CLong) -> IO CLong
forall a. PosixPath -> (CString -> IO a) -> IO a
withFilePath PosixPath
name ((CString -> IO CLong) -> IO CLong)
-> (CString -> IO CLong) -> IO CLong
forall a b. (a -> b) -> a -> b
$\CString
nameP ->String -> PosixPath -> IO CLong -> IO CLong
forall a. (Eq a, Num a) => String -> PosixPath -> IO a -> IO a
throwErrnoPathIfMinus1 String
"getPathVar"PosixPath
name (IO CLong -> IO CLong) -> IO CLong -> IO CLong
forall a b. (a -> b) -> a -> b
$CString -> CInt -> IO CLong
c_pathconf CString
nameP (PathVar -> CInt
Common.pathVarConst PathVar
v )foreignimportccallunsafe"pathconf"c_pathconf ::CString->CInt->IOCLong

AltStyle によって変換されたページ (->オリジナル) /