{-# LINE 1 "System/Posix/Files/ByteString.hsc" #-}{-# LANGUAGE Safe #-}{-# LANGUAGE CApiFFI #-}{-# LANGUAGE PatternSynonyms #-}------------------------------------------------------------------------------- |-- 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.-------------------------------------------------------------------------------moduleSystem.Posix.Files.ByteString(-- * 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 ,fileBlockSize ,fileBlocks ,-- * 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 146 "System/Posix/Files/ByteString.hsc" #-}setSymbolicLinkOwnerAndGroup,{-# LINE 148 "System/Posix/Files/ByteString.hsc" #-}-- * Changing file timestampssetFileTimes ,setFileTimesHiRes ,setFdTimesHiRes ,setSymbolicLinkTimesHiRes ,touchFile ,touchFd ,touchSymbolicLink ,-- * Setting file sizessetFileSize ,setFdSize ,-- * Find system-specific limits for a filePathVar (..),getPathVar ,getFdPathVar ,)whereimportSystem.Posix.TypesimportSystem.Posix.Internalshiding(withFilePath,peekFilePathLen)importForeignimportForeign.Chiding(throwErrnoPath,throwErrnoPathIf,throwErrnoPathIf_,throwErrnoPathIfNull,throwErrnoPathIfMinus1,throwErrnoPathIfMinus1_)importSystem.Posix.Files.Common importSystem.Posix.ByteString.FilePath importData.Time.Clock.POSIX(POSIXTime){-# LINE 181 "System/Posix/Files/ByteString.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 ::RawFilePath ->FileMode->IO()setFileMode :: RawFilePath -> CMode -> IO () setFileMode RawFilePath name CMode m =RawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\CString s ->doString -> RawFilePath -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO () throwErrnoPathIfMinus1_ String "setFileMode"RawFilePath 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 ::RawFilePath ->Bool->Bool->Bool->IOBoolfileAccess :: RawFilePath -> Bool -> Bool -> Bool -> IO Bool fileAccess RawFilePath name Bool readOK Bool writeOK Bool execOK =RawFilePath -> CMode -> IO Bool access RawFilePath 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 210 "System/Posix/Files/ByteString.hsc" #-}write_f=ifwriteOKthen(2)else0{-# LINE 211 "System/Posix/Files/ByteString.hsc" #-}exec_f=ifexecOKthen(1)else0{-# LINE 212 "System/Posix/Files/ByteString.hsc" #-}-- | Checks for the existence of the file.---- Note: calls @access@.fileExist ::RawFilePath ->IOBoolfileExist :: RawFilePath -> IO Bool fileExist RawFilePath name =RawFilePath -> (CString -> IO Bool) -> IO Bool forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath 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 220 "System/Posix/Files/ByteString.hsc" #-}if(r==0)thenreturnTrueelsedoerr<-getErrnoif(err==eNOENT)thenreturnFalseelsethrowErrnoPath"fileExist"nameaccess ::RawFilePath ->CMode->IOBoolaccess :: RawFilePath -> CMode -> IO Bool access RawFilePath name CMode flags =RawFilePath -> (CString -> IO Bool) -> IO Bool forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath 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 -> RawFilePath -> IO Bool forall a. String -> RawFilePath -> IO a throwErrnoPath String "fileAccess"RawFilePath name -- | @getFileStatus path@ calls gets the @FileStatus@ information (user ID,-- size, access times, etc.) for the file @path@.---- Note: calls @stat@.getFileStatus ::RawFilePath ->IOFileStatus getFileStatus :: RawFilePath -> IO FileStatus getFileStatus RawFilePath path =doForeignPtr CStat fp <-Int -> IO (ForeignPtr CStat) forall a. Int -> IO (ForeignPtr a) mallocForeignPtrBytes(Int 144){-# LINE 247 "System/Posix/Files/ByteString.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 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@)->RawFilePath -- ^ @pathname@ to open->StatxFlags -- ^ flags->StatxMask -- ^ mask->IOExtendedFileStatus getExtendedFileStatus :: Maybe Fd -> RawFilePath -> StatxFlags -> StatxMask -> IO ExtendedFileStatus getExtendedFileStatus Maybe Fd mfd RawFilePath path StatxFlags flags StatxMask masks =RawFilePath -> (CString -> IO ExtendedFileStatus) -> IO ExtendedFileStatus forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath 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 '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 ->IOFileStatus getSymbolicLinkStatus :: RawFilePath -> IO FileStatus getSymbolicLinkStatus RawFilePath path =doForeignPtr CStat fp <-Int -> IO (ForeignPtr CStat) forall a. Int -> IO (ForeignPtr a) mallocForeignPtrBytes(Int 144){-# LINE 279 "System/Posix/Files/ByteString.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 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 ::RawFilePath ->FileMode->IO()createNamedPipe :: RawFilePath -> CMode -> IO () createNamedPipe RawFilePath name CMode mode =doRawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\CString s ->String -> RawFilePath -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO () throwErrnoPathIfMinus1_ String "createNamedPipe"RawFilePath name (CString -> CMode -> IO CInt c_mkfifoCString s CMode mode ){-# LINE 306 "System/Posix/Files/ByteString.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 ::RawFilePath ->FileMode->DeviceID->IO()createDevice :: RawFilePath -> CMode -> DeviceID -> IO () createDevice RawFilePath path CMode mode DeviceID dev =RawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\CString s ->String -> RawFilePath -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO () throwErrnoPathIfMinus1_ String "createDevice"RawFilePath 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 324 "System/Posix/Files/ByteString.hsc" #-}-- ------------------------------------------------------------------------------- Hard links-- | @createLink old new@ creates a new path, @new@, linked to an existing file,-- @old@.---- Note: calls @link@.createLink ::RawFilePath ->RawFilePath ->IO()createLink :: RawFilePath -> RawFilePath -> IO () createLink RawFilePath name1 RawFilePath name2 =RawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath name1 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\CString s1 ->RawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath name2 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\CString s2 ->String -> RawFilePath -> RawFilePath -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> RawFilePath -> RawFilePath -> IO a -> IO () throwErrnoTwoPathsIfMinus1_ String "createLink"RawFilePath name1 RawFilePath name2 (CString -> CString -> IO CInt c_linkCString s1 CString s2 )-- | @removeLink path@ removes the link named @path@.---- Note: calls @unlink@.removeLink ::RawFilePath ->IO()removeLink :: RawFilePath -> IO () removeLink RawFilePath name =RawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\CString s ->String -> RawFilePath -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO () throwErrnoPathIfMinus1_ String "removeLink"RawFilePath 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 ::RawFilePath ->RawFilePath ->IO()createSymbolicLink :: RawFilePath -> RawFilePath -> IO () createSymbolicLink RawFilePath name1 RawFilePath name2 =RawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath name1 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\CString s1 ->RawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath name2 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\CString s2 ->String -> RawFilePath -> RawFilePath -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> RawFilePath -> RawFilePath -> IO a -> IO () throwErrnoTwoPathsIfMinus1_ String "createSymbolicLink"RawFilePath name1 RawFilePath 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 373 "System/Posix/Files/ByteString.hsc" #-}-- | Reads the @RawFilePath@ pointed to by the symbolic link and returns it.---- Note: calls @readlink@.readSymbolicLink ::RawFilePath ->IORawFilePath readSymbolicLink :: RawFilePath -> IO RawFilePath readSymbolicLink RawFilePath file =Int -> (CString -> IO RawFilePath) -> IO RawFilePath forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b allocaArray0(Int 4096)((CString -> IO RawFilePath) -> IO RawFilePath) -> (CString -> IO RawFilePath) -> IO RawFilePath forall a b. (a -> b) -> a -> b $\CString buf ->do{-# LINE 380 "System/Posix/Files/ByteString.hsc" #-}withFilePathfile$\s->dolen<-throwErrnoPathIfMinus1"readSymbolicLink"file$c_readlinksbuf(4096){-# LINE 383 "System/Posix/Files/ByteString.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 ::RawFilePath ->RawFilePath ->IO()rename :: RawFilePath -> RawFilePath -> IO () rename RawFilePath name1 RawFilePath name2 =RawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath name1 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\CString s1 ->RawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath name2 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\CString s2 ->String -> RawFilePath -> RawFilePath -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> RawFilePath -> RawFilePath -> IO a -> IO () throwErrnoTwoPathsIfMinus1_ String "rename"RawFilePath name1 RawFilePath name2 (CString -> CString -> IO CInt c_rename CString s1 CString s2 )foreignimportccallunsafe"rename"c_rename ::CString->CString->IOCInt-- ------------------------------------------------------------------------------- chown(){-# LINE 407 "System/Posix/Files/ByteString.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 ::RawFilePath ->UserID->GroupID->IO()setOwnerAndGroup :: RawFilePath -> UserID -> GroupID -> IO () setOwnerAndGroup RawFilePath name UserID uid GroupID gid =doRawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\CString s ->String -> RawFilePath -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO () throwErrnoPathIfMinus1_ String "setOwnerAndGroup"RawFilePath name (CString -> UserID -> GroupID -> IO CInt c_chown CString s UserID uid GroupID gid )foreignimportccallunsafe"chown"c_chown ::CString->CUid->CGid->IOCInt{-# LINE 429 "System/Posix/Files/ByteString.hsc" #-}{-# LINE 431 "System/Posix/Files/ByteString.hsc" #-}-- | 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 :: RawFilePath -> UserID -> GroupID -> IO () setSymbolicLinkOwnerAndGroup RawFilePath name UserID uid GroupID gid =doRawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\CString s ->String -> RawFilePath -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO () throwErrnoPathIfMinus1_ String "setSymbolicLinkOwnerAndGroup"RawFilePath name (CString -> UserID -> GroupID -> IO CInt c_lchown CString s UserID uid GroupID gid )foreignimportccallunsafe"lchown"c_lchown ::CString->CUid->CGid->IOCInt{-# LINE 444 "System/Posix/Files/ByteString.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 ::RawFilePath ->EpochTime->EpochTime->IO()setFileTimes :: RawFilePath -> EpochTime -> EpochTime -> IO () setFileTimes RawFilePath name EpochTime atime EpochTime mtime =doRawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath 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 456 "System/Posix/Files/ByteString.hsc" #-}((\hsc_ptr->pokeByteOffhsc_ptr0))patime{-# LINE 457 "System/Posix/Files/ByteString.hsc" #-}((\hsc_ptr->pokeByteOffhsc_ptr8))pmtime{-# LINE 458 "System/Posix/Files/ByteString.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 ::RawFilePath ->POSIXTime->POSIXTime->IO(){-# LINE 474 "System/Posix/Files/ByteString.hsc" #-}setFileTimesHiRes :: RawFilePath -> POSIXTime -> POSIXTime -> IO () setFileTimesHiRes RawFilePath name POSIXTime atime POSIXTime mtime =RawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath 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 toCTimeSpec POSIXTime atime ,POSIXTime -> CTimeSpec toCTimeSpec POSIXTime mtime ]((Ptr CTimeSpec -> IO ()) -> IO ()) -> (Ptr CTimeSpec -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\Ptr CTimeSpec times ->String -> RawFilePath -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO () throwErrnoPathIfMinus1_ String "setFileTimesHiRes"RawFilePath name (IO CInt -> IO ()) -> IO CInt -> IO () forall a b. (a -> b) -> a -> b $CInt -> CString -> Ptr CTimeSpec -> CInt -> IO CInt c_utimensat (-CInt 100)CString s Ptr CTimeSpec times CInt 0{-# LINE 479 "System/Posix/Files/ByteString.hsc" #-}{-# LINE 485 "System/Posix/Files/ByteString.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 ::RawFilePath ->POSIXTime->POSIXTime->IO(){-# LINE 502 "System/Posix/Files/ByteString.hsc" #-}setSymbolicLinkTimesHiRes :: RawFilePath -> POSIXTime -> POSIXTime -> IO () setSymbolicLinkTimesHiRes RawFilePath name POSIXTime atime POSIXTime mtime =RawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath 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 toCTimeSpec POSIXTime atime ,POSIXTime -> CTimeSpec toCTimeSpec POSIXTime mtime ]((Ptr CTimeSpec -> IO ()) -> IO ()) -> (Ptr CTimeSpec -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\Ptr CTimeSpec times ->String -> RawFilePath -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO () throwErrnoPathIfMinus1_ String "setSymbolicLinkTimesHiRes"RawFilePath name (IO CInt -> IO ()) -> IO CInt -> IO () forall a b. (a -> b) -> a -> b $CInt -> CString -> Ptr CTimeSpec -> CInt -> IO CInt c_utimensat (-CInt 100)CString s Ptr CTimeSpec times (CInt 256){-# LINE 507 "System/Posix/Files/ByteString.hsc" #-}{-# LINE 518 "System/Posix/Files/ByteString.hsc" #-}-- | @touchFile path@ sets the access and modification times associated with-- file @path@ to the current time.---- Note: calls @utime@.touchFile ::RawFilePath ->IO()touchFile :: RawFilePath -> IO () touchFile RawFilePath name =doRawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\CString s ->String -> RawFilePath -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO () throwErrnoPathIfMinus1_ String "touchFile"RawFilePath 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 ::RawFilePath ->IO(){-# LINE 539 "System/Posix/Files/ByteString.hsc" #-}touchSymbolicLink :: RawFilePath -> IO () touchSymbolicLink RawFilePath name =RawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\CString s ->String -> RawFilePath -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO () throwErrnoPathIfMinus1_ String "touchSymbolicLink"RawFilePath name (CString -> Ptr CTimeVal -> IO CInt c_lutimes CString s Ptr CTimeVal forall a. Ptr a nullPtr){-# LINE 547 "System/Posix/Files/ByteString.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 ::RawFilePath ->FileOffset->IO()setFileSize :: RawFilePath -> FileOffset -> IO () setFileSize RawFilePath file FileOffset off =RawFilePath -> (CString -> IO ()) -> IO () forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath file ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO () forall a b. (a -> b) -> a -> b $\CString s ->String -> RawFilePath -> IO CInt -> IO () forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO () throwErrnoPathIfMinus1_ String "setFileSize"RawFilePath 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 ::RawFilePath ->PathVar ->IOLimitgetPathVar :: RawFilePath -> PathVar -> IO CLong getPathVar RawFilePath name PathVar v =doRawFilePath -> (CString -> IO CLong) -> IO CLong forall a. RawFilePath -> (CString -> IO a) -> IO a withFilePath RawFilePath name ((CString -> IO CLong) -> IO CLong) -> (CString -> IO CLong) -> IO CLong forall a b. (a -> b) -> a -> b $\CString nameP ->String -> RawFilePath -> IO CLong -> IO CLong forall a. (Eq a, Num a) => String -> RawFilePath -> IO a -> IO a throwErrnoPathIfMinus1 String "getPathVar"RawFilePath 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 pathVarConst PathVar v )foreignimportccallunsafe"pathconf"c_pathconf ::CString->CInt->IOCLong