module Z.IO.FileSystem
(
File, initFile, readFile, writeFile, getFileFD, seek
, quickReadFile, quickReadTextFile, quickWriteFile, quickWriteTextFile
, FilePtr, newFilePtr, getFilePtrOffset, setFilePtrOffset
, mkdir, mkdirp
, unlink
, mkdtemp
, rmdir, rmdirrf
, DirEntType(..)
, scandir
, scandirRecursively
, FStat(..), UVTimeSpec(..)
, stat, lstat, fstat
, isLink, isDir, isFile
, rename
, fsync, fdatasync
, ftruncate
, copyfile
, AccessResult(..)
, access
, chmod, fchmod
, utime, futime, lutime
, link, symlink
, readlink, realpath
, chown, fchown, lchown
, AccessMode
, pattern F_OK
, pattern R_OK
, pattern W_OK
, pattern X_OK
, FileMode
, pattern DEFAULT_MODE
, pattern S_IRWXU
, pattern S_IRUSR
, pattern S_IWUSR
, pattern S_IXUSR
, pattern S_IRWXG
, pattern S_IRGRP
, pattern S_IWGRP
, pattern S_IXGRP
, pattern S_IRWXO
, pattern S_IROTH
, pattern S_IFMT
, pattern S_IFLNK
, pattern S_IFDIR
, pattern S_IFREG
, FileFlag
, pattern O_APPEND
, pattern O_CREAT
, pattern O_DIRECT
, pattern O_DSYNC
, pattern O_EXCL
, pattern O_EXLOCK
, pattern O_NOATIME
, pattern O_NOFOLLOW
, pattern O_RDONLY
, pattern O_RDWR
, pattern O_SYMLINK
, pattern O_SYNC
, pattern O_TRUNC
, pattern O_WRONLY
, pattern O_RANDOM
, pattern O_SHORT_LIVED
, pattern O_SEQUENTIAL
, pattern O_TEMPORARY
, CopyFileFlag
, pattern COPYFILE_DEFAULT
, pattern COPYFILE_EXCL
, pattern COPYFILE_FICLONE
, pattern COPYFILE_FICLONE_FORCE
, SymlinkFlag
, pattern SYMLINK_DEFAULT
, pattern SYMLINK_DIR
, pattern SYMLINK_JUNCTION
, Whence
, pattern SEEK_SET
, pattern SEEK_CUR
, pattern SEEK_END
) where
import Control.Monad
import Data.Bits
import Data.Int
import Data.IORef
import Data.Word
import Foreign.Ptr
import Foreign.Storable (peekElemOff)
import Foreign.Marshal.Alloc (allocaBytes)
import Z.Data.CBytes as CBytes
import Z.Data.PrimRef.PrimIORef
import qualified Z.Data.Text as T
import qualified Z.Data.Text.ShowT as T
import qualified Z.Data.Vector as V
import Z.Foreign
import Z.IO.Buffered
import Z.IO.Exception
import qualified Z.IO.FileSystem.FilePath as P
import Z.IO.Resource
import Z.IO.UV.FFI
import Prelude hiding (writeFile, readFile)
data File = File {-# UNPACK #-} !FD
{-# UNPACK #-} !(IORef Bool)
instance Show File where show :: File -> String
show = File -> String
forall a. ShowT a => a -> String
T.toString
instance T.ShowT File where
toUTF8BuilderP :: Int -> File -> Builder ()
toUTF8BuilderP Int
_ (File FD
fd IORef Bool
_) = Builder ()
"File " Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FD -> Builder ()
forall a. (Integral a, Bounded a) => a -> Builder ()
T.int FD
fd
getFileFD :: File -> IO FD
getFileFD :: File -> IO FD
getFileFD (File FD
fd IORef Bool
closedRef) = do
Bool
closed <- IORef Bool -> IO Bool
forall a. IORef a -> IO a
readIORef IORef Bool
closedRef
if Bool
closed then IO FD
forall a. HasCallStack => IO a
throwECLOSED else FD -> IO FD
forall (m :: * -> *) a. Monad m => a -> m a
return FD
fd
checkFileClosed :: HasCallStack => File -> (FD -> IO a) -> IO a
checkFileClosed :: File -> (FD -> IO a) -> IO a
checkFileClosed (File FD
fd IORef Bool
closedRef) FD -> IO a
f = do
Bool
closed <- IORef Bool -> IO Bool
forall a. IORef a -> IO a
readIORef IORef Bool
closedRef
if Bool
closed then IO a
forall a. HasCallStack => IO a
throwECLOSED else FD -> IO a
f FD
fd
seek :: HasCallStack => File -> Int64 -> Whence -> IO Int64
seek :: File -> Int64 -> FD -> IO Int64
seek File
uvf Int64
off FD
w = File -> (FD -> IO Int64) -> IO Int64
forall a. HasCallStack => File -> (FD -> IO a) -> IO a
checkFileClosed File
uvf ((FD -> IO Int64) -> IO Int64) -> (FD -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ \ FD
fd -> IO Int64 -> IO Int64
forall a. (HasCallStack, Integral a) => IO a -> IO a
throwUVIfMinus (IO Int64 -> IO Int64) -> IO Int64 -> IO Int64
forall a b. (a -> b) -> a -> b
$ FD -> Int64 -> FD -> IO Int64
hs_seek FD
fd Int64
off FD
w
instance Input File where
readInput :: File -> Ptr Word8 -> Int -> IO Int
readInput File
f Ptr Word8
buf Int
bufSiz = HasCallStack => File -> Ptr Word8 -> Int -> Int64 -> IO Int
File -> Ptr Word8 -> Int -> Int64 -> IO Int
readFile File
f Ptr Word8
buf Int
bufSiz (-Int64
1)
readFile :: HasCallStack
=> File
-> Ptr Word8
-> Int
-> Int64
-> IO Int
readFile :: File -> Ptr Word8 -> Int -> Int64 -> IO Int
readFile File
uvf Ptr Word8
buf Int
bufSiz Int64
off =
File -> (FD -> IO Int) -> IO Int
forall a. HasCallStack => File -> (FD -> IO a) -> IO a
checkFileClosed File
uvf ((FD -> IO Int) -> IO Int) -> (FD -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \ FD
fd -> IO Int -> IO Int
forall a. (HasCallStack, Integral a) => IO a -> IO a
throwUVIfMinus (IO Int -> IO Int) -> IO Int -> IO Int
forall a b. (a -> b) -> a -> b
$ FD -> Ptr Word8 -> Int -> Int64 -> IO Int
hs_uv_fs_read FD
fd Ptr Word8
buf Int
bufSiz Int64
off
instance Output File where
writeOutput :: File -> Ptr Word8 -> Int -> IO ()
writeOutput File
f Ptr Word8
buf Int
bufSiz = HasCallStack => File -> Ptr Word8 -> Int -> Int64 -> IO ()
File -> Ptr Word8 -> Int -> Int64 -> IO ()
writeFile File
f Ptr Word8
buf Int
bufSiz (-Int64
1)
writeFile :: HasCallStack
=> File
-> Ptr Word8
-> Int
-> Int64
-> IO ()
writeFile :: File -> Ptr Word8 -> Int -> Int64 -> IO ()
writeFile File
uvf Ptr Word8
buf0 Int
bufSiz0 Int64
off0 =
File -> (FD -> IO ()) -> IO ()
forall a. HasCallStack => File -> (FD -> IO a) -> IO a
checkFileClosed File
uvf ((FD -> IO ()) -> IO ()) -> (FD -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \FD
fd -> if Int64
off0 Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
== -Int64
1 then FD -> Ptr Word8 -> Int -> IO ()
go FD
fd Ptr Word8
buf0 Int
bufSiz0
else FD -> Ptr Word8 -> Int -> Int64 -> IO ()
go' FD
fd Ptr Word8
buf0 Int
bufSiz0 Int64
off0
where
go :: FD -> Ptr Word8 -> Int -> IO ()
go FD
fd !Ptr Word8
buf !Int
bufSiz = do
Int
written <- IO Int -> IO Int
forall a. (HasCallStack, Integral a) => IO a -> IO a
throwUVIfMinus (FD -> Ptr Word8 -> Int -> Int64 -> IO Int
hs_uv_fs_write FD
fd Ptr Word8
buf Int
bufSiz (-Int64
1))
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
written Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
bufSiz)
(FD -> Ptr Word8 -> Int -> IO ()
go FD
fd (Ptr Word8
buf Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
written) (Int
bufSizInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
written))
go' :: FD -> Ptr Word8 -> Int -> Int64 -> IO ()
go' FD
fd !Ptr Word8
buf !Int
bufSiz !Int64
off = do
Int
written <- IO Int -> IO Int
forall a. (HasCallStack, Integral a) => IO a -> IO a
throwUVIfMinus (FD -> Ptr Word8 -> Int -> Int64 -> IO Int
hs_uv_fs_write FD
fd Ptr Word8
buf Int
bufSiz Int64
off)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
written Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
bufSiz) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
FD -> Ptr Word8 -> Int -> Int64 -> IO ()
go' FD
fd (Ptr Word8
buf Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
written)
(Int
bufSizInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
written)
(Int64
offInt64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
written)
data FilePtr = FilePtr {-# UNPACK #-} !File
{-# UNPACK #-} !(PrimIORef Int64)
newFilePtr :: File
-> Int64
-> IO FilePtr
newFilePtr :: File -> Int64 -> IO FilePtr
newFilePtr File
uvf Int64
off = File -> PrimIORef Int64 -> FilePtr
FilePtr File
uvf (PrimIORef Int64 -> FilePtr) -> IO (PrimIORef Int64) -> IO FilePtr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int64 -> IO (PrimIORef Int64)
forall a. Prim a => a -> IO (PrimIORef a)
newPrimIORef Int64
off
getFilePtrOffset :: FilePtr -> IO Int64
getFilePtrOffset :: FilePtr -> IO Int64
getFilePtrOffset (FilePtr File
_ PrimIORef Int64
offsetRef) = PrimIORef Int64 -> IO Int64
forall a. Prim a => PrimIORef a -> IO a
readPrimIORef PrimIORef Int64
offsetRef
setFilePtrOffset :: FilePtr -> Int64 -> IO ()
setFilePtrOffset :: FilePtr -> Int64 -> IO ()
setFilePtrOffset (FilePtr File
_ PrimIORef Int64
offsetRef) = PrimIORef Int64 -> Int64 -> IO ()
forall a. Prim a => PrimIORef a -> a -> IO ()
writePrimIORef PrimIORef Int64
offsetRef
instance Input FilePtr where
readInput :: FilePtr -> Ptr Word8 -> Int -> IO Int
readInput (FilePtr File
file PrimIORef Int64
offsetRef) Ptr Word8
buf Int
bufSiz =
PrimIORef Int64 -> IO Int64
forall a. Prim a => PrimIORef a -> IO a
readPrimIORef PrimIORef Int64
offsetRef IO Int64 -> (Int64 -> IO Int) -> IO Int
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ Int64
off -> do
Int
l <- HasCallStack => File -> Ptr Word8 -> Int -> Int64 -> IO Int
File -> Ptr Word8 -> Int -> Int64 -> IO Int
readFile File
file Ptr Word8
buf Int
bufSiz Int64
off
PrimIORef Int64 -> Int64 -> IO ()
forall a. Prim a => PrimIORef a -> a -> IO ()
writePrimIORef PrimIORef Int64
offsetRef (Int64
off Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l)
Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
l
instance Output FilePtr where
writeOutput :: FilePtr -> Ptr Word8 -> Int -> IO ()
writeOutput (FilePtr File
file PrimIORef Int64
offsetRef) Ptr Word8
buf Int
bufSiz =
PrimIORef Int64 -> IO Int64
forall a. Prim a => PrimIORef a -> IO a
readPrimIORef PrimIORef Int64
offsetRef IO Int64 -> (Int64 -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ Int64
off -> do
HasCallStack => File -> Ptr Word8 -> Int -> Int64 -> IO ()
File -> Ptr Word8 -> Int -> Int64 -> IO ()
writeFile File
file Ptr Word8
buf Int
bufSiz Int64
off
PrimIORef Int64 -> Int64 -> IO ()
forall a. Prim a => PrimIORef a -> a -> IO ()
writePrimIORef PrimIORef Int64
offsetRef (Int64
off Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
bufSiz)
initFile :: CBytes
-> FileFlag
-> FileMode
-> Resource File
initFile :: CBytes -> FD -> FD -> Resource File
initFile CBytes
path FD
flags FD
mode =
IO File -> (File -> IO ()) -> Resource File
forall a. IO a -> (a -> IO ()) -> Resource a
initResource
(do !FD
fd <- CBytes -> (BA# Word8 -> IO FD) -> IO FD
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO FD) -> IO FD) -> (BA# Word8 -> IO FD) -> IO FD
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
IO FD -> IO FD
forall a. (HasCallStack, Integral a) => IO a -> IO a
throwUVIfMinus (IO FD -> IO FD) -> IO FD -> IO FD
forall a b. (a -> b) -> a -> b
$ BA# Word8 -> FD -> FD -> IO FD
hs_uv_fs_open BA# Word8
p FD
flags FD
mode
FD -> IORef Bool -> File
File FD
fd (IORef Bool -> File) -> IO (IORef Bool) -> IO File
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> IO (IORef Bool)
forall a. a -> IO (IORef a)
newIORef Bool
False)
(\ (File FD
fd IORef Bool
closedRef) -> do
Bool
closed <- IORef Bool -> IO Bool
forall a. IORef a -> IO a
readIORef IORef Bool
closedRef
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
closed (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (FD -> IO Int
hs_uv_fs_close FD
fd)
IORef Bool -> Bool -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Bool
closedRef Bool
True)
quickReadFile :: HasCallStack => CBytes -> IO V.Bytes
quickReadFile :: CBytes -> IO Bytes
quickReadFile CBytes
filename = do
Resource File -> (File -> IO Bytes) -> IO Bytes
forall (m :: * -> *) a b.
(MonadMask m, MonadIO m, HasCallStack) =>
Resource a -> (a -> m b) -> m b
withResource (CBytes -> FD -> FD -> Resource File
initFile CBytes
filename FD
O_RDONLY FD
DEFAULT_MODE) ((File -> IO Bytes) -> IO Bytes) -> (File -> IO Bytes) -> IO Bytes
forall a b. (a -> b) -> a -> b
$ \ File
file -> do
HasCallStack => BufferedInput -> IO Bytes
BufferedInput -> IO Bytes
readAll' (BufferedInput -> IO Bytes) -> IO BufferedInput -> IO Bytes
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< File -> IO BufferedInput
forall i. Input i => i -> IO BufferedInput
newBufferedInput File
file
quickReadTextFile :: HasCallStack => CBytes -> IO T.Text
quickReadTextFile :: CBytes -> IO Text
quickReadTextFile CBytes
filename = HasCallStack => Bytes -> Text
Bytes -> Text
T.validate (Bytes -> Text) -> IO Bytes -> IO Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HasCallStack => CBytes -> IO Bytes
CBytes -> IO Bytes
quickReadFile CBytes
filename
quickWriteFile :: HasCallStack => CBytes -> V.Bytes -> IO ()
quickWriteFile :: CBytes -> Bytes -> IO ()
quickWriteFile CBytes
filename Bytes
content = do
Resource File -> (File -> IO ()) -> IO ()
forall (m :: * -> *) a b.
(MonadMask m, MonadIO m, HasCallStack) =>
Resource a -> (a -> m b) -> m b
withResource (CBytes -> FD -> FD -> Resource File
initFile CBytes
filename (FD
O_WRONLY FD -> FD -> FD
forall a. Bits a => a -> a -> a
.|. FD
O_CREAT) FD
DEFAULT_MODE) ((File -> IO ()) -> IO ()) -> (File -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ File
file -> do
Bytes -> (Ptr Word8 -> Int -> IO ()) -> IO ()
forall a b.
Prim a =>
PrimVector a -> (Ptr a -> Int -> IO b) -> IO b
withPrimVectorSafe Bytes
content (File -> Ptr Word8 -> Int -> IO ()
forall o.
(Output o, HasCallStack) =>
o -> Ptr Word8 -> Int -> IO ()
writeOutput File
file)
quickWriteTextFile :: HasCallStack => CBytes -> T.Text -> IO ()
quickWriteTextFile :: CBytes -> Text -> IO ()
quickWriteTextFile CBytes
filename Text
content = HasCallStack => CBytes -> Bytes -> IO ()
CBytes -> Bytes -> IO ()
quickWriteFile CBytes
filename (Text -> Bytes
T.getUTF8Bytes Text
content)
mkdir :: HasCallStack => CBytes -> FileMode -> IO ()
mkdir :: CBytes -> FD -> IO ()
mkdir CBytes
path FD
mode = IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO Int -> IO ())
-> ((BA# Word8 -> IO Int) -> IO Int)
-> (BA# Word8 -> IO Int)
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO Int) -> IO ()) -> (BA# Word8 -> IO Int) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
BA# Word8 -> FD -> IO Int
hs_uv_fs_mkdir BA# Word8
p FD
mode
mkdirp :: HasCallStack => CBytes -> FileMode -> IO ()
mkdirp :: CBytes -> FD -> IO ()
mkdirp CBytes
path FD
mode = do
Int
r <- CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO Int) -> IO Int)
-> (BA# Word8 -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p -> BA# Word8 -> FD -> IO Int
hs_uv_fs_mkdir BA# Word8
p FD
mode
if Int -> FD
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
r FD -> FD -> Bool
forall a. Eq a => a -> a -> Bool
== FD
UV_ENOENT
then do
(CBytes
root, [CBytes]
segs) <- CBytes -> IO (CBytes, [CBytes])
P.splitSegments CBytes
path
case [CBytes]
segs of
CBytes
seg:[CBytes]
segs' -> [CBytes] -> CBytes -> IO ()
loop [CBytes]
segs' (CBytes -> IO ()) -> IO CBytes -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< CBytes -> CBytes -> IO CBytes
P.join CBytes
root CBytes
seg
[CBytes]
_ -> IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
r)
else IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
r)
where
loop :: [CBytes] -> CBytes -> IO ()
loop [CBytes]
segs CBytes
p = do
AccessResult
a <- HasCallStack => CBytes -> FD -> IO AccessResult
CBytes -> FD -> IO AccessResult
access CBytes
p FD
F_OK
case AccessResult
a of
AccessResult
AccessOK -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
AccessResult
NoExistence -> HasCallStack => CBytes -> FD -> IO ()
CBytes -> FD -> IO ()
mkdir CBytes
p FD
mode
AccessResult
NoPermission -> IO FD -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (FD -> IO FD
forall (m :: * -> *) a. Monad m => a -> m a
return FD
UV_EACCES)
case [CBytes]
segs of
(CBytes
nextp:[CBytes]
ps) -> CBytes -> CBytes -> IO CBytes
P.join CBytes
p CBytes
nextp IO CBytes -> (CBytes -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [CBytes] -> CBytes -> IO ()
loop [CBytes]
ps
[CBytes]
_ -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
unlink :: HasCallStack => CBytes -> IO ()
unlink :: CBytes -> IO ()
unlink CBytes
path = IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path BA# Word8 -> IO Int
hs_uv_fs_unlink)
mkdtemp :: HasCallStack => CBytes -> IO CBytes
mkdtemp :: CBytes -> IO CBytes
mkdtemp CBytes
path = do
let size :: Int
size = CBytes -> Int
CBytes.length CBytes
path
CBytes -> (BA# Word8 -> IO CBytes) -> IO CBytes
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO CBytes) -> IO CBytes)
-> (BA# Word8 -> IO CBytes) -> IO CBytes
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p -> do
(CBytes
p',()
_) <- Int -> (MBA# Word8 -> IO ()) -> IO (CBytes, ())
forall a.
HasCallStack =>
Int -> (MBA# Word8 -> IO a) -> IO (CBytes, a)
CBytes.allocCBytesUnsafe (Int
sizeInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
7) ((MBA# Word8 -> IO ()) -> IO (CBytes, ()))
-> (MBA# Word8 -> IO ()) -> IO (CBytes, ())
forall a b. (a -> b) -> a -> b
$ \ MBA# Word8
p' -> do
IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (BA# Word8 -> Int -> MBA# Word8 -> IO Int
hs_uv_fs_mkdtemp BA# Word8
p Int
size MBA# Word8
p')
CBytes -> IO CBytes
forall (m :: * -> *) a. Monad m => a -> m a
return CBytes
p'
rmdir :: HasCallStack => CBytes -> IO ()
rmdir :: CBytes -> IO ()
rmdir CBytes
path = IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path BA# Word8 -> IO Int
hs_uv_fs_rmdir)
rmdirrf :: HasCallStack => CBytes -> IO ()
rmdirrf :: CBytes -> IO ()
rmdirrf CBytes
path = do
[(CBytes, DirEntType)]
ds <- HasCallStack => CBytes -> IO [(CBytes, DirEntType)]
CBytes -> IO [(CBytes, DirEntType)]
scandir CBytes
path
[(CBytes, DirEntType)] -> ((CBytes, DirEntType) -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [(CBytes, DirEntType)]
ds (((CBytes, DirEntType) -> IO ()) -> IO ())
-> ((CBytes, DirEntType) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ (CBytes
d, DirEntType
t) -> do
if DirEntType
t DirEntType -> DirEntType -> Bool
forall a. Eq a => a -> a -> Bool
/= DirEntType
DirEntDir
then HasCallStack => CBytes -> IO ()
CBytes -> IO ()
unlink CBytes
d
else HasCallStack => CBytes -> IO ()
CBytes -> IO ()
rmdirrf (CBytes -> IO ()) -> IO CBytes -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< CBytes
path CBytes -> CBytes -> IO CBytes
`P.join` CBytes
d
HasCallStack => CBytes -> IO ()
CBytes -> IO ()
rmdir CBytes
path
scandir :: HasCallStack => CBytes -> IO [(CBytes, DirEntType)]
scandir :: CBytes -> IO [(CBytes, DirEntType)]
scandir CBytes
path = do
IO (Ptr (Ptr DirEntType), Int)
-> ((Ptr (Ptr DirEntType), Int) -> IO ())
-> ((Ptr (Ptr DirEntType), Int) -> IO [(CBytes, DirEntType)])
-> IO [(CBytes, DirEntType)]
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
(CBytes
-> (BA# Word8 -> IO (Ptr (Ptr DirEntType), Int))
-> IO (Ptr (Ptr DirEntType), Int)
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO (Ptr (Ptr DirEntType), Int))
-> IO (Ptr (Ptr DirEntType), Int))
-> (BA# Word8 -> IO (Ptr (Ptr DirEntType), Int))
-> IO (Ptr (Ptr DirEntType), Int)
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
(MBA# Word8 -> IO Int) -> IO (Ptr (Ptr DirEntType), Int)
forall a b. Prim a => (MBA# Word8 -> IO b) -> IO (a, b)
allocPrimUnsafe ((MBA# Word8 -> IO Int) -> IO (Ptr (Ptr DirEntType), Int))
-> (MBA# Word8 -> IO Int) -> IO (Ptr (Ptr DirEntType), Int)
forall a b. (a -> b) -> a -> b
$ \ MBA# Word8
dents ->
IO Int -> IO Int
forall a. (HasCallStack, Integral a) => IO a -> IO a
throwUVIfMinus (BA# Word8 -> MBA# Word8 -> IO Int
hs_uv_fs_scandir BA# Word8
p MBA# Word8
dents))
(\ (Ptr (Ptr DirEntType)
dents, Int
n) -> Ptr (Ptr DirEntType) -> Int -> IO ()
hs_uv_fs_scandir_cleanup Ptr (Ptr DirEntType)
dents Int
n)
(\ (Ptr (Ptr DirEntType)
dents, Int
n) -> [Int]
-> (Int -> IO (CBytes, DirEntType)) -> IO [(CBytes, DirEntType)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Int
0..Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1] ((Int -> IO (CBytes, DirEntType)) -> IO [(CBytes, DirEntType)])
-> (Int -> IO (CBytes, DirEntType)) -> IO [(CBytes, DirEntType)]
forall a b. (a -> b) -> a -> b
$ \ Int
i -> do
Ptr DirEntType
dent <- Ptr (Ptr DirEntType) -> Int -> IO (Ptr DirEntType)
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr (Ptr DirEntType)
dents Int
i
(CString
p, UVDirEntType
typ) <- Ptr DirEntType -> IO (CString, UVDirEntType)
peekUVDirEnt Ptr DirEntType
dent
let !typ' :: DirEntType
typ' = UVDirEntType -> DirEntType
fromUVDirEntType UVDirEntType
typ
!CBytes
p' <- CString -> IO CBytes
fromCString CString
p
(CBytes, DirEntType) -> IO (CBytes, DirEntType)
forall (m :: * -> *) a. Monad m => a -> m a
return (CBytes
p', DirEntType
typ'))
scandirRecursively :: HasCallStack => CBytes -> (CBytes -> DirEntType -> IO Bool) -> IO [CBytes]
scandirRecursively :: CBytes -> (CBytes -> DirEntType -> IO Bool) -> IO [CBytes]
scandirRecursively CBytes
dir CBytes -> DirEntType -> IO Bool
p = [CBytes] -> CBytes -> IO [CBytes]
loop [] (CBytes -> IO [CBytes]) -> IO CBytes -> IO [CBytes]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< CBytes -> IO CBytes
P.normalize CBytes
dir
where
loop :: [CBytes] -> CBytes -> IO [CBytes]
loop [CBytes]
acc0 CBytes
pdir =
([CBytes] -> (CBytes, DirEntType) -> IO [CBytes])
-> [CBytes] -> [(CBytes, DirEntType)] -> IO [CBytes]
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM (\ [CBytes]
acc (CBytes
d,DirEntType
t) -> do
CBytes
d' <- CBytes
pdir CBytes -> CBytes -> IO CBytes
`P.join` CBytes
d
Bool
r <- CBytes -> DirEntType -> IO Bool
p CBytes
d' DirEntType
t
let acc' :: [CBytes]
acc' = if Bool
r then (CBytes
d'CBytes -> [CBytes] -> [CBytes]
forall a. a -> [a] -> [a]
:[CBytes]
acc) else [CBytes]
acc
if (DirEntType
t DirEntType -> DirEntType -> Bool
forall a. Eq a => a -> a -> Bool
== DirEntType
DirEntDir)
then [CBytes] -> CBytes -> IO [CBytes]
loop [CBytes]
acc' CBytes
d'
else [CBytes] -> IO [CBytes]
forall (m :: * -> *) a. Monad m => a -> m a
return [CBytes]
acc'
) [CBytes]
acc0 ([(CBytes, DirEntType)] -> IO [CBytes])
-> IO [(CBytes, DirEntType)] -> IO [CBytes]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< HasCallStack => CBytes -> IO [(CBytes, DirEntType)]
CBytes -> IO [(CBytes, DirEntType)]
scandir CBytes
pdir
stat :: HasCallStack => CBytes -> IO FStat
stat :: CBytes -> IO FStat
stat CBytes
path = CBytes -> (BA# Word8 -> IO FStat) -> IO FStat
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO FStat) -> IO FStat)
-> (BA# Word8 -> IO FStat) -> IO FStat
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
Int -> (Ptr FStat -> IO FStat) -> IO FStat
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
uvStatSize ((Ptr FStat -> IO FStat) -> IO FStat)
-> (Ptr FStat -> IO FStat) -> IO FStat
forall a b. (a -> b) -> a -> b
$ \ Ptr FStat
s -> do
IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (BA# Word8 -> Ptr FStat -> IO Int
hs_uv_fs_stat BA# Word8
p Ptr FStat
s)
Ptr FStat -> IO FStat
peekUVStat Ptr FStat
s
lstat :: HasCallStack => CBytes -> IO FStat
lstat :: CBytes -> IO FStat
lstat CBytes
path = CBytes -> (BA# Word8 -> IO FStat) -> IO FStat
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO FStat) -> IO FStat)
-> (BA# Word8 -> IO FStat) -> IO FStat
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
Int -> (Ptr FStat -> IO FStat) -> IO FStat
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
uvStatSize ((Ptr FStat -> IO FStat) -> IO FStat)
-> (Ptr FStat -> IO FStat) -> IO FStat
forall a b. (a -> b) -> a -> b
$ \ Ptr FStat
s -> do
IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (BA# Word8 -> Ptr FStat -> IO Int
hs_uv_fs_lstat BA# Word8
p Ptr FStat
s)
Ptr FStat -> IO FStat
peekUVStat Ptr FStat
s
fstat :: HasCallStack => File -> IO FStat
fstat :: File -> IO FStat
fstat File
uvf = File -> (FD -> IO FStat) -> IO FStat
forall a. HasCallStack => File -> (FD -> IO a) -> IO a
checkFileClosed File
uvf ((FD -> IO FStat) -> IO FStat) -> (FD -> IO FStat) -> IO FStat
forall a b. (a -> b) -> a -> b
$ \ FD
fd ->
Int -> (Ptr FStat -> IO FStat) -> IO FStat
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
uvStatSize ((Ptr FStat -> IO FStat) -> IO FStat)
-> (Ptr FStat -> IO FStat) -> IO FStat
forall a b. (a -> b) -> a -> b
$ \ Ptr FStat
s -> do
IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (FD -> Ptr FStat -> IO Int
hs_uv_fs_fstat FD
fd Ptr FStat
s)
Ptr FStat -> IO FStat
peekUVStat Ptr FStat
s
isLink :: HasCallStack => CBytes -> IO Bool
isLink :: CBytes -> IO Bool
isLink CBytes
p = HasCallStack => CBytes -> IO FStat
CBytes -> IO FStat
lstat CBytes
p IO FStat -> (FStat -> IO Bool) -> IO Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ FStat
st -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (FStat -> FD
stMode FStat
st FD -> FD -> FD
forall a. Bits a => a -> a -> a
.&. FD
S_IFMT FD -> FD -> Bool
forall a. Eq a => a -> a -> Bool
== FD
S_IFLNK)
isDir :: HasCallStack => CBytes -> IO Bool
isDir :: CBytes -> IO Bool
isDir CBytes
p = HasCallStack => CBytes -> IO FStat
CBytes -> IO FStat
stat CBytes
p IO FStat -> (FStat -> IO Bool) -> IO Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ FStat
st -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (FStat -> FD
stMode FStat
st FD -> FD -> FD
forall a. Bits a => a -> a -> a
.&. FD
S_IFMT FD -> FD -> Bool
forall a. Eq a => a -> a -> Bool
== FD
S_IFDIR)
isFile :: HasCallStack => CBytes -> IO Bool
isFile :: CBytes -> IO Bool
isFile CBytes
p = HasCallStack => CBytes -> IO FStat
CBytes -> IO FStat
stat CBytes
p IO FStat -> (FStat -> IO Bool) -> IO Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ FStat
st -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (FStat -> FD
stMode FStat
st FD -> FD -> FD
forall a. Bits a => a -> a -> a
.&. FD
S_IFMT FD -> FD -> Bool
forall a. Eq a => a -> a -> Bool
== FD
S_IFREG)
rename :: HasCallStack => CBytes -> CBytes -> IO ()
rename :: CBytes -> CBytes -> IO ()
rename CBytes
path CBytes
path' = IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO Int -> IO ())
-> ((BA# Word8 -> IO Int) -> IO Int)
-> (BA# Word8 -> IO Int)
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO Int) -> IO ()) -> (BA# Word8 -> IO Int) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path' (BA# Word8 -> BA# Word8 -> IO Int
hs_uv_fs_rename BA# Word8
p)
fsync :: HasCallStack => File -> IO ()
fsync :: File -> IO ()
fsync File
uvf = File -> (FD -> IO ()) -> IO ()
forall a. HasCallStack => File -> (FD -> IO a) -> IO a
checkFileClosed File
uvf ((FD -> IO ()) -> IO ()) -> (FD -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ FD
fd -> IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO Int -> IO ()) -> IO Int -> IO ()
forall a b. (a -> b) -> a -> b
$ FD -> IO Int
hs_uv_fs_fsync FD
fd
fdatasync :: HasCallStack => File -> IO ()
fdatasync :: File -> IO ()
fdatasync File
uvf = File -> (FD -> IO ()) -> IO ()
forall a. HasCallStack => File -> (FD -> IO a) -> IO a
checkFileClosed File
uvf ((FD -> IO ()) -> IO ()) -> (FD -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ FD
fd -> IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO Int -> IO ()) -> IO Int -> IO ()
forall a b. (a -> b) -> a -> b
$ FD -> IO Int
hs_uv_fs_fdatasync FD
fd
ftruncate :: HasCallStack => File -> Int64 -> IO ()
ftruncate :: File -> Int64 -> IO ()
ftruncate File
uvf Int64
off = File -> (FD -> IO ()) -> IO ()
forall a. HasCallStack => File -> (FD -> IO a) -> IO a
checkFileClosed File
uvf ((FD -> IO ()) -> IO ()) -> (FD -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ FD
fd -> IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO Int -> IO ()) -> IO Int -> IO ()
forall a b. (a -> b) -> a -> b
$ FD -> Int64 -> IO Int
hs_uv_fs_ftruncate FD
fd Int64
off
copyfile :: HasCallStack => CBytes -> CBytes -> CopyFileFlag -> IO ()
copyfile :: CBytes -> CBytes -> FD -> IO ()
copyfile CBytes
path CBytes
path' FD
flag = IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO Int -> IO ())
-> ((BA# Word8 -> IO Int) -> IO Int)
-> (BA# Word8 -> IO Int)
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO Int) -> IO ()) -> (BA# Word8 -> IO Int) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path' ((BA# Word8 -> IO Int) -> IO Int)
-> (BA# Word8 -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p' -> BA# Word8 -> BA# Word8 -> FD -> IO Int
hs_uv_fs_copyfile BA# Word8
p BA# Word8
p' FD
flag
access :: HasCallStack => CBytes -> AccessMode -> IO AccessResult
access :: CBytes -> FD -> IO AccessResult
access CBytes
path FD
mode = do
FD
r <- CBytes -> (BA# Word8 -> IO FD) -> IO FD
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO FD) -> IO FD) -> (BA# Word8 -> IO FD) -> IO FD
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p -> Int -> FD
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> FD) -> IO Int -> IO FD
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> BA# Word8 -> FD -> IO Int
hs_uv_fs_access BA# Word8
p FD
mode
if | FD
r FD -> FD -> Bool
forall a. Eq a => a -> a -> Bool
== FD
0 -> AccessResult -> IO AccessResult
forall (m :: * -> *) a. Monad m => a -> m a
return AccessResult
AccessOK
| FD
r FD -> FD -> Bool
forall a. Eq a => a -> a -> Bool
== FD
UV_ENOENT -> AccessResult -> IO AccessResult
forall (m :: * -> *) a. Monad m => a -> m a
return AccessResult
NoExistence
| FD
r FD -> FD -> Bool
forall a. Eq a => a -> a -> Bool
== FD
UV_EACCES -> AccessResult -> IO AccessResult
forall (m :: * -> *) a. Monad m => a -> m a
return AccessResult
NoPermission
| Bool
otherwise -> do
Text
name <- FD -> IO Text
uvErrName FD
r
Text
desc <- FD -> IO Text
uvStdError FD
r
FD -> IOEInfo -> IO AccessResult
forall a. FD -> IOEInfo -> IO a
throwUVError FD
r (Text -> Text -> CallStack -> IOEInfo
IOEInfo Text
name Text
desc CallStack
HasCallStack => CallStack
callStack)
chmod :: HasCallStack => CBytes -> FileMode -> IO ()
chmod :: CBytes -> FD -> IO ()
chmod CBytes
path FD
mode = IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO Int -> IO ())
-> ((BA# Word8 -> IO Int) -> IO Int)
-> (BA# Word8 -> IO Int)
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO Int) -> IO ()) -> (BA# Word8 -> IO Int) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p -> BA# Word8 -> FD -> IO Int
hs_uv_fs_chmod BA# Word8
p FD
mode
fchmod :: HasCallStack => File -> FileMode -> IO ()
fchmod :: File -> FD -> IO ()
fchmod File
uvf FD
mode = File -> (FD -> IO ()) -> IO ()
forall a. HasCallStack => File -> (FD -> IO a) -> IO a
checkFileClosed File
uvf ((FD -> IO ()) -> IO ()) -> (FD -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ FD
fd -> IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO Int -> IO ()) -> IO Int -> IO ()
forall a b. (a -> b) -> a -> b
$ FD -> FD -> IO Int
hs_uv_fs_fchmod FD
fd FD
mode
utime :: HasCallStack
=> CBytes
-> Double
-> Double
-> IO ()
utime :: CBytes -> Double -> Double -> IO ()
utime CBytes
path Double
atime Double
mtime = IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO Int -> IO ())
-> ((BA# Word8 -> IO Int) -> IO Int)
-> (BA# Word8 -> IO Int)
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO Int) -> IO ()) -> (BA# Word8 -> IO Int) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p -> BA# Word8 -> Double -> Double -> IO Int
hs_uv_fs_utime BA# Word8
p Double
atime Double
mtime
futime :: HasCallStack => File -> Double -> Double -> IO ()
futime :: File -> Double -> Double -> IO ()
futime File
uvf Double
atime Double
mtime = File -> (FD -> IO ()) -> IO ()
forall a. HasCallStack => File -> (FD -> IO a) -> IO a
checkFileClosed File
uvf ((FD -> IO ()) -> IO ()) -> (FD -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ FD
fd ->
IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (FD -> Double -> Double -> IO Int
hs_uv_fs_futime FD
fd Double
atime Double
mtime)
lutime :: HasCallStack
=> CBytes
-> Double
-> Double
-> IO ()
lutime :: CBytes -> Double -> Double -> IO ()
lutime CBytes
path Double
atime Double
mtime = IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO Int -> IO ())
-> ((BA# Word8 -> IO Int) -> IO Int)
-> (BA# Word8 -> IO Int)
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO Int) -> IO ()) -> (BA# Word8 -> IO Int) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p -> BA# Word8 -> Double -> Double -> IO Int
hs_uv_fs_lutime BA# Word8
p Double
atime Double
mtime
link :: HasCallStack => CBytes -> CBytes -> IO ()
link :: CBytes -> CBytes -> IO ()
link CBytes
path CBytes
path' = IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO Int -> IO ())
-> ((BA# Word8 -> IO Int) -> IO Int)
-> (BA# Word8 -> IO Int)
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO Int) -> IO ()) -> (BA# Word8 -> IO Int) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path' ((BA# Word8 -> IO Int) -> IO Int)
-> (BA# Word8 -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ BA# Word8 -> BA# Word8 -> IO Int
hs_uv_fs_link BA# Word8
p
symlink :: HasCallStack => CBytes -> CBytes -> SymlinkFlag -> IO ()
symlink :: CBytes -> CBytes -> FD -> IO ()
symlink CBytes
path CBytes
path' FD
flag = IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO Int -> IO ())
-> ((BA# Word8 -> IO Int) -> IO Int)
-> (BA# Word8 -> IO Int)
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO Int) -> IO ()) -> (BA# Word8 -> IO Int) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path' ((BA# Word8 -> IO Int) -> IO Int)
-> (BA# Word8 -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p' -> BA# Word8 -> BA# Word8 -> FD -> IO Int
hs_uv_fs_symlink BA# Word8
p BA# Word8
p' FD
flag
readlink :: HasCallStack => CBytes -> IO CBytes
readlink :: CBytes -> IO CBytes
readlink CBytes
path = do
IO (CString, Int)
-> ((CString, Int) -> IO ())
-> ((CString, Int) -> IO CBytes)
-> IO CBytes
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
(CBytes -> (BA# Word8 -> IO (CString, Int)) -> IO (CString, Int)
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO (CString, Int)) -> IO (CString, Int))
-> (BA# Word8 -> IO (CString, Int)) -> IO (CString, Int)
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
(MBA# Word8 -> IO Int) -> IO (CString, Int)
forall a b. Prim a => (MBA# Word8 -> IO b) -> IO (a, b)
allocPrimUnsafe ((MBA# Word8 -> IO Int) -> IO (CString, Int))
-> (MBA# Word8 -> IO Int) -> IO (CString, Int)
forall a b. (a -> b) -> a -> b
$ \ MBA# Word8
p' ->
IO Int -> IO Int
forall a. (HasCallStack, Integral a) => IO a -> IO a
throwUVIfMinus (BA# Word8 -> MBA# Word8 -> IO Int
hs_uv_fs_readlink BA# Word8
p MBA# Word8
p'))
(CString -> IO ()
hs_uv_fs_readlink_cleanup (CString -> IO ())
-> ((CString, Int) -> CString) -> (CString, Int) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CString, Int) -> CString
forall a b. (a, b) -> a
fst)
(CString -> IO CBytes
fromCString (CString -> IO CBytes)
-> ((CString, Int) -> CString) -> (CString, Int) -> IO CBytes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CString, Int) -> CString
forall a b. (a, b) -> a
fst)
realpath :: HasCallStack => CBytes -> IO CBytes
realpath :: CBytes -> IO CBytes
realpath CBytes
path = do
IO (CString, Int)
-> ((CString, Int) -> IO ())
-> ((CString, Int) -> IO CBytes)
-> IO CBytes
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket
(CBytes -> (BA# Word8 -> IO (CString, Int)) -> IO (CString, Int)
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO (CString, Int)) -> IO (CString, Int))
-> (BA# Word8 -> IO (CString, Int)) -> IO (CString, Int)
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
(MBA# Word8 -> IO Int) -> IO (CString, Int)
forall a b. Prim a => (MBA# Word8 -> IO b) -> IO (a, b)
allocPrimUnsafe ((MBA# Word8 -> IO Int) -> IO (CString, Int))
-> (MBA# Word8 -> IO Int) -> IO (CString, Int)
forall a b. (a -> b) -> a -> b
$ \ MBA# Word8
p' ->
IO Int -> IO Int
forall a. (HasCallStack, Integral a) => IO a -> IO a
throwUVIfMinus (BA# Word8 -> MBA# Word8 -> IO Int
hs_uv_fs_realpath BA# Word8
p MBA# Word8
p'))
(CString -> IO ()
hs_uv_fs_readlink_cleanup (CString -> IO ())
-> ((CString, Int) -> CString) -> (CString, Int) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CString, Int) -> CString
forall a b. (a, b) -> a
fst)
(CString -> IO CBytes
fromCString (CString -> IO CBytes)
-> ((CString, Int) -> CString) -> (CString, Int) -> IO CBytes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CString, Int) -> CString
forall a b. (a, b) -> a
fst)
chown :: HasCallStack => CBytes -> UID -> GID -> IO ()
chown :: CBytes -> UID -> GID -> IO ()
chown CBytes
path UID
uid GID
gid = IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO Int -> IO ())
-> ((BA# Word8 -> IO Int) -> IO Int)
-> (BA# Word8 -> IO Int)
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO Int) -> IO ()) -> (BA# Word8 -> IO Int) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p -> BA# Word8 -> UID -> GID -> IO Int
hs_uv_fs_chown BA# Word8
p UID
uid GID
gid
fchown :: HasCallStack => File -> UID -> GID -> IO ()
fchown :: File -> UID -> GID -> IO ()
fchown File
uvf UID
uid GID
gid = File -> (FD -> IO ()) -> IO ()
forall a. HasCallStack => File -> (FD -> IO a) -> IO a
checkFileClosed File
uvf ((FD -> IO ()) -> IO ()) -> (FD -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ FD
fd -> IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO Int -> IO ()) -> IO Int -> IO ()
forall a b. (a -> b) -> a -> b
$ FD -> UID -> GID -> IO Int
hs_uv_fs_fchown FD
fd UID
uid GID
gid
lchown :: HasCallStack => CBytes -> UID -> GID -> IO ()
lchown :: CBytes -> UID -> GID -> IO ()
lchown CBytes
path UID
uid GID
gid = IO Int -> IO ()
forall a. (HasCallStack, Integral a) => IO a -> IO ()
throwUVIfMinus_ (IO Int -> IO ())
-> ((BA# Word8 -> IO Int) -> IO Int)
-> (BA# Word8 -> IO Int)
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CBytes -> (BA# Word8 -> IO Int) -> IO Int
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO Int) -> IO ()) -> (BA# Word8 -> IO Int) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p -> BA# Word8 -> UID -> GID -> IO Int
hs_uv_fs_lchown BA# Word8
p UID
uid GID
gid