{-# LINE 1 "src/Network/Socket/SendFile/Linux.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module Network.Socket.SendFile.Linux (_sendFile, sendFileIter, sendfile) where
import Data.Int (Int32, Int64)
import Data.Word (Word32, Word64)
import Foreign.C (CInt(..))
import Foreign.C.Error (eAGAIN, getErrno, throwErrno)
import Foreign.Marshal (alloca)
import Foreign.Ptr (Ptr)
import Foreign.Storable(poke)
import Network.Socket.SendFile.Iter (Iter(..), runIter)
import System.Posix.Types (Fd(..))
_sendFile :: Fd -> Fd -> Int64 -> Int64 -> IO ()
_sendFile :: Fd -> Fd -> Int64 -> Int64 -> IO ()
_sendFile Fd
out_fd Fd
in_fd Int64
off Int64
count =
do Int64
_ <- IO Iter -> IO Int64
runIter (Fd -> Fd -> Int64 -> Int64 -> Int64 -> IO Iter
sendFileIter Fd
out_fd Fd
in_fd Int64
count Int64
off Int64
count)
forall (m :: * -> *) a. Monad m => a -> m a
return ()
sendFileIter :: Fd
-> Fd
-> Int64
-> Int64
-> Int64
-> IO Iter
sendFileIter :: Fd -> Fd -> Int64 -> Int64 -> Int64 -> IO Iter
sendFileIter Fd
out_fd Fd
in_fd Int64
blockSize Int64
off Int64
remaining =
Fd -> Fd -> Int64 -> Int64 -> Int64 -> IO Iter
sendFileIterI Fd
out_fd Fd
in_fd (forall a. Ord a => a -> a -> a
min Int64
blockSize Int64
maxBytes) Int64
off Int64
remaining
sendFileIterI :: Fd
-> Fd
-> Int64
-> Int64
-> Int64
-> IO Iter
sendFileIterI :: Fd -> Fd -> Int64 -> Int64 -> Int64 -> IO Iter
sendFileIterI Fd
_out_fd Fd
_in_fd Int64
_blockSize Int64
_off Int64
0 = forall (m :: * -> *) a. Monad m => a -> m a
return (Int64 -> Iter
Done Int64
0)
sendFileIterI Fd
out_fd Fd
in_fd Int64
blockSize Int64
off Int64
remaining =
do let bytes :: Int64
bytes = forall a. Ord a => a -> a -> a
min Int64
remaining Int64
blockSize
(Bool
wouldBlock, Int64
sbytes) <- Fd -> Fd -> Int64 -> Int64 -> IO (Bool, Int64)
sendfile Fd
out_fd Fd
in_fd Int64
off Int64
bytes
let cont :: IO Iter
cont = Fd -> Fd -> Int64 -> Int64 -> Int64 -> IO Iter
sendFileIterI Fd
out_fd Fd
in_fd Int64
blockSize (Int64
off forall a. Num a => a -> a -> a
+ Int64
sbytes) (Int64
remaining forall a. (Ord a, Num a, Show a) => a -> a -> a
`safeMinus` Int64
sbytes)
case Bool
wouldBlock of
Bool
True -> forall (m :: * -> *) a. Monad m => a -> m a
return (Int64 -> Fd -> IO Iter -> Iter
WouldBlock Int64
sbytes Fd
out_fd IO Iter
cont)
Bool
False -> forall (m :: * -> *) a. Monad m => a -> m a
return (Int64 -> IO Iter -> Iter
Sent Int64
sbytes IO Iter
cont)
sendfile :: Fd -> Fd -> Int64 -> Int64 -> IO (Bool, Int64)
sendfile :: Fd -> Fd -> Int64 -> Int64 -> IO (Bool, Int64)
sendfile Fd
out_fd Fd
in_fd Int64
off Int64
bytes =
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr Int64
poff ->
do forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Int64
poff Int64
off
Fd -> Fd -> Ptr Int64 -> Int64 -> IO (Bool, Int64)
sendfileI Fd
out_fd Fd
in_fd Ptr Int64
poff Int64
bytes
sendfileI :: Fd -> Fd -> Ptr Int64 -> Int64 -> IO (Bool, Int64)
sendfileI :: Fd -> Fd -> Ptr Int64 -> Int64 -> IO (Bool, Int64)
sendfileI Fd
out_fd Fd
in_fd Ptr Int64
poff Int64
bytes = do
Int64
sbytes <- {-# SCC "c_sendfile" #-} Fd -> Fd -> Ptr Int64 -> Word64 -> IO Int64
c_sendfile Fd
out_fd Fd
in_fd Ptr Int64
poff (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
bytes)
if Int64
sbytes forall a. Ord a => a -> a -> Bool
<= -Int64
1
then do Errno
errno <- IO Errno
getErrno
if Errno
errno forall a. Eq a => a -> a -> Bool
== Errno
eAGAIN
then forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
True, Int64
0)
else forall a. String -> IO a
throwErrno String
"Network.Socket.SendFile.Linux.sendfileI"
else forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
False, forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
sbytes)
safeMinus :: (Ord a, Num a, Show a) => a -> a -> a
safeMinus :: forall a. (Ord a, Num a, Show a) => a -> a -> a
safeMinus a
x a
y
| a
y forall a. Ord a => a -> a -> Bool
> a
x = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"y > x " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (a
y,a
x)
| Bool
otherwise = a
x forall a. Num a => a -> a -> a
- a
y
maxBytes :: Int64
maxBytes :: Int64
maxBytes = forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Bounded a => a
maxBound :: (Int64))
{-# LINE 80 "src/Network/Socket/SendFile/Linux.hsc" #-}
foreign import ccall unsafe "sendfile64" c_sendfile
:: Fd -> Fd -> Ptr (Int64) -> (Word64) -> IO (Int64)
{-# LINE 84 "src/Network/Socket/SendFile/Linux.hsc" #-}