{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Std.IO.FileSystemT
(
UVFile
, UVFileReader, newUVFileReader, peekUVFileReader
, UVFileWriter, newUVFileWriter, peekUVFileWriter
, initUVFile
, UVFileMode(DEFAULT_MODE, S_IRWXU, S_IRUSR, S_IWUSR
, S_IXUSR, S_IRWXG, S_IRGRP, S_IWGRP, S_IXGRP, S_IRWXO, S_IROTH
)
, UVFileFlag(O_APPEND, O_CREAT, O_DIRECT, O_DSYNC, O_EXCL
, O_EXLOCK, O_NOATIME, O_NOFOLLOW, O_RDONLY, O_RDWR, O_SYMLINK
, O_SYNC, O_TRUNC, O_WRONLY, O_RANDOM, O_SHORT_LIVED, O_SEQUENTIAL, O_TEMPORARY
)
, mkdir
, unlink
, mkdtemp
, rmdir
, DirEntType(..)
, scandir
, UVStat(..), UVTimeSpec(..)
, stat, lstat, fstat
, rename
, fsync, fdatasync
, ftruncate
, UVCopyFileFlag(COPYFILE_DEFAULT, COPYFILE_EXCL, COPYFILE_FICLONE)
, copyfile
, UVAccessMode(F_OK, R_OK, W_OK, X_OK)
, AccessResult(..)
, access
, chmod, fchmod
, utime, futime
, UVSymlinkFlag(SYMLINK_DEFAULT, SYMLINK_DIR, SYMLINK_JUNCTION)
, link, symlink
, readlink, realpath
) where
import Control.Concurrent.STM.TVar
import Control.Concurrent.MVar
import Control.Monad
import Control.Monad.STM
import Data.Word
import Data.Int
import Std.Data.CBytes as CBytes
import Foreign.Ptr
import Foreign.Storable (peekElemOff)
import Foreign.Marshal.Alloc (allocaBytes)
import Std.Foreign.PrimArray (withPrimSafe', withPrimUnsafe')
import Std.IO.Buffered
import Std.IO.Exception
import Std.IO.Resource
import Std.IO.UV.Errno
import Std.IO.UV.FFI
import Std.IO.UV.Manager
data UVFile = UVFile
{ uvfFD :: {-# UNPACK #-} !UVFD
, uvfCounter :: {-# UNPACK #-} !(TVar Int)
}
instance Show UVFile where
show (UVFile fd _) = "Std.IO.FileSystemT: UVFile" ++ show fd
instance Input UVFile where
readInput f buf bufSiz = readUVFile f buf bufSiz (-1)
readUVFile :: HasCallStack => UVFile -> Ptr Word8 -> Int -> Int64 -> IO Int
readUVFile (UVFile fd counter) buf bufSiz off =
bracket_ (atomically $ do
s <- readTVar counter
if s >= 0 then modifyTVar' counter (+1)
else throwECLOSEDSTM)
(atomically $ modifyTVar' counter (subtract 1))
(do uvm <- getUVManager
withUVRequest uvm
(hs_uv_fs_read_threaded fd buf bufSiz off))
instance Output UVFile where
writeOutput f buf bufSiz = writeUVFile f buf bufSiz (-1)
writeUVFile :: HasCallStack => UVFile -> Ptr Word8 -> Int -> Int64 -> IO ()
writeUVFile (UVFile fd counter) buf bufSiz off =
bracket_ (atomically $ do
s <- readTVar counter
if s >= 0 then modifyTVar' counter (+1)
else throwECLOSEDSTM)
(atomically $ modifyTVar' counter (subtract 1))
(if off == -1 then go buf bufSiz
else go' buf bufSiz off)
where
go buf bufSiz = do
uvm <- getUVManager
written <- withUVRequest uvm
(hs_uv_fs_write_threaded fd buf bufSiz (-1))
when (written < bufSiz)
(go (buf `plusPtr` written) (bufSiz-written))
go' buf bufSiz !off = do
uvm <- getUVManager
written <- withUVRequest uvm
(hs_uv_fs_write_threaded fd buf bufSiz off)
when (written < bufSiz) $
go' (buf `plusPtr` written)
(bufSiz-written)
(off+fromIntegral written)
data UVFileReader = UVFileReader {-# UNPACK #-} !UVFile
{-# UNPACK #-} !(MVar Int64)
newUVFileReader :: UVFile
-> Int64
-> IO UVFileReader
newUVFileReader uvf off = UVFileReader uvf <$> newMVar off
peekUVFileReader :: UVFileReader
-> Int64
-> IO Int64
peekUVFileReader (UVFileReader _ offsetLock) = swapMVar offsetLock
instance Input UVFileReader where
readInput (UVFileReader file offsetLock) buf bufSiz =
modifyMVar offsetLock $ \ off -> do
!l <- readUVFile file buf bufSiz off
let !off' = off + fromIntegral l
return (off', l)
data UVFileWriter = UVFileWriter {-# UNPACK #-} !UVFile
{-# UNPACK #-} !(MVar Int64)
newUVFileWriter :: UVFile
-> Int64
-> IO UVFileWriter
newUVFileWriter uvf off = UVFileWriter uvf <$> newMVar off
peekUVFileWriter :: UVFileWriter
-> Int64
-> IO Int64
peekUVFileWriter (UVFileWriter _ offsetLock) = swapMVar offsetLock
instance Output UVFileWriter where
writeOutput (UVFileWriter file offsetLock) buf bufSiz =
modifyMVar_ offsetLock $ \ off -> do
writeUVFile file buf bufSiz off
let !off' = off + fromIntegral bufSiz
return off'
initUVFile :: HasCallStack
=> CBytes
-> UVFileFlag
-> UVFileMode
-> Resource UVFile
initUVFile path flags mode =
initResource
(do uvm <- getUVManager
fd <- withCBytes path $ \ p ->
withUVRequest uvm (hs_uv_fs_open_threaded p flags mode)
counter <- newTVarIO 0
return (UVFile (fromIntegral fd) counter))
(\ (UVFile fd counter) -> join . atomically $ do
s <- readTVar counter
case s `compare` 0 of
GT -> retry
EQ -> do swapTVar counter (-1)
return (do
uvm <- getUVManager
void . withUVRequest uvm $
hs_uv_fs_close_threaded fd)
LT -> return (return ()))
mkdir :: HasCallStack => CBytes -> UVFileMode -> IO ()
mkdir path mode = do
uvm <- getUVManager
withCBytes path $ \ p ->
withUVRequest_ uvm (hs_uv_fs_mkdir_threaded p mode)
unlink :: HasCallStack => CBytes -> IO ()
unlink path = do
uvm <- getUVManager
withCBytes path $ \ p ->
withUVRequest_ uvm (hs_uv_fs_unlink_threaded p)
mkdtemp :: HasCallStack => CBytes -> IO CBytes
mkdtemp path = do
let size = CBytes.length path
withCBytes path $ \ p ->
CBytes.create (size+7) $ \ p' -> do
uvm <- getUVManager
withUVRequest_ uvm (hs_uv_fs_mkdtemp_threaded p size p')
return (size+6)
rmdir :: HasCallStack => CBytes -> IO ()
rmdir path = do
uvm <- getUVManager
withCBytes path (void . withUVRequest uvm . hs_uv_fs_rmdir_threaded)
scandir :: HasCallStack => CBytes -> IO [(CBytes, DirEntType)]
scandir path = do
uvm <- getUVManager
bracket
(withCBytes path $ \ p ->
withPrimSafe' $ \ dents ->
withUVRequestEx uvm
(hs_uv_fs_scandir_threaded p dents)
(hs_uv_fs_scandir_extra_cleanup dents))
(\ (dents, n) -> hs_uv_fs_scandir_cleanup dents n)
(\ (dents, n) -> forM [0..n-1] $ \ i -> do
dent <- peekElemOff dents i
(path, typ) <- peekUVDirEnt dent
let !typ' = fromUVDirEntType typ
!path' <- fromCString path
return (path', typ'))
stat :: HasCallStack => CBytes -> IO UVStat
stat path = do
withCBytes path $ \ p ->
allocaBytes uvStatSize $ \ stat -> do
uvm <- getUVManager
withUVRequest_ uvm (hs_uv_fs_stat_threaded p stat)
peekUVStat stat
lstat :: HasCallStack => CBytes -> IO UVStat
lstat path = do
withCBytes path $ \ p ->
allocaBytes uvStatSize $ \ stat -> do
uvm <- getUVManager
withUVRequest_ uvm (hs_uv_fs_lstat_threaded p stat)
peekUVStat stat
fstat :: HasCallStack => UVFile -> IO UVStat
fstat (UVFile fd counter) = do
bracket_ (atomically $ do
s <- readTVar counter
if s >= 0 then modifyTVar' counter (+1)
else throwECLOSEDSTM)
(atomically $ modifyTVar' counter (subtract 1))
(allocaBytes uvStatSize $ \ stat -> do
uvm <- getUVManager
withUVRequest_ uvm (hs_uv_fs_fstat_threaded fd stat)
peekUVStat stat)
rename :: HasCallStack => CBytes -> CBytes -> IO ()
rename path path' = do
uvm <- getUVManager
withCBytes path $ \ p ->
withCBytes path' $ \ p' ->
withUVRequest_ uvm (hs_uv_fs_rename_threaded p p')
fsync :: HasCallStack => UVFile -> IO ()
fsync (UVFile fd counter) =
bracket_ (atomically $ do
s <- readTVar counter
if s >= 0 then modifyTVar' counter (+1)
else throwECLOSEDSTM)
(atomically $ modifyTVar' counter (subtract 1))
(do uvm <- getUVManager
withUVRequest_ uvm (hs_uv_fs_fsync_threaded fd))
fdatasync :: HasCallStack => UVFile -> IO ()
fdatasync (UVFile fd counter) =
bracket_ (atomically $ do
s <- readTVar counter
if s >= 0 then modifyTVar' counter (+1)
else throwECLOSEDSTM)
(atomically $ modifyTVar' counter (subtract 1))
(do uvm <- getUVManager
withUVRequest_ uvm (hs_uv_fs_fdatasync_threaded fd))
ftruncate :: HasCallStack => UVFile -> Int64 -> IO ()
ftruncate (UVFile fd counter) off =
bracket_ (atomically $ do
s <- readTVar counter
if s >= 0 then modifyTVar' counter (+1)
else throwECLOSEDSTM)
(atomically $ modifyTVar' counter (subtract 1))
(do uvm <- getUVManager
withUVRequest_ uvm (hs_uv_fs_ftruncate_threaded fd off))
copyfile :: HasCallStack => CBytes -> CBytes -> UVCopyFileFlag -> IO ()
copyfile path path' flag = do
uvm <- getUVManager
withCBytes path $ \ p ->
withCBytes path' $ \ p' ->
withUVRequest_ uvm (hs_uv_fs_copyfile_threaded p p' flag)
access :: HasCallStack => CBytes -> UVAccessMode -> IO AccessResult
access path mode = do
uvm <- getUVManager
withCBytes path $ \ p ->
withUVRequest' uvm (hs_uv_fs_access_threaded p mode) (handleResult . fromIntegral)
where
handleResult r
| r == 0 = return AccessOK
| r == UV_ENOENT = return NoExistence
| r == UV_EACCES = return NoPermission
| otherwise = do
name <- uvErrName r
desc <- uvStdError r
throwUVError r (IOEInfo name desc callStack)
chmod :: HasCallStack => CBytes -> UVFileMode -> IO ()
chmod path mode = do
uvm <- getUVManager
withCBytes path $ \ p ->
withUVRequest_ uvm (hs_uv_fs_chmod_threaded p mode)
fchmod :: HasCallStack => UVFile -> UVFileMode -> IO ()
fchmod (UVFile fd counter) mode =
bracket_ (atomically $ do
s <- readTVar counter
if s >= 0 then modifyTVar' counter (+1)
else throwECLOSEDSTM)
(atomically $ modifyTVar' counter (subtract 1))
(do uvm <- getUVManager
withUVRequest_ uvm (hs_uv_fs_fchmod_threaded fd mode))
utime :: HasCallStack
=> CBytes
-> Double
-> Double
-> IO ()
utime path atime mtime = do
uvm <- getUVManager
withCBytes path $ \ p ->
withUVRequest_ uvm (hs_uv_fs_utime_threaded p atime mtime)
futime :: HasCallStack => UVFile -> Double -> Double -> IO ()
futime (UVFile fd counter) atime mtime =
bracket_ (atomically $ do
s <- readTVar counter
if s >= 0 then modifyTVar' counter (+1)
else throwECLOSEDSTM)
(atomically $ modifyTVar' counter (subtract 1))
(do uvm <- getUVManager
withUVRequest_ uvm (hs_uv_fs_futime_threaded fd atime mtime))
link :: HasCallStack => CBytes -> CBytes -> IO ()
link path path' = do
uvm <- getUVManager
withCBytes path $ \ p ->
withCBytes path' $ \ p' ->
withUVRequest_ uvm (hs_uv_fs_link_threaded p p')
symlink :: HasCallStack => CBytes -> CBytes -> UVSymlinkFlag -> IO ()
symlink path path' flag = do
uvm <- getUVManager
withCBytes path $ \ p ->
withCBytes path' $ \ p' ->
withUVRequest_ uvm (hs_uv_fs_symlink_threaded p p' flag)
readlink :: HasCallStack => CBytes -> IO CBytes
readlink path = do
uvm <- getUVManager
bracket
(withCBytes path $ \ p ->
withPrimSafe' $ \ p' ->
withUVRequestEx uvm
(hs_uv_fs_readlink_threaded p p')
(\ _ -> hs_uv_fs_readlink_extra_cleanup p'))
(\ (path, _) -> hs_uv_fs_readlink_cleanup path)
(\ (path, _) -> do
!path' <- fromCString path
return path')
realpath :: HasCallStack => CBytes -> IO CBytes
realpath path = do
uvm <- getUVManager
bracket
(withCBytes path $ \ p ->
withPrimSafe' $ \ p' ->
withUVRequestEx uvm
(hs_uv_fs_realpath_threaded p p')
(\ _ -> hs_uv_fs_readlink_extra_cleanup p'))
(\ (path, _) -> hs_uv_fs_readlink_cleanup path)
(\ (path, _) -> do
!path' <- fromCString path
return path')