{-# LINE 1 "libraries/unix/System/Posix/Files.hsc" #-}
{-# LINE 2 "libraries/unix/System/Posix/Files.hsc" #-}
{-# LANGUAGE Safe #-}
{-# LINE 6 "libraries/unix/System/Posix/Files.hsc" #-}
{-# LANGUAGE CApiFFI #-}
module System.Posix.Files (
    
    
    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,
    
    setFileMode, setFdMode, setFileCreationMask,
    
    fileAccess, fileExist,
    
    FileStatus,
    
    getFileStatus, getFdStatus, getSymbolicLinkStatus,
    
    deviceID, fileID, fileMode, linkCount, fileOwner, fileGroup,
    specialDeviceID, fileSize, accessTime, modificationTime,
    statusChangeTime,
    accessTimeHiRes, modificationTimeHiRes, statusChangeTimeHiRes,
    isBlockDevice, isCharacterDevice, isNamedPipe, isRegularFile,
    isDirectory, isSymbolicLink, isSocket,
    
    createNamedPipe,
    createDevice,
    
    createLink, removeLink,
    
    createSymbolicLink, readSymbolicLink,
    
    rename,
    
    setOwnerAndGroup,  setFdOwnerAndGroup,
{-# LINE 82 "libraries/unix/System/Posix/Files.hsc" #-}
    setSymbolicLinkOwnerAndGroup,
{-# LINE 84 "libraries/unix/System/Posix/Files.hsc" #-}
    
    setFileTimes, setFileTimesHiRes,
    setFdTimesHiRes, setSymbolicLinkTimesHiRes,
    touchFile, touchFd, touchSymbolicLink,
    
    setFileSize, setFdSize,
    
    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
import Data.Time.Clock.POSIX (POSIXTime)
setFileMode :: FilePath -> FileMode -> IO ()
setFileMode name m =
  withFilePath name $ \s -> do
    throwErrnoPathIfMinus1_ "setFileMode" name (c_chmod s m)
fileAccess :: FilePath -> 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 (4) else 0
{-# LINE 135 "libraries/unix/System/Posix/Files.hsc" #-}
   write_f = if writeOK then (2) else 0
{-# LINE 136 "libraries/unix/System/Posix/Files.hsc" #-}
   exec_f  = if execOK  then (1) else 0
{-# LINE 137 "libraries/unix/System/Posix/Files.hsc" #-}
fileExist :: FilePath -> IO Bool
fileExist name =
  withFilePath name $ \s -> do
    r <- c_access s (0)
{-# LINE 145 "libraries/unix/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 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 || err == eROFS || err == eTXTBSY ||
                    err == ePERM)
                   then return False
                   else throwErrnoPath "fileAccess" name
getFileStatus :: FilePath -> IO FileStatus
getFileStatus path = do
  fp <- mallocForeignPtrBytes (144)
{-# LINE 172 "libraries/unix/System/Posix/Files.hsc" #-}
  withForeignPtr fp $ \p ->
    withFilePath path $ \s ->
      throwErrnoPathIfMinus1Retry_ "getFileStatus" path (c_stat s p)
  return (FileStatus fp)
getSymbolicLinkStatus :: FilePath -> IO FileStatus
getSymbolicLinkStatus path = do
  fp <- mallocForeignPtrBytes (144)
{-# LINE 185 "libraries/unix/System/Posix/Files.hsc" #-}
  withForeignPtr fp $ \p ->
    withFilePath path $ \s ->
      throwErrnoPathIfMinus1_ "getSymbolicLinkStatus" path (c_lstat s p)
  return (FileStatus fp)
foreign import capi unsafe "HsUnix.h lstat"
  c_lstat :: CString -> Ptr CStat -> IO CInt
createNamedPipe :: FilePath -> FileMode -> IO ()
createNamedPipe name mode = do
  withFilePath name $ \s ->
    throwErrnoPathIfMinus1_ "createNamedPipe" name (c_mkfifo s mode)
createDevice :: FilePath -> FileMode -> DeviceID -> IO ()
createDevice path mode dev =
  withFilePath path $ \s ->
    throwErrnoPathIfMinus1_ "createDevice" path (c_mknod s mode dev)
foreign import capi unsafe "HsUnix.h mknod"
  c_mknod :: CString -> CMode -> CDev -> IO CInt
createLink :: FilePath -> FilePath -> IO ()
createLink name1 name2 =
  withFilePath name1 $ \s1 ->
  withFilePath name2 $ \s2 ->
  throwErrnoPathIfMinus1_ "createLink" name1 (c_link s1 s2)
removeLink :: FilePath -> IO ()
removeLink name =
  withFilePath name $ \s ->
  throwErrnoPathIfMinus1_ "removeLink" name (c_unlink s)
createSymbolicLink :: FilePath -> FilePath -> IO ()
createSymbolicLink file1 file2 =
  withFilePath file1 $ \s1 ->
  withFilePath file2 $ \s2 ->
  throwErrnoPathIfMinus1_ "createSymbolicLink" file2 (c_symlink s1 s2)
foreign import ccall unsafe "symlink"
  c_symlink :: CString -> CString -> IO CInt
{-# LINE 269 "libraries/unix/System/Posix/Files.hsc" #-}
readSymbolicLink :: FilePath -> IO FilePath
readSymbolicLink file =
  allocaArray0 (4096) $ \buf -> do
{-# LINE 276 "libraries/unix/System/Posix/Files.hsc" #-}
    withFilePath file $ \s -> do
      len <- throwErrnoPathIfMinus1 "readSymbolicLink" file $
        c_readlink s buf (4096)
{-# LINE 279 "libraries/unix/System/Posix/Files.hsc" #-}
      peekFilePathLen (buf,fromIntegral len)
foreign import ccall unsafe "readlink"
  c_readlink :: CString -> CString -> CSize -> IO CInt
rename :: FilePath -> FilePath -> 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
setOwnerAndGroup :: FilePath -> 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
{-# LINE 317 "libraries/unix/System/Posix/Files.hsc" #-}
setSymbolicLinkOwnerAndGroup :: FilePath -> 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
{-# LINE 330 "libraries/unix/System/Posix/Files.hsc" #-}
setFileTimes :: FilePath -> EpochTime -> EpochTime -> IO ()
setFileTimes name atime mtime = do
  withFilePath name $ \s ->
   allocaBytes (16) $ \p -> do
{-# LINE 342 "libraries/unix/System/Posix/Files.hsc" #-}
     ((\hsc_ptr -> pokeByteOff hsc_ptr 0))  p atime
{-# LINE 343 "libraries/unix/System/Posix/Files.hsc" #-}
     ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p mtime
{-# LINE 344 "libraries/unix/System/Posix/Files.hsc" #-}
     throwErrnoPathIfMinus1_ "setFileTimes" name (c_utime s p)
setFileTimesHiRes :: FilePath -> POSIXTime -> POSIXTime -> IO ()
{-# LINE 353 "libraries/unix/System/Posix/Files.hsc" #-}
setFileTimesHiRes name atime mtime =
  withFilePath name $ \s ->
    withArray [toCTimeSpec atime, toCTimeSpec mtime] $ \times ->
      throwErrnoPathIfMinus1_ "setFileTimesHiRes" name $
        c_utimensat (-100) s times 0
{-# LINE 358 "libraries/unix/System/Posix/Files.hsc" #-}
{-# LINE 364 "libraries/unix/System/Posix/Files.hsc" #-}
setSymbolicLinkTimesHiRes :: FilePath -> POSIXTime -> POSIXTime -> IO ()
{-# LINE 374 "libraries/unix/System/Posix/Files.hsc" #-}
setSymbolicLinkTimesHiRes name atime mtime =
  withFilePath name $ \s ->
    withArray [toCTimeSpec atime, toCTimeSpec mtime] $ \times ->
      throwErrnoPathIfMinus1_ "setSymbolicLinkTimesHiRes" name $
        c_utimensat (-100) s times (256)
{-# LINE 379 "libraries/unix/System/Posix/Files.hsc" #-}
{-# LINE 389 "libraries/unix/System/Posix/Files.hsc" #-}
touchFile :: FilePath -> IO ()
touchFile name = do
  withFilePath name $ \s ->
   throwErrnoPathIfMinus1_ "touchFile" name (c_utime s nullPtr)
touchSymbolicLink :: FilePath -> IO ()
{-# LINE 408 "libraries/unix/System/Posix/Files.hsc" #-}
touchSymbolicLink name =
  withFilePath name $ \s ->
    throwErrnoPathIfMinus1_ "touchSymbolicLink" name (c_lutimes s nullPtr)
{-# LINE 415 "libraries/unix/System/Posix/Files.hsc" #-}
setFileSize :: FilePath -> FileOffset -> IO ()
setFileSize file off =
  withFilePath file $ \s ->
    throwErrnoPathIfMinus1_ "setFileSize" file (c_truncate s off)
foreign import capi unsafe "HsUnix.h truncate"
  c_truncate :: CString -> COff -> IO CInt
getPathVar :: FilePath -> 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