#include "inline.hs"
module Streamly.Internal.FileSystem.FDIO
    ( write
    , writeAll
    , writev
    , writevAll
    )
where
import Control.Monad (when)
import Streamly.Internal.System.IOVec.Type (IOVec)
#if !defined(mingw32_HOST_OS)
import Control.Concurrent (threadWaitWrite)
import Data.Int (Int64)
import Foreign.C.Error (throwErrnoIfMinus1RetryMayBlock)
#if __GLASGOW_HASKELL__ >= 802
import Foreign.C.Types (CBool(..))
#endif
import System.Posix.Internals (c_write, c_safe_write)
import Streamly.Internal.System.IOVec.Type (c_writev, c_safe_writev)
#endif
import Foreign.C.Types (CSize(..), CInt(..))
import Data.Word (Word8)
import Foreign.Ptr (plusPtr, Ptr)
import GHC.IO.FD (FD(..))
#if !defined(mingw32_HOST_OS)
foreign import ccall unsafe "rtsSupportsBoundThreads" threaded :: Bool
isNonBlocking :: FD -> Bool
isNonBlocking :: FD -> Bool
isNonBlocking FD
fd = FD -> Int
fdIsNonBlocking FD
fd forall a. Eq a => a -> a -> Bool
/= Int
0
#if __GLASGOW_HASKELL__ >= 804
foreign import ccall unsafe "fdReady"
    unsafe_fdReady :: CInt -> CBool -> Int64 -> CBool -> IO CInt
#else
foreign import ccall safe "fdReady"
    unsafe_fdReady :: CInt -> CInt -> CInt -> CInt -> IO CInt
#endif
writeNonBlocking :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO CInt
writeNonBlocking :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO CInt
writeNonBlocking String
loc !FD
fd !Ptr Word8
buf !Int
off !CSize
len
    | FD -> Bool
isNonBlocking FD
fd = IO CInt
unsafe_write 
    | Bool
otherwise   = do
        let isWrite :: CBool
isWrite = CBool
1
            isSocket :: CBool
isSocket = CBool
0
            msecs :: Int64
msecs = Int64
0
        CInt
r <- CInt -> CBool -> Int64 -> CBool -> IO CInt
unsafe_fdReady (FD -> CInt
fdFD FD
fd) CBool
isWrite Int64
msecs CBool
isSocket
        forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CInt
r forall a. Eq a => a -> a -> Bool
== CInt
0) forall a b. (a -> b) -> a -> b
$ Fd -> IO ()
threadWaitWrite (forall a b. (Integral a, Num b) => a -> b
fromIntegral (FD -> CInt
fdFD FD
fd))
        if Bool
threaded then IO CInt
safe_write else IO CInt
unsafe_write
    where
    do_write :: IO a -> IO b
do_write IO a
call = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
                      forall a b. (Eq a, Num a) => String -> IO a -> IO b -> IO a
throwErrnoIfMinus1RetryMayBlock String
loc IO a
call
                        (Fd -> IO ()
threadWaitWrite (forall a b. (Integral a, Num b) => a -> b
fromIntegral (FD -> CInt
fdFD FD
fd)))
    unsafe_write :: IO CInt
unsafe_write  = forall {a} {b}. (Integral a, Num b) => IO a -> IO b
do_write (CInt -> Ptr Word8 -> CSize -> IO CSsize
c_write (FD -> CInt
fdFD FD
fd) (Ptr Word8
buf forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
off) CSize
len)
    safe_write :: IO CInt
safe_write    = forall {a} {b}. (Integral a, Num b) => IO a -> IO b
do_write (CInt -> Ptr Word8 -> CSize -> IO CSsize
c_safe_write (FD -> CInt
fdFD FD
fd) (Ptr Word8
buf forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
off) CSize
len)
writevNonBlocking :: String -> FD -> Ptr IOVec -> Int -> IO CInt
writevNonBlocking :: String -> FD -> Ptr IOVec -> Int -> IO CInt
writevNonBlocking String
loc !FD
fd !Ptr IOVec
iov !Int
cnt
    | FD -> Bool
isNonBlocking FD
fd = IO CInt
unsafe_write 
    | Bool
otherwise   = do
        let isWrite :: CBool
isWrite = CBool
1
            isSocket :: CBool
isSocket = CBool
0
            msecs :: Int64
msecs = Int64
0
        CInt
r <- CInt -> CBool -> Int64 -> CBool -> IO CInt
unsafe_fdReady (FD -> CInt
fdFD FD
fd) CBool
isWrite Int64
msecs CBool
isSocket
        forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CInt
r forall a. Eq a => a -> a -> Bool
== CInt
0) forall a b. (a -> b) -> a -> b
$ Fd -> IO ()
threadWaitWrite (forall a b. (Integral a, Num b) => a -> b
fromIntegral (FD -> CInt
fdFD FD
fd))
        if Bool
threaded then IO CInt
safe_write else IO CInt
unsafe_write
    where
    do_write :: IO a -> IO b
do_write IO a
call = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap`
                      forall a b. (Eq a, Num a) => String -> IO a -> IO b -> IO a
throwErrnoIfMinus1RetryMayBlock String
loc IO a
call
                        (Fd -> IO ()
threadWaitWrite (forall a b. (Integral a, Num b) => a -> b
fromIntegral (FD -> CInt
fdFD FD
fd)))
    unsafe_write :: IO CInt
unsafe_write  = forall {a} {b}. (Integral a, Num b) => IO a -> IO b
do_write (CInt -> Ptr IOVec -> CInt -> IO CSsize
c_writev (FD -> CInt
fdFD FD
fd) Ptr IOVec
iov (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
cnt))
    safe_write :: IO CInt
safe_write    = forall {a} {b}. (Integral a, Num b) => IO a -> IO b
do_write (CInt -> Ptr IOVec -> CInt -> IO CSsize
c_safe_writev (FD -> CInt
fdFD FD
fd) Ptr IOVec
iov (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
cnt))
#else
writeNonBlocking :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO CInt
writeNonBlocking = undefined
writevNonBlocking :: String -> FD -> Ptr IOVec -> Int -> IO CInt
writevNonBlocking = undefined
#endif
#if 0
#if defined(mingw32_HOST_OS)
# if defined(i386_HOST_ARCH)
#  define WINDOWS_CCONV stdcall
# elif defined(x86_64_HOST_ARCH)
#  define WINDOWS_CCONV ccall
# else
#  error Unknown mingw32 arch
# endif
#endif
foreign import WINDOWS_CCONV safe "recv"
   c_safe_recv :: CInt -> Ptr Word8 -> CInt -> CInt -> IO CInt
foreign import WINDOWS_CCONV safe "send"
   c_safe_send :: CInt -> Ptr Word8 -> CInt -> CInt -> IO CInt
blockingWriteRawBufferPtr :: String -> FD -> Ptr Word8-> Int -> CSize -> IO CInt
blockingWriteRawBufferPtr loc !fd !buf !off !len
  = throwErrnoIfMinus1Retry loc $ do
        let start_ptr = buf `plusPtr` off
            send_ret = c_safe_send  (fdFD fd) start_ptr (fromIntegral len) 0
            write_ret = c_safe_write (fdFD fd) start_ptr (fromIntegral len)
        r <- bool write_ret send_ret (fdIsSocket fd)
        when (r == -1) c_maperrno
        return r
      
      
      
      
      
      
      
      
      
      
asyncWriteRawBufferPtr :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO CInt
asyncWriteRawBufferPtr loc !fd !buf !off !len = do
    (l, rc) <- asyncWrite (fromIntegral (fdFD fd)) (fdIsSocket_ fd)
                  (fromIntegral len) (buf `plusPtr` off)
    if l == (-1)
      then let sock_errno = c_maperrno_func (fromIntegral rc)
               non_sock_errno = Errno (fromIntegral rc)
               errno = bool non_sock_errno sock_errno (fdIsSocket fd)
           in  ioError (errnoToIOError loc errno Nothing Nothing)
      else return (fromIntegral l)
writeNonBlocking :: String -> FD -> Ptr Word8 -> Int -> CSize -> IO CInt
writeNonBlocking loc !fd !buf !off !len
    | threaded  = blockingWriteRawBufferPtr loc fd buf off len
    | otherwise = asyncWriteRawBufferPtr    loc fd buf off len
#endif
write :: FD -> Ptr Word8 -> Int -> CSize -> IO CInt
write :: FD -> Ptr Word8 -> Int -> CSize -> IO CInt
write = String -> FD -> Ptr Word8 -> Int -> CSize -> IO CInt
writeNonBlocking String
"Streamly.Internal.FileSystem.FDIO"
writeAll :: FD -> Ptr Word8 -> Int -> IO ()
writeAll :: FD -> Ptr Word8 -> Int -> IO ()
writeAll FD
fd Ptr Word8
ptr Int
bytes = do
    CInt
res <- FD -> Ptr Word8 -> Int -> CSize -> IO CInt
write FD
fd Ptr Word8
ptr Int
0 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
bytes)
    let res' :: Int
res' = forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
res
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
res' forall a. Ord a => a -> a -> Bool
< Int
bytes) forall a b. (a -> b) -> a -> b
$
      FD -> Ptr Word8 -> Int -> IO ()
writeAll FD
fd (Ptr Word8
ptr forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
res') (Int
bytes forall a. Num a => a -> a -> a
- Int
res')
writev :: FD -> Ptr IOVec -> Int -> IO CInt
writev :: FD -> Ptr IOVec -> Int -> IO CInt
writev = String -> FD -> Ptr IOVec -> Int -> IO CInt
writevNonBlocking String
"Streamly.Internal.FileSystem.FDIO"
writevAll :: FD -> Ptr IOVec -> Int -> IO ()
writevAll :: FD -> Ptr IOVec -> Int -> IO ()
writevAll FD
fd Ptr IOVec
iovec Int
count = do
    CInt
_res <- FD -> Ptr IOVec -> Int -> IO CInt
writev FD
fd Ptr IOVec
iovec Int
count
    
    forall (m :: * -> *) a. Monad m => a -> m a
return ()