module Z.IO.FileSystem.Threaded
(
File, initFile, readFileP, writeFileP, getFileFD, seek
, readFile, readTextFile, writeFile, writeTextFile
, readJSONFile, writeJSONFile
, FilePtr, newFilePtr, getFilePtrOffset, setFilePtrOffset
, mkdir, mkdirp
, unlink
, mkdtemp, mkstemp , initTempFile, initTempDir
, rmdir, rmrf
, DirEntType(..)
, scandir
, scandirRecursively
, FStat(..), UVTimeSpec(..)
, doesPathExist, doesFileExist, doesDirExist
, isLink, isDir, isFile
, isLinkSt, isDirSt, isFileSt
, stat, lstat, fstat
, stat', lstat'
, 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_FILE_MODE
, pattern DEFAULT_DIR_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
) where
import Control.Monad
import Data.Bits
import Data.IORef
import Data.Int
import Data.Word
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr
import Foreign.Storable (peekElemOff)
import Prelude hiding (readFile, writeFile)
import qualified Z.Data.Builder as B
import Z.Data.CBytes as CBytes
import qualified Z.Data.JSON as JSON
import Z.Data.PrimRef.PrimIORef
import qualified Z.Data.Text as T
import qualified Z.Data.Text.Print as T
import qualified Z.Data.Vector as V
import Z.Foreign
import Z.IO.Buffered
import qualified Z.IO.Environment as Env
import Z.IO.Exception
import qualified Z.IO.FileSystem.FilePath as P
import Z.IO.Resource
import Z.IO.UV.FFI
import Z.IO.UV.Manager
#include "_Shared.hs"
data File = File {-# UNPACK #-} !FD
{-# UNPACK #-} !(IORef Bool)
instance Show File where show :: File -> String
show = File -> String
forall a. Print a => a -> String
T.toString
instance T.Print 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
readFileP File
f Ptr Word8
buf Int
bufSiz (-Int64
1)
readFileP :: HasCallStack
=> File
-> Ptr Word8
-> Int
-> Int64
-> IO Int
readFileP :: File -> Ptr Word8 -> Int -> Int64 -> IO Int
readFileP 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 -> do
UVManager
uvm <- IO UVManager
getUVManager
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO Int
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO Int
withUVRequest UVManager
uvm (FD -> Ptr Word8 -> Int -> Int64 -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_read_threaded 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 ()
writeFileP File
f Ptr Word8
buf Int
bufSiz (-Int64
1)
writeFileP :: HasCallStack
=> File
-> Ptr Word8
-> Int
-> Int64
-> IO ()
writeFileP :: File -> Ptr Word8 -> Int -> Int64 -> IO ()
writeFileP 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 -> do
(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
UVManager
uvm <- IO UVManager
getUVManager
Int
written <- HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO Int
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO Int
withUVRequest UVManager
uvm
(FD -> Ptr Word8 -> Int -> Int64 -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_write_threaded 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
UVManager
uvm <- IO UVManager
getUVManager
Int
written <- HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO Int
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO Int
withUVRequest UVManager
uvm
(FD -> Ptr Word8 -> Int -> Int64 -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_write_threaded 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)
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 UVManager
uvm <- IO UVManager
getUVManager
Int
fd <- 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 ->
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO Int
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO Int
withUVRequest UVManager
uvm (BA# Word8 -> FD -> FD -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_open_threaded BA# Word8
p FD
flags FD
mode)
FD -> IORef Bool -> File
File (Int -> FD
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
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)
mkdir :: HasCallStack => CBytes -> FileMode -> IO ()
mkdir :: CBytes -> FD -> IO ()
mkdir CBytes
path FD
mode = do
UVManager
uvm <- IO UVManager
getUVManager
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (BA# Word8 -> FD -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_mkdir_threaded BA# Word8
p FD
mode)
mkdirp :: HasCallStack => CBytes -> FileMode -> IO ()
mkdirp :: CBytes -> FD -> IO ()
mkdirp CBytes
path FD
mode = do
UVManager
uvm <- IO UVManager
getUVManager
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 ->
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe) -> (Int -> IO Int) -> IO Int
forall b.
HasCallStack =>
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe) -> (Int -> IO b) -> IO b
withUVRequest' UVManager
uvm (BA# Word8 -> FD -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_mkdir_threaded BA# Word8
p FD
mode) Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return
case Int -> FD
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
r of
FD
UV_ENOENT -> 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]
_ -> Int -> IO ()
forall a b. (Integral a, HasCallStack) => a -> IO b
throwUV Int
r
FD
UV_EEXIST -> do
Bool
canIgnore <- HasCallStack => CBytes -> IO Bool
CBytes -> IO Bool
isDir CBytes
path
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
canIgnore (Int -> IO ()
forall a b. (Integral a, HasCallStack) => a -> IO b
throwUV Int
r)
FD
_ -> Int -> IO ()
forall a b. (Integral a, HasCallStack) => a -> IO b
throwUV 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 -> FD -> IO ()
forall a b. (Integral a, HasCallStack) => a -> IO b
throwUV 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 = do
UVManager
uvm <- IO UVManager
getUVManager
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (BA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_unlink_threaded BA# Word8
p)
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
UVManager
uvm <- IO UVManager
getUVManager
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (BA# Word8 -> Int -> MBA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_mkdtemp_threaded BA# Word8
p Int
size MBA# Word8
p')
CBytes -> IO CBytes
forall (m :: * -> *) a. Monad m => a -> m a
return CBytes
p''
mkstemp :: HasCallStack => CBytes -> IO CBytes
mkstemp :: CBytes -> IO CBytes
mkstemp CBytes
template = do
let size :: Int
size = CBytes -> Int
CBytes.length CBytes
template
CBytes -> (BA# Word8 -> IO CBytes) -> IO CBytes
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
CBytes.withCBytesUnsafe CBytes
template ((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
UVManager
uvm <- IO UVManager
getUVManager
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (BA# Word8 -> Int -> MBA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_mkstemp_threaded 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 = do
UVManager
uvm <- IO UVManager
getUVManager
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path (\ BA# Word8
p -> IO Int -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO Int -> IO ())
-> ((Ptr UVLoop -> IO UVSlotUnsafe) -> IO Int)
-> (Ptr UVLoop -> IO UVSlotUnsafe)
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO Int
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO Int
withUVRequest UVManager
uvm ((Ptr UVLoop -> IO UVSlotUnsafe) -> IO ())
-> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
forall a b. (a -> b) -> a -> b
$ BA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_rmdir_threaded BA# Word8
p)
rmrf :: HasCallStack => CBytes -> IO ()
rmrf :: CBytes -> IO ()
rmrf CBytes
path =
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \BA# Word8
path' ->
Int -> (Ptr FStat -> IO ()) -> IO ()
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
uvStatSize ((Ptr FStat -> IO ()) -> IO ()) -> (Ptr FStat -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr FStat
s -> do
UVManager
uvm <- IO UVManager
getUVManager
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe) -> (Int -> IO ()) -> IO ()
forall b.
HasCallStack =>
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe) -> (Int -> IO b) -> IO b
withUVRequest' UVManager
uvm (BA# Word8 -> Ptr FStat -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_stat_threaded BA# Word8
path' Ptr FStat
s) ((Int -> IO ()) -> IO ()) -> (Int -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ Int
r -> do
if | Int
r Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== FD -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral FD
UV_ENOENT -> () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
| Int
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 -> Int -> IO ()
forall a b. (Integral a, HasCallStack) => a -> IO b
throwUV Int
r
| Bool
otherwise -> do
FStat
st <- Ptr FStat -> IO FStat
peekUVStat Ptr FStat
s
case FStat -> FD
stMode FStat
st FD -> FD -> FD
forall a. Bits a => a -> a -> a
.&. FD
S_IFMT of
FD
S_IFREG -> HasCallStack => CBytes -> IO ()
CBytes -> IO ()
unlink CBytes
path
FD
S_IFLNK -> HasCallStack => CBytes -> IO ()
CBytes -> IO ()
unlink CBytes
path
FD
S_IFDIR -> 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) ->
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 ()
rmrf (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
FD
mode -> do
let desc :: Text
desc = Builder () -> Text
forall a. HasCallStack => Builder a -> Text
B.buildText (Builder () -> Text) -> Builder () -> Text
forall a b. (a -> b) -> a -> b
$ Builder ()
"Unsupported file mode: " Builder () -> Builder () -> Builder ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> FD -> Builder ()
forall a. (FiniteBits a, Integral a) => a -> Builder ()
B.hex FD
mode
UnsupportedOperation -> IO ()
forall e a. Exception e => e -> IO a
throwIO (UnsupportedOperation -> IO ()) -> UnsupportedOperation -> IO ()
forall a b. (a -> b) -> a -> b
$ IOEInfo -> UnsupportedOperation
UnsupportedOperation (Text -> Text -> CallStack -> IOEInfo
IOEInfo Text
"" Text
desc CallStack
HasCallStack => CallStack
callStack)
scandir :: HasCallStack => CBytes -> IO [(CBytes, DirEntType)]
scandir :: CBytes -> IO [(CBytes, DirEntType)]
scandir CBytes
path = do
UVManager
uvm <- IO UVManager
getUVManager
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 ->
(Ptr (Ptr (Ptr DirEntType)) -> IO Int)
-> IO (Ptr (Ptr DirEntType), Int)
forall a b. Prim a => (Ptr a -> IO b) -> IO (a, b)
allocPrimSafe ((Ptr (Ptr (Ptr DirEntType)) -> IO Int)
-> IO (Ptr (Ptr DirEntType), Int))
-> (Ptr (Ptr (Ptr DirEntType)) -> IO Int)
-> IO (Ptr (Ptr DirEntType), Int)
forall a b. (a -> b) -> a -> b
$ \ Ptr (Ptr (Ptr DirEntType))
dents ->
HasCallStack =>
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe) -> (Int -> IO ()) -> IO Int
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe) -> (Int -> IO ()) -> IO Int
withUVRequestEx UVManager
uvm
(BA# Word8
-> Ptr (Ptr (Ptr DirEntType)) -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_scandir_threaded BA# Word8
p Ptr (Ptr (Ptr DirEntType))
dents)
(Ptr (Ptr (Ptr DirEntType)) -> Int -> IO ()
hs_uv_fs_scandir_extra_cleanup Ptr (Ptr (Ptr DirEntType))
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'))
stat :: HasCallStack => CBytes -> IO FStat
stat :: CBytes -> IO FStat
stat CBytes
path = do
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
UVManager
uvm <- IO UVManager
getUVManager
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (BA# Word8 -> Ptr FStat -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_stat_threaded 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
UVManager
uvm <- IO UVManager
getUVManager
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (BA# Word8 -> Ptr FStat -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_lstat_threaded BA# Word8
p Ptr FStat
s)
Ptr FStat -> IO FStat
peekUVStat Ptr FStat
s
stat' :: HasCallStack => CBytes -> IO (Maybe FStat)
stat' :: CBytes -> IO (Maybe FStat)
stat' CBytes
path = do
CBytes -> (BA# Word8 -> IO (Maybe FStat)) -> IO (Maybe FStat)
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO (Maybe FStat)) -> IO (Maybe FStat))
-> (BA# Word8 -> IO (Maybe FStat)) -> IO (Maybe FStat)
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
Int -> (Ptr FStat -> IO (Maybe FStat)) -> IO (Maybe FStat)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
uvStatSize ((Ptr FStat -> IO (Maybe FStat)) -> IO (Maybe FStat))
-> (Ptr FStat -> IO (Maybe FStat)) -> IO (Maybe FStat)
forall a b. (a -> b) -> a -> b
$ \ Ptr FStat
s -> do
UVManager
uvm <- IO UVManager
getUVManager
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe)
-> (Int -> IO (Maybe FStat))
-> IO (Maybe FStat)
forall b.
HasCallStack =>
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe) -> (Int -> IO b) -> IO b
withUVRequest' UVManager
uvm (BA# Word8 -> Ptr FStat -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_stat_threaded BA# Word8
p Ptr FStat
s) ((Int -> IO (Maybe FStat)) -> IO (Maybe FStat))
-> (Int -> IO (Maybe FStat)) -> IO (Maybe FStat)
forall a b. (a -> b) -> a -> b
$ \ Int
r ->
if | Int
r Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== FD -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral FD
UV_ENOENT -> Maybe FStat -> IO (Maybe FStat)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe FStat
forall a. Maybe a
Nothing
| Int
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 -> Int -> IO (Maybe FStat)
forall a b. (Integral a, HasCallStack) => a -> IO b
throwUV Int
r
| Bool
otherwise -> FStat -> Maybe FStat
forall a. a -> Maybe a
Just (FStat -> Maybe FStat) -> IO FStat -> IO (Maybe FStat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr FStat -> IO FStat
peekUVStat Ptr FStat
s
lstat' :: HasCallStack => CBytes -> IO (Maybe FStat)
lstat' :: CBytes -> IO (Maybe FStat)
lstat' CBytes
path =
CBytes -> (BA# Word8 -> IO (Maybe FStat)) -> IO (Maybe FStat)
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO (Maybe FStat)) -> IO (Maybe FStat))
-> (BA# Word8 -> IO (Maybe FStat)) -> IO (Maybe FStat)
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
Int -> (Ptr FStat -> IO (Maybe FStat)) -> IO (Maybe FStat)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
uvStatSize ((Ptr FStat -> IO (Maybe FStat)) -> IO (Maybe FStat))
-> (Ptr FStat -> IO (Maybe FStat)) -> IO (Maybe FStat)
forall a b. (a -> b) -> a -> b
$ \ Ptr FStat
s -> do
UVManager
uvm <- IO UVManager
getUVManager
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe)
-> (Int -> IO (Maybe FStat))
-> IO (Maybe FStat)
forall b.
HasCallStack =>
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe) -> (Int -> IO b) -> IO b
withUVRequest' UVManager
uvm (BA# Word8 -> Ptr FStat -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_lstat_threaded BA# Word8
p Ptr FStat
s) ((Int -> IO (Maybe FStat)) -> IO (Maybe FStat))
-> (Int -> IO (Maybe FStat)) -> IO (Maybe FStat)
forall a b. (a -> b) -> a -> b
$ \ Int
r ->
if | Int
r Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== FD -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral FD
UV_ENOENT -> Maybe FStat -> IO (Maybe FStat)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe FStat
forall a. Maybe a
Nothing
| Int
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 -> Int -> IO (Maybe FStat)
forall a b. (Integral a, HasCallStack) => a -> IO b
throwUV Int
r
| Bool
otherwise -> FStat -> Maybe FStat
forall a. a -> Maybe a
Just (FStat -> Maybe FStat) -> IO FStat -> IO (Maybe FStat)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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
UVManager
uvm <- IO UVManager
getUVManager
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (FD -> Ptr FStat -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_fstat_threaded FD
fd Ptr FStat
s)
Ptr FStat -> IO FStat
peekUVStat Ptr FStat
s)
rename :: HasCallStack => CBytes -> CBytes -> IO ()
rename :: CBytes -> CBytes -> IO ()
rename CBytes
path CBytes
path' = do
UVManager
uvm <- IO UVManager
getUVManager
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path' ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p' ->
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (BA# Word8 -> BA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_rename_threaded BA# Word8
p 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 -> do
UVManager
uvm <- IO UVManager
getUVManager
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (FD -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_fsync_threaded 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 -> do
UVManager
uvm <- IO UVManager
getUVManager
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (FD -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_fdatasync_threaded 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 -> do
UVManager
uvm <- IO UVManager
getUVManager
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (FD -> Int64 -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_ftruncate_threaded FD
fd Int64
off)
copyfile :: HasCallStack => CBytes -> CBytes -> CopyFileFlag -> IO ()
copyfile :: CBytes -> CBytes -> FD -> IO ()
copyfile CBytes
path CBytes
path' FD
flag = do
UVManager
uvm <- IO UVManager
getUVManager
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path' ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p' ->
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (BA# Word8 -> BA# Word8 -> FD -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_copyfile_threaded 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
UVManager
uvm <- IO UVManager
getUVManager
CBytes -> (BA# Word8 -> IO AccessResult) -> IO AccessResult
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO AccessResult) -> IO AccessResult)
-> (BA# Word8 -> IO AccessResult) -> IO AccessResult
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe)
-> (Int -> IO AccessResult)
-> IO AccessResult
forall b.
HasCallStack =>
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe) -> (Int -> IO b) -> IO b
withUVRequest' UVManager
uvm (BA# Word8 -> FD -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_access_threaded BA# Word8
p FD
mode) (FD -> IO AccessResult
handleResult (FD -> IO AccessResult) -> (Int -> FD) -> Int -> IO AccessResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> FD
forall a b. (Integral a, Num b) => a -> b
fromIntegral)
where
handleResult :: FD -> IO AccessResult
handleResult FD
r
| 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 = do
UVManager
uvm <- IO UVManager
getUVManager
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (BA# Word8 -> FD -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_chmod_threaded 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 -> do
UVManager
uvm <- IO UVManager
getUVManager
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (FD -> FD -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_fchmod_threaded FD
fd FD
mode)
utime :: HasCallStack
=> CBytes
-> Double
-> Double
-> IO ()
utime :: CBytes -> Double -> Double -> IO ()
utime CBytes
path Double
atime Double
mtime = do
UVManager
uvm <- IO UVManager
getUVManager
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (BA# Word8 -> Double -> Double -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_utime_threaded 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 -> do
UVManager
uvm <- IO UVManager
getUVManager
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (FD -> Double -> Double -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_futime_threaded FD
fd Double
atime Double
mtime)
lutime :: HasCallStack
=> CBytes
-> Double
-> Double
-> IO ()
lutime :: CBytes -> Double -> Double -> IO ()
lutime CBytes
path Double
atime Double
mtime = do
UVManager
uvm <- IO UVManager
getUVManager
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (BA# Word8 -> Double -> Double -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_lutime_threaded BA# Word8
p Double
atime Double
mtime)
link :: HasCallStack => CBytes -> CBytes -> IO ()
link :: CBytes -> CBytes -> IO ()
link CBytes
path CBytes
path' = do
UVManager
uvm <- IO UVManager
getUVManager
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path' ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p' ->
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (BA# Word8 -> BA# Word8 -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_link_threaded BA# Word8
p BA# Word8
p')
symlink :: HasCallStack => CBytes -> CBytes -> SymlinkFlag -> IO ()
symlink :: CBytes -> CBytes -> FD -> IO ()
symlink CBytes
path CBytes
path' FD
flag = do
UVManager
uvm <- IO UVManager
getUVManager
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path' ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p' ->
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (BA# Word8 -> BA# Word8 -> FD -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_symlink_threaded BA# Word8
p BA# Word8
p' FD
flag)
readlink :: HasCallStack => CBytes -> IO CBytes
readlink :: CBytes -> IO CBytes
readlink CBytes
path = do
UVManager
uvm <- IO UVManager
getUVManager
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 ->
(Ptr CString -> IO Int) -> IO (CString, Int)
forall a b. Prim a => (Ptr a -> IO b) -> IO (a, b)
allocPrimSafe ((Ptr CString -> IO Int) -> IO (CString, Int))
-> (Ptr CString -> IO Int) -> IO (CString, Int)
forall a b. (a -> b) -> a -> b
$ \ Ptr CString
p' ->
HasCallStack =>
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe) -> (Int -> IO ()) -> IO Int
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe) -> (Int -> IO ()) -> IO Int
withUVRequestEx UVManager
uvm
(BA# Word8 -> Ptr CString -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_readlink_threaded BA# Word8
p Ptr CString
p')
(\ Int
_ -> Ptr CString -> IO ()
hs_uv_fs_readlink_extra_cleanup Ptr CString
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
UVManager
uvm <- IO UVManager
getUVManager
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 ->
(Ptr CString -> IO Int) -> IO (CString, Int)
forall a b. Prim a => (Ptr a -> IO b) -> IO (a, b)
allocPrimSafe ((Ptr CString -> IO Int) -> IO (CString, Int))
-> (Ptr CString -> IO Int) -> IO (CString, Int)
forall a b. (a -> b) -> a -> b
$ \ Ptr CString
p' ->
HasCallStack =>
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe) -> (Int -> IO ()) -> IO Int
UVManager
-> (Ptr UVLoop -> IO UVSlotUnsafe) -> (Int -> IO ()) -> IO Int
withUVRequestEx UVManager
uvm
(BA# Word8 -> Ptr CString -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_realpath_threaded BA# Word8
p Ptr CString
p')
(\ Int
_ -> Ptr CString -> IO ()
hs_uv_fs_readlink_extra_cleanup Ptr CString
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 = do
UVManager
uvm <- IO UVManager
getUVManager
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (BA# Word8 -> UID -> GID -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_chown_threaded BA# Word8
p UID
uid GID
gid)
fchown :: HasCallStack => FD -> UID -> GID -> IO ()
fchown :: FD -> UID -> GID -> IO ()
fchown FD
fd UID
uid GID
gid = do
UVManager
uvm <- IO UVManager
getUVManager
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (FD -> UID -> GID -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_fchown_threaded FD
fd UID
uid GID
gid)
lchown :: HasCallStack => CBytes -> UID -> GID -> IO ()
lchown :: CBytes -> UID -> GID -> IO ()
lchown CBytes
path UID
uid GID
gid = do
UVManager
uvm <- IO UVManager
getUVManager
CBytes -> (BA# Word8 -> IO ()) -> IO ()
forall a. CBytes -> (BA# Word8 -> IO a) -> IO a
withCBytesUnsafe CBytes
path ((BA# Word8 -> IO ()) -> IO ()) -> (BA# Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ BA# Word8
p ->
HasCallStack =>
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
UVManager -> (Ptr UVLoop -> IO UVSlotUnsafe) -> IO ()
withUVRequest_ UVManager
uvm (BA# Word8 -> UID -> GID -> Ptr UVLoop -> IO UVSlotUnsafe
hs_uv_fs_lchown_threaded BA# Word8
p UID
uid GID
gid)