{-# LINE 1 "System/Posix/Files.hsc" #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE CApiFFI #-}
{-# LANGUAGE PatternSynonyms #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  System.Posix.Files
-- 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.
--
-----------------------------------------------------------------------------



module System.Posix.Files (
    -- * 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,
    accessTimeHiRes, modificationTimeHiRes, statusChangeTimeHiRes,
    isBlockDevice, isCharacterDevice, isNamedPipe, isRegularFile,
    isDirectory, isSymbolicLink, isSocket,

    fileBlockSize,
    fileBlocks,

    -- * Extended file status
    ExtendedFileStatus(..),
    CAttributes(..),
    haveStatx,
    -- ** Obtaining extended file status
    getExtendedFileStatus,
    -- ** Flags
    StatxFlags(..),
    defaultStatxFlags,
    pattern EmptyPath,
    pattern NoAutoMount,
    pattern SymlinkNoFollow,
    pattern SyncAsStat,
    pattern ForceSync,
    pattern DontSync,
    -- ** Mask
    StatxMask(..),
    defaultStatxMask,
    pattern StatxType,
    pattern StatxMode,
    pattern StatxNlink,
    pattern StatxUid,
    pattern StatxGid,
    pattern StatxAtime,
    pattern StatxMtime,
    pattern StatxCtime,
    pattern StatxIno,
    pattern StatxSize,
    pattern StatxBlocks,
    pattern StatxBasicStats,
    pattern StatxBtime,
    pattern StatxMntId,
    pattern StatxAll,
    -- ** Querying extended file status
    fileBlockSizeX,
    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,

    -- * Creation
    createNamedPipe,
    createDevice,

    -- * Hard links
    createLink, removeLink,

    -- * Symbolic links
    createSymbolicLink, readSymbolicLink,

    -- * Renaming files
    rename,

    -- * Changing file ownership
    setOwnerAndGroup,  setFdOwnerAndGroup,

{-# LINE 146 "System/Posix/Files.hsc" #-}
    setSymbolicLinkOwnerAndGroup,

{-# LINE 148 "System/Posix/Files.hsc" #-}

    -- * Changing file timestamps
    setFileTimes, setFileTimesHiRes,
    setFdTimesHiRes, setSymbolicLinkTimesHiRes,
    touchFile, touchFd, touchSymbolicLink,

    -- * Setting file sizes
    setFileSize, setFdSize,

    -- * Find system-specific limits for a file
    PathVar(..), getPathVar, getFdPathVar,
  ) where


import Foreign
import Foreign.C

import System.Posix.Types
import System.Posix.Files.Common
import System.Posix.Error
import System.Posix.Internals


{-# LINE 173 "System/Posix/Files.hsc" #-}

import Data.Time.Clock.POSIX (POSIXTime)


{-# LINE 180 "System/Posix/Files.hsc" #-}

-- throwErrnoTwoPathsIfMinus1_
--
-- | For operations that require two paths (e.g., renaming a file)
throwErrnoTwoPathsIfMinus1_ :: (Eq a, Num a) => String -> FilePath -> FilePath -> IO a -> IO ()
throwErrnoTwoPathsIfMinus1_ :: forall a.
(Eq a, Num a) =>
String -> String -> String -> IO a -> IO ()
throwErrnoTwoPathsIfMinus1_ String
loc String
path1 String
path2 =
  String -> IO a -> IO ()
forall a. (Eq a, Num a) => String -> IO a -> IO ()
throwErrnoIfMinus1_ (String
loc String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" '" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
path1 String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"' to '" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
path2 String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"'")

-- -----------------------------------------------------------------------------
-- 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 :: FilePath -> FileMode -> IO ()
setFileMode :: String -> CMode -> IO ()
setFileMode String
name CMode
m =
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s -> do
    String -> String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> String -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"setFileMode" String
name (CString -> CMode -> IO CInt
c_chmod CString
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 :: FilePath -> Bool -> Bool -> Bool -> IO Bool
fileAccess :: String -> Bool -> Bool -> Bool -> IO Bool
fileAccess String
name Bool
readOK Bool
writeOK Bool
execOK = String -> CMode -> IO Bool
access String
name CMode
flags
  where
   flags :: 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  = if Bool
readOK  then (CMode
4) else CMode
0
{-# LINE 215 "System/Posix/Files.hsc" #-}
   write_f = if writeOK then (2) else 0
{-# LINE 216 "System/Posix/Files.hsc" #-}
   exec_f  = if execOK  then (1) else 0
{-# LINE 217 "System/Posix/Files.hsc" #-}

-- | Checks for the existence of the file.
--
-- Note: calls @access@.
fileExist :: FilePath -> IO Bool
fileExist :: String -> IO Bool
fileExist String
name =
  String -> (CString -> IO Bool) -> IO Bool
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name ((CString -> IO Bool) -> IO Bool)
-> (CString -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \CString
s -> do
    CInt
r <- CString -> CInt -> IO CInt
c_access CString
s (CInt
0)
{-# LINE 225 "System/Posix/Files.hsc" #-}
    if (r == 0)
        then return True
        else do err <- getErrno
                if (err == eNOENT)
                   then return False
                   else throwErrnoPath "fileExist" name

access :: FilePath -> CMode -> IO Bool
access :: String -> CMode -> IO Bool
access String
name CMode
flags =
  String -> (CString -> IO Bool) -> IO Bool
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name ((CString -> IO Bool) -> IO Bool)
-> (CString -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \CString
s -> do
    CInt
r <- CString -> CInt -> IO CInt
c_access CString
s (CMode -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral CMode
flags)
    if (CInt
r CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
0)
        then Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
        else do Errno
err <- IO Errno
getErrno
                if (Errno
err Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
eACCES Bool -> Bool -> Bool
|| Errno
err Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
eROFS Bool -> Bool -> Bool
|| Errno
err Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
eTXTBSY Bool -> Bool -> Bool
||
                    Errno
err Errno -> Errno -> Bool
forall a. Eq a => a -> a -> Bool
== Errno
ePERM)
                   then Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
                   else String -> String -> IO Bool
forall a. String -> String -> IO a
throwErrnoPath String
"fileAccess" String
name


-- | @getFileStatus path@ calls gets the @FileStatus@ information (user ID,
-- size, access times, etc.) for the file @path@.
--
-- Note: calls @stat@.
getFileStatus :: FilePath -> IO FileStatus
getFileStatus :: String -> IO FileStatus
getFileStatus String
path = do
  ForeignPtr CStat
fp <- Int -> IO (ForeignPtr CStat)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes (Int
144)
{-# LINE 252 "System/Posix/Files.hsc" #-}
  withForeignPtr fp $ \p ->
    withFilePath path $ \s ->
      throwErrnoPathIfMinus1Retry_ "getFileStatus" path (c_stat s p)
  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 :: Maybe Fd    -- ^ Optional directory file descriptor (@dirfd@)
                      -> FilePath    -- ^ @pathname@ to open
                      -> StatxFlags  -- ^ flags
                      -> StatxMask   -- ^ mask
                      -> IO ExtendedFileStatus
getExtendedFileStatus :: Maybe Fd
-> String -> StatxFlags -> StatxMask -> IO ExtendedFileStatus
getExtendedFileStatus Maybe Fd
mfd String
path StatxFlags
flags StatxMask
masks = String
-> (CString -> IO ExtendedFileStatus) -> IO ExtendedFileStatus
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
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 'FilePath' 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 :: FilePath -> IO FileStatus
getSymbolicLinkStatus :: String -> IO FileStatus
getSymbolicLinkStatus String
path = do
  ForeignPtr CStat
fp <- Int -> IO (ForeignPtr CStat)
forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes (Int
144)
{-# LINE 284 "System/Posix/Files.hsc" #-}
  withForeignPtr fp $ \p ->
    withFilePath path $ \s ->
      throwErrnoPathIfMinus1_ "getSymbolicLinkStatus" path (c_lstat s p)
  FileStatus -> IO FileStatus
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr CStat -> FileStatus
FileStatus ForeignPtr CStat
fp)

foreign import capi unsafe "HsUnix.h 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 :: FilePath -> FileMode -> IO ()
createNamedPipe :: String -> CMode -> IO ()
createNamedPipe String
name CMode
mode = do
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s ->
    String -> String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> String -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"createNamedPipe" String
name (CString -> CMode -> IO CInt
c_mkfifo CString
s CMode
mode)


{-# LINE 311 "System/Posix/Files.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 :: FilePath -> FileMode -> DeviceID -> IO ()
createDevice :: String -> CMode -> DeviceID -> IO ()
createDevice String
path CMode
mode DeviceID
dev =
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
path ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s ->
    String -> String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> String -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"createDevice" String
path (CString -> CMode -> DeviceID -> IO CInt
c_mknod CString
s CMode
mode DeviceID
dev)

foreign import capi unsafe "HsUnix.h mknod"
  c_mknod :: CString -> CMode -> CDev -> IO CInt


{-# LINE 328 "System/Posix/Files.hsc" #-}

-- -----------------------------------------------------------------------------
-- Hard links

-- | @createLink old new@ creates a new path, @new@, linked to an existing file,
-- @old@.
--
-- Note: calls @link@.
createLink :: FilePath -> FilePath -> IO ()
createLink :: String -> String -> IO ()
createLink String
name1 String
name2 =
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name1 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s1 ->
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name2 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s2 ->
  String -> String -> String -> IO CInt -> IO ()
forall a.
(Eq a, Num a) =>
String -> String -> String -> IO a -> IO ()
throwErrnoTwoPathsIfMinus1_ String
"createLink" String
name1 String
name2 (CString -> CString -> IO CInt
c_link CString
s1 CString
s2)

-- | @removeLink path@ removes the link named @path@.
--
-- Note: calls @unlink@.
removeLink :: FilePath -> IO ()
removeLink :: String -> IO ()
removeLink String
name =
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s ->
  String -> String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> String -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"removeLink" String
name (CString -> IO CInt
c_unlink CString
s)

-- -----------------------------------------------------------------------------
-- Symbolic Links

-- | @createSymbolicLink name1 name2@ creates a symbolic link named @name2@
-- which points to the file @name1@.
--
-- 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 :: FilePath -> FilePath -> IO ()
createSymbolicLink :: String -> String -> IO ()
createSymbolicLink String
name1 String
name2 =
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name1 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s1 ->
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name2 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s2 ->
  String -> String -> String -> IO CInt -> IO ()
forall a.
(Eq a, Num a) =>
String -> String -> String -> IO a -> IO ()
throwErrnoTwoPathsIfMinus1_ String
"createSymbolicLink" String
name1 String
name2 (CString -> CString -> IO CInt
c_symlink CString
s1 CString
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.

{-# LINE 377 "System/Posix/Files.hsc" #-}

-- | Reads the @FilePath@ pointed to by the symbolic link and returns it.
--
-- Note: calls @readlink@.
readSymbolicLink :: FilePath -> IO FilePath
readSymbolicLink :: String -> IO String
readSymbolicLink String
file =
  Int -> (CString -> IO String) -> IO String
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray0 (Int
4096) ((CString -> IO String) -> IO String)
-> (CString -> IO String) -> IO String
forall a b. (a -> b) -> a -> b
$ \CString
buf -> do
{-# LINE 384 "System/Posix/Files.hsc" #-}
    withFilePath file $ \s -> do
      len <- throwErrnoPathIfMinus1 "readSymbolicLink" file $
        c_readlink s buf (4096)
{-# LINE 387 "System/Posix/Files.hsc" #-}
      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 :: FilePath -> FilePath -> IO ()
rename :: String -> String -> IO ()
rename String
name1 String
name2 =
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name1 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s1 ->
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name2 ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s2 ->
  String -> String -> String -> IO CInt -> IO ()
forall a.
(Eq a, Num a) =>
String -> String -> String -> IO a -> IO ()
throwErrnoTwoPathsIfMinus1_  String
"rename" String
name1 String
name2 (CString -> CString -> IO CInt
c_rename CString
s1 CString
s2)

foreign import ccall unsafe "rename"
   c_rename :: CString -> CString -> IO CInt

-- -----------------------------------------------------------------------------
-- chown()


{-# LINE 411 "System/Posix/Files.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 :: FilePath -> UserID -> GroupID -> IO ()
setOwnerAndGroup :: String -> UserID -> GroupID -> IO ()
setOwnerAndGroup String
name UserID
uid GroupID
gid = do
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s ->
    String -> String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> String -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"setOwnerAndGroup" String
name (CString -> UserID -> GroupID -> IO CInt
c_chown CString
s UserID
uid GroupID
gid)

foreign import ccall unsafe "chown"
  c_chown :: CString -> CUid -> CGid -> IO CInt


{-# LINE 433 "System/Posix/Files.hsc" #-}


{-# LINE 435 "System/Posix/Files.hsc" #-}
-- | Acts as 'setOwnerAndGroup' but does not follow symlinks (and thus
-- changes permissions on the link itself).
--
-- Note: calls @lchown@.
setSymbolicLinkOwnerAndGroup :: FilePath -> UserID -> GroupID -> IO ()
setSymbolicLinkOwnerAndGroup :: String -> UserID -> GroupID -> IO ()
setSymbolicLinkOwnerAndGroup String
name UserID
uid GroupID
gid = do
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s ->
    String -> String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> String -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"setSymbolicLinkOwnerAndGroup" String
name
        (CString -> UserID -> GroupID -> IO CInt
c_lchown CString
s UserID
uid GroupID
gid)

foreign import ccall unsafe "lchown"
  c_lchown :: CString -> CUid -> CGid -> IO CInt

{-# LINE 448 "System/Posix/Files.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 :: FilePath -> EpochTime -> EpochTime -> IO ()
setFileTimes :: String -> EpochTime -> EpochTime -> IO ()
setFileTimes String
name EpochTime
atime EpochTime
mtime = do
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
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 460 "System/Posix/Files.hsc" #-}
     ((\hsc_ptr -> pokeByteOff hsc_ptr 0))  p atime
{-# LINE 461 "System/Posix/Files.hsc" #-}
     ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p mtime
{-# LINE 462 "System/Posix/Files.hsc" #-}
     throwErrnoPathIfMinus1_ "setFileTimes" name (c_utime s p)

-- | 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.
--
-- @since 2.7.0.0
setFileTimesHiRes :: FilePath -> POSIXTime -> POSIXTime -> IO ()

{-# LINE 479 "System/Posix/Files.hsc" #-}
setFileTimesHiRes :: String -> POSIXTime -> POSIXTime -> IO ()
setFileTimesHiRes String
name POSIXTime
atime POSIXTime
mtime =
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
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 -> String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> String -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"setFileTimesHiRes" String
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 484 "System/Posix/Files.hsc" #-}

{-# LINE 490 "System/Posix/Files.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.
--
-- @since 2.7.0.0
setSymbolicLinkTimesHiRes :: FilePath -> POSIXTime -> POSIXTime -> IO ()

{-# LINE 508 "System/Posix/Files.hsc" #-}
setSymbolicLinkTimesHiRes :: String -> POSIXTime -> POSIXTime -> IO ()
setSymbolicLinkTimesHiRes String
name POSIXTime
atime POSIXTime
mtime =
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
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 -> String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> String -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"setSymbolicLinkTimesHiRes" String
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 513 "System/Posix/Files.hsc" #-}

{-# LINE 526 "System/Posix/Files.hsc" #-}

-- | @touchFile path@ sets the access and modification times associated with
-- file @path@ to the current time.
--
-- Note: calls @utime@.
touchFile :: FilePath -> IO ()
touchFile :: String -> IO ()
touchFile String
name = do
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s ->
   String -> String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> String -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"touchFile" String
name (CString -> Ptr CUtimbuf -> IO CInt
c_utime CString
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@.
--
-- @since 2.7.0.0
touchSymbolicLink :: FilePath -> IO ()

{-# LINE 549 "System/Posix/Files.hsc" #-}
touchSymbolicLink :: String -> IO ()
touchSymbolicLink String
name =
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s ->
    String -> String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> String -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"touchSymbolicLink" String
name (CString -> Ptr CTimeVal -> IO CInt
c_lutimes CString
s Ptr CTimeVal
forall a. Ptr a
nullPtr)

{-# LINE 559 "System/Posix/Files.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 :: FilePath -> FileOffset -> IO ()
setFileSize :: String -> FileOffset -> IO ()
setFileSize String
file FileOffset
off =
  String -> (CString -> IO ()) -> IO ()
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
file ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \CString
s ->
    String -> String -> IO CInt -> IO ()
forall a. (Eq a, Num a) => String -> String -> IO a -> IO ()
throwErrnoPathIfMinus1_ String
"setFileSize" String
file (CString -> FileOffset -> IO CInt
c_truncate CString
s FileOffset
off)

foreign import capi unsafe "HsUnix.h 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 :: FilePath -> PathVar -> IO Limit
getPathVar :: String -> PathVar -> IO CLong
getPathVar String
name PathVar
v = do
  String -> (CString -> IO CLong) -> IO CLong
forall a. String -> (CString -> IO a) -> IO a
withFilePath String
name ((CString -> IO CLong) -> IO CLong)
-> (CString -> IO CLong) -> IO CLong
forall a b. (a -> b) -> a -> b
$ \ CString
nameP ->
    String -> String -> IO CLong -> IO CLong
forall a. (Eq a, Num a) => String -> String -> IO a -> IO a
throwErrnoPathIfMinus1 String
"getPathVar" String
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)

foreign import ccall unsafe "pathconf"
  c_pathconf :: CString -> CInt -> IO CLong