{-# LINE 1 "System/Posix/Files/PosixString.hsc" #-}
{-# LANGUAGE CApiFFI #-}
module System.Posix.Files.PosixString (
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 77 "System/Posix/Files/PosixString.hsc" #-}
setSymbolicLinkOwnerAndGroup,
{-# LINE 79 "System/Posix/Files/PosixString.hsc" #-}
setFileTimes, setFileTimesHiRes,
setSymbolicLinkTimesHiRes,
touchFile, touchFd, touchSymbolicLink,
setFileSize, setFdSize,
PathVar(..), getPathVar, getFdPathVar,
) where
import System.Posix.Types
import System.Posix.Internals hiding (withFilePath, peekFilePathLen)
import qualified System.Posix.Files.Common as Common
import Foreign
import Foreign.C hiding (
throwErrnoPath,
throwErrnoPathIf,
throwErrnoPathIf_,
throwErrnoPathIfNull,
throwErrnoPathIfMinus1,
throwErrnoPathIfMinus1_ )
import System.OsPath.Types
import System.Posix.Files hiding (getFileStatus, getSymbolicLinkStatus, createNamedPipe, createDevice, createLink, removeLink, createSymbolicLink, readSymbolicLink, rename, setOwnerAndGroup, setSymbolicLinkOwnerAndGroup, setFileTimes, setSymbolicLinkTimesHiRes, touchFile, touchSymbolicLink, setFileSize, getPathVar, setFileMode, fileAccess, fileExist, setFdTimesHiRes, setFileTimesHiRes)
import System.Posix.PosixPath.FilePath
import Data.Time.Clock.POSIX (POSIXTime)
{-# LINE 114 "System/Posix/Files/PosixString.hsc" #-}
setFileMode :: PosixPath -> FileMode -> IO ()
setFileMode name m =
withFilePath name $ \s -> do
throwErrnoPathIfMinus1_ "setFileMode" name (c_chmod s m)
fileAccess :: PosixPath -> 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 143 "System/Posix/Files/PosixString.hsc" #-}
write_f = if writeOK then (2) else 0
{-# LINE 144 "System/Posix/Files/PosixString.hsc" #-}
exec_f = if execOK then (1) else 0
{-# LINE 145 "System/Posix/Files/PosixString.hsc" #-}
fileExist :: PosixPath -> IO Bool
fileExist name =
withFilePath name $ \s -> do
r <- c_access s (0)
{-# LINE 153 "System/Posix/Files/PosixString.hsc" #-}
if (r == 0)
then return True
else do err <- getErrno
if (err == eNOENT)
then return False
else throwErrnoPath "fileExist" name
access :: PosixPath -> 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 :: PosixPath -> IO FileStatus
getFileStatus path = do
fp <- mallocForeignPtrBytes (144)
{-# LINE 180 "System/Posix/Files/PosixString.hsc" #-}
withForeignPtr fp $ \p ->
withFilePath path $ \s ->
throwErrnoPathIfMinus1Retry_ "getFileStatus" path (c_stat s p)
return (Common.FileStatus fp)
getSymbolicLinkStatus :: PosixPath -> IO FileStatus
getSymbolicLinkStatus path = do
fp <- mallocForeignPtrBytes (144)
{-# LINE 193 "System/Posix/Files/PosixString.hsc" #-}
withForeignPtr fp $ \p ->
withFilePath path $ \s ->
throwErrnoPathIfMinus1_ "getSymbolicLinkStatus" path (c_lstat s p)
return (Common.FileStatus fp)
foreign import capi unsafe "HsUnix.h lstat"
c_lstat :: CString -> Ptr CStat -> IO CInt
createNamedPipe :: PosixPath -> FileMode -> IO ()
createNamedPipe name mode = do
withFilePath name $ \s ->
throwErrnoPathIfMinus1_ "createNamedPipe" name (c_mkfifo s mode)
{-# LINE 220 "System/Posix/Files/PosixString.hsc" #-}
createDevice :: PosixPath -> 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
{-# LINE 237 "System/Posix/Files/PosixString.hsc" #-}
createLink :: PosixPath -> PosixPath -> IO ()
createLink name1 name2 =
withFilePath name1 $ \s1 ->
withFilePath name2 $ \s2 ->
throwErrnoTwoPathsIfMinus1_ "createLink" name1 name2 (c_link s1 s2)
removeLink :: PosixPath -> IO ()
removeLink name =
withFilePath name $ \s ->
throwErrnoPathIfMinus1_ "removeLink" name (c_unlink s)
createSymbolicLink :: PosixPath -> PosixPath -> IO ()
createSymbolicLink name1 name2 =
withFilePath name1 $ \s1 ->
withFilePath name2 $ \s2 ->
throwErrnoTwoPathsIfMinus1_ "createSymbolicLink" name1 name2 (c_symlink s1 s2)
foreign import ccall unsafe "symlink"
c_symlink :: CString -> CString -> IO CInt
{-# LINE 286 "System/Posix/Files/PosixString.hsc" #-}
readSymbolicLink :: PosixPath -> IO PosixPath
readSymbolicLink file =
allocaArray0 (4096) $ \buf -> do
{-# LINE 293 "System/Posix/Files/PosixString.hsc" #-}
withFilePath file $ \s -> do
len <- throwErrnoPathIfMinus1 "readSymbolicLink" file $
c_readlink s buf (4096)
{-# LINE 296 "System/Posix/Files/PosixString.hsc" #-}
peekFilePathLen (buf,fromIntegral len)
foreign import ccall unsafe "readlink"
c_readlink :: CString -> CString -> CSize -> IO CInt
rename :: PosixPath -> PosixPath -> IO ()
rename name1 name2 =
withFilePath name1 $ \s1 ->
withFilePath name2 $ \s2 ->
throwErrnoTwoPathsIfMinus1_ "rename" name1 name2 (c_rename s1 s2)
foreign import ccall unsafe "rename"
c_rename :: CString -> CString -> IO CInt
{-# LINE 320 "System/Posix/Files/PosixString.hsc" #-}
setOwnerAndGroup :: PosixPath -> 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 342 "System/Posix/Files/PosixString.hsc" #-}
{-# LINE 344 "System/Posix/Files/PosixString.hsc" #-}
setSymbolicLinkOwnerAndGroup :: PosixPath -> 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 357 "System/Posix/Files/PosixString.hsc" #-}
setFileTimes :: PosixPath -> EpochTime -> EpochTime -> IO ()
setFileTimes name atime mtime = do
withFilePath name $ \s ->
allocaBytes (16) $ \p -> do
{-# LINE 369 "System/Posix/Files/PosixString.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 0)) p atime
{-# LINE 370 "System/Posix/Files/PosixString.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p mtime
{-# LINE 371 "System/Posix/Files/PosixString.hsc" #-}
throwErrnoPathIfMinus1_ "setFileTimes" name (c_utime s p)
setFileTimesHiRes :: PosixPath -> POSIXTime -> POSIXTime -> IO ()
{-# LINE 382 "System/Posix/Files/PosixString.hsc" #-}
setFileTimesHiRes name atime mtime =
withFilePath name $ \s ->
withArray [Common.toCTimeSpec atime, Common.toCTimeSpec mtime] $ \times ->
throwErrnoPathIfMinus1_ "setFileTimesHiRes" name $
Common.c_utimensat (-100) s times 0
{-# LINE 387 "System/Posix/Files/PosixString.hsc" #-}
{-# LINE 393 "System/Posix/Files/PosixString.hsc" #-}
setSymbolicLinkTimesHiRes :: PosixPath -> POSIXTime -> POSIXTime -> IO ()
{-# LINE 405 "System/Posix/Files/PosixString.hsc" #-}
setSymbolicLinkTimesHiRes name atime mtime =
withFilePath name $ \s ->
withArray [Common.toCTimeSpec atime, Common.toCTimeSpec mtime] $ \times ->
throwErrnoPathIfMinus1_ "setSymbolicLinkTimesHiRes" name $
Common.c_utimensat (-100) s times (256)
{-# LINE 410 "System/Posix/Files/PosixString.hsc" #-}
{-# LINE 420 "System/Posix/Files/PosixString.hsc" #-}
touchFile :: PosixPath -> IO ()
touchFile name = do
withFilePath name $ \s ->
throwErrnoPathIfMinus1_ "touchFile" name (c_utime s nullPtr)
touchSymbolicLink :: PosixPath -> IO ()
{-# LINE 437 "System/Posix/Files/PosixString.hsc" #-}
touchSymbolicLink name =
withFilePath name $ \s ->
throwErrnoPathIfMinus1_ "touchSymbolicLink" name (Common.c_lutimes s nullPtr)
{-# LINE 444 "System/Posix/Files/PosixString.hsc" #-}
setFileSize :: PosixPath -> 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 :: PosixPath -> PathVar -> IO Limit
getPathVar name v = do
withFilePath name $ \ nameP ->
throwErrnoPathIfMinus1 "getPathVar" name $
c_pathconf nameP (Common.pathVarConst v)
foreign import ccall unsafe "pathconf"
c_pathconf :: CString -> CInt -> IO CLong