{-# LINE 1 "libraries/unix/System/Posix/Files.hsc" #-}
{-# LANGUAGE Safe #-}
{-# 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,
fileBlockSize,
fileBlocks,
createNamedPipe,
createDevice,
createLink, removeLink,
createSymbolicLink, readSymbolicLink,
rename,
setOwnerAndGroup, setFdOwnerAndGroup,
{-# LINE 81 "libraries/unix/System/Posix/Files.hsc" #-}
setSymbolicLinkOwnerAndGroup,
{-# LINE 83 "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
{-# LINE 108 "libraries/unix/System/Posix/Files.hsc" #-}
import Data.Time.Clock.POSIX (POSIXTime)
{-# LINE 115 "libraries/unix/System/Posix/Files.hsc" #-}
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
"'")
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)
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 150 "libraries/unix/System/Posix/Files.hsc" #-}
write_f = if writeOK then (2) else 0
{-# LINE 151 "libraries/unix/System/Posix/Files.hsc" #-}
exec_f = if execOK then (1) else 0
{-# LINE 152 "libraries/unix/System/Posix/Files.hsc" #-}
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 160 "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 :: 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 :: 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 187 "libraries/unix/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)
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 200 "libraries/unix/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 :: 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 227 "libraries/unix/System/Posix/Files.hsc" #-}
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 244 "libraries/unix/System/Posix/Files.hsc" #-}
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 :: 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)
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
{-# LINE 293 "libraries/unix/System/Posix/Files.hsc" #-}
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 300 "libraries/unix/System/Posix/Files.hsc" #-}
withFilePath file $ \s -> do
len <- throwErrnoPathIfMinus1 "readSymbolicLink" file $
c_readlink s buf (4096)
{-# LINE 303 "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 :: 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
{-# LINE 327 "libraries/unix/System/Posix/Files.hsc" #-}
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 349 "libraries/unix/System/Posix/Files.hsc" #-}
{-# LINE 351 "libraries/unix/System/Posix/Files.hsc" #-}
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 364 "libraries/unix/System/Posix/Files.hsc" #-}
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 376 "libraries/unix/System/Posix/Files.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 0)) p atime
{-# LINE 377 "libraries/unix/System/Posix/Files.hsc" #-}
((\hsc_ptr -> pokeByteOff hsc_ptr 8)) p mtime
{-# LINE 378 "libraries/unix/System/Posix/Files.hsc" #-}
throwErrnoPathIfMinus1_ "setFileTimes" name (c_utime s p)
setFileTimesHiRes :: FilePath -> POSIXTime -> POSIXTime -> IO ()
{-# LINE 390 "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 395 "libraries/unix/System/Posix/Files.hsc" #-}
{-# LINE 401 "libraries/unix/System/Posix/Files.hsc" #-}
setSymbolicLinkTimesHiRes :: FilePath -> POSIXTime -> POSIXTime -> IO ()
{-# LINE 414 "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 419 "libraries/unix/System/Posix/Files.hsc" #-}
{-# LINE 432 "libraries/unix/System/Posix/Files.hsc" #-}
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)
touchSymbolicLink :: FilePath -> IO ()
{-# LINE 451 "libraries/unix/System/Posix/Files.hsc" #-}
touchSymbolicLink name =
withFilePath name $ \s ->
throwErrnoPathIfMinus1_ "touchSymbolicLink" name (c_lutimes s nullPtr)
{-# LINE 461 "libraries/unix/System/Posix/Files.hsc" #-}
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
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