{-# LANGUAGE CPP, RecordWildCards #-}
module Network.Socket.SendFile.Internal (
sendFile,
sendFileIterWith,
sendFile',
sendFileIterWith',
sendFile'',
sendFileIterWith'',
unsafeSendFile,
unsafeSendFileIterWith,
unsafeSendFile',
unsafeSendFileIterWith',
sendFileMode,
) where
#if defined(PORTABLE_SENDFILE)
import Network.Socket.SendFile.Portable (sendFileMode, sendFile'', sendFileIterWith'', unsafeSendFile'', unsafeSendFileIterWith'')
#else
import Network.Socket (fdSocket)
import Network.Socket.SendFile.Util
import System.Posix.Types (Fd(..))
#ifdef __GLASGOW_HASKELL__
#if __GLASGOW_HASKELL__ >= 611
import GHC.IO.Handle.Internals (withHandle_)
import GHC.IO.Handle.Types (Handle__(..))
import qualified GHC.IO.FD as FD
import GHC.IO.Exception
import Data.Typeable (cast)
#else
import GHC.IOBase
import GHC.Handle hiding (fdToHandle)
import qualified GHC.Handle
#endif
#endif
#endif
import Network.Socket (Socket)
import Network.Socket.SendFile.Iter (Iter(..))
import System.IO (Handle, IOMode(..), hFileSize, hFlush, withBinaryFile)
#ifdef __GLASGOW_HASKELL__
#if __GLASGOW_HASKELL__ >= 611
import System.IO.Error
#endif
#endif
#if defined(WIN32_SENDFILE)
import Network.Socket.SendFile.Win32 (_sendFile, sendFileIter)
sendFileMode :: String
sendFileMode = "WIN32_SENDFILE"
#endif
#if defined(LINUX_SENDFILE)
import Network.Socket.SendFile.Linux (_sendFile, sendFileIter)
sendFileMode :: String
sendFileMode :: String
sendFileMode = String
"LINUX_SENDFILE"
#endif
#if defined(FREEBSD_SENDFILE)
import Network.Socket.SendFile.FreeBSD (_sendFile, sendFileIter)
sendFileMode :: String
sendFileMode = "FREEBSD_SENDFILE"
#endif
#if defined(DARWIN_SENDFILE)
import Network.Socket.SendFile.Darwin (_sendFile, sendFileIter)
sendFileMode :: String
sendFileMode = "DARWIN_SENDFILE"
#endif
#if defined(PORTABLE_SENDFILE)
#else
sendFile'' :: Socket -> Handle -> Integer -> Integer -> IO ()
sendFile'' :: Socket -> Handle -> Integer -> Integer -> IO ()
sendFile'' Socket
outs Handle
inh Integer
off Integer
count =
#if MIN_VERSION_network(3,0,0)
do Fd
out_fd <- (CInt -> Fd) -> IO CInt -> IO Fd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CInt -> Fd
Fd (Socket -> IO CInt
fdSocket Socket
outs)
#else
do let out_fd = Fd (fdSocket outs)
#endif
Handle -> (Fd -> IO ()) -> IO ()
forall a. Handle -> (Fd -> IO a) -> IO a
withFd Handle
inh ((Fd -> IO ()) -> IO ()) -> (Fd -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Fd
in_fd ->
(Fd -> Fd -> Int64 -> Int64 -> Int64 -> IO ())
-> Fd -> Fd -> Integer -> Integer -> Integer -> IO ()
forall i a b c.
Integral i =>
(a -> b -> i -> i -> i -> IO c)
-> a -> b -> Integer -> Integer -> Integer -> IO c
wrapSendFile' (\Fd
out_fd_ Fd
in_fd_ Int64
_blockSize_ Int64
off_ Int64
count_ -> Fd -> Fd -> Int64 -> Int64 -> IO ()
_sendFile Fd
out_fd_ Fd
in_fd_ Int64
off_ Int64
count_)
Fd
out_fd Fd
in_fd Integer
count Integer
off Integer
count
sendFileIterWith'' :: (IO Iter -> IO a) -> Socket -> Handle -> Integer -> Integer -> Integer -> IO a
sendFileIterWith'' :: (IO Iter -> IO a)
-> Socket -> Handle -> Integer -> Integer -> Integer -> IO a
sendFileIterWith'' IO Iter -> IO a
stepper Socket
outs Handle
inp Integer
blockSize Integer
off Integer
count =
#if MIN_VERSION_network(3,0,0)
do Fd
out_fd <- (CInt -> Fd) -> IO CInt -> IO Fd
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CInt -> Fd
Fd (Socket -> IO CInt
fdSocket Socket
outs)
#else
do let out_fd = Fd (fdSocket outs)
#endif
Handle -> (Fd -> IO a) -> IO a
forall a. Handle -> (Fd -> IO a) -> IO a
withFd Handle
inp ((Fd -> IO a) -> IO a) -> (Fd -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Fd
in_fd ->
IO Iter -> IO a
stepper (IO Iter -> IO a) -> IO Iter -> IO a
forall a b. (a -> b) -> a -> b
$ (Fd -> Fd -> Int64 -> Int64 -> Int64 -> IO Iter)
-> Fd -> Fd -> Integer -> Integer -> Integer -> IO Iter
forall i a b c.
Integral i =>
(a -> b -> i -> i -> i -> IO c)
-> a -> b -> Integer -> Integer -> Integer -> IO c
wrapSendFile' Fd -> Fd -> Int64 -> Int64 -> Int64 -> IO Iter
sendFileIter Fd
out_fd Fd
in_fd Integer
blockSize Integer
off Integer
count
unsafeSendFile'' :: Handle -> Handle -> Integer -> Integer -> IO ()
unsafeSendFile'' :: Handle -> Handle -> Integer -> Integer -> IO ()
unsafeSendFile'' Handle
outp Handle
inp Integer
off Integer
count =
do Handle -> IO ()
hFlush Handle
outp
Handle -> (Fd -> IO ()) -> IO ()
forall a. Handle -> (Fd -> IO a) -> IO a
withFd Handle
outp ((Fd -> IO ()) -> IO ()) -> (Fd -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Fd
out_fd ->
Handle -> (Fd -> IO ()) -> IO ()
forall a. Handle -> (Fd -> IO a) -> IO a
withFd Handle
inp ((Fd -> IO ()) -> IO ()) -> (Fd -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Fd
in_fd ->
(Fd -> Fd -> Int64 -> Int64 -> Int64 -> IO ())
-> Fd -> Fd -> Integer -> Integer -> Integer -> IO ()
forall i a b c.
Integral i =>
(a -> b -> i -> i -> i -> IO c)
-> a -> b -> Integer -> Integer -> Integer -> IO c
wrapSendFile' (\Fd
out_fd_ Fd
in_fd_ Int64
_blockSize_ Int64
off_ Int64
count_ -> Fd -> Fd -> Int64 -> Int64 -> IO ()
_sendFile Fd
out_fd_ Fd
in_fd_ Int64
off_ Int64
count_)
Fd
out_fd Fd
in_fd Integer
count Integer
off Integer
count
unsafeSendFileIterWith'' :: (IO Iter -> IO a) -> Handle -> Handle -> Integer -> Integer -> Integer -> IO a
unsafeSendFileIterWith'' :: (IO Iter -> IO a)
-> Handle -> Handle -> Integer -> Integer -> Integer -> IO a
unsafeSendFileIterWith'' IO Iter -> IO a
stepper Handle
outp Handle
inp Integer
blockSize Integer
off Integer
count =
do Handle -> IO ()
hFlush Handle
outp
Handle -> (Fd -> IO a) -> IO a
forall a. Handle -> (Fd -> IO a) -> IO a
withFd Handle
outp ((Fd -> IO a) -> IO a) -> (Fd -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Fd
out_fd ->
Handle -> (Fd -> IO a) -> IO a
forall a. Handle -> (Fd -> IO a) -> IO a
withFd Handle
inp ((Fd -> IO a) -> IO a) -> (Fd -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Fd
in_fd ->
IO Iter -> IO a
stepper (IO Iter -> IO a) -> IO Iter -> IO a
forall a b. (a -> b) -> a -> b
$ (Fd -> Fd -> Int64 -> Int64 -> Int64 -> IO Iter)
-> Fd -> Fd -> Integer -> Integer -> Integer -> IO Iter
forall i a b c.
Integral i =>
(a -> b -> i -> i -> i -> IO c)
-> a -> b -> Integer -> Integer -> Integer -> IO c
wrapSendFile' Fd -> Fd -> Int64 -> Int64 -> Int64 -> IO Iter
sendFileIter Fd
out_fd Fd
in_fd Integer
blockSize Integer
off Integer
count
withFd :: Handle -> (Fd -> IO a) -> IO a
#ifdef __GLASGOW_HASKELL__
#if __GLASGOW_HASKELL__ >= 611
withFd :: Handle -> (Fd -> IO a) -> IO a
withFd Handle
h Fd -> IO a
f = String -> Handle -> (Handle__ -> IO a) -> IO a
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
withHandle_ String
"withFd" Handle
h ((Handle__ -> IO a) -> IO a) -> (Handle__ -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \ Handle__{dev
Maybe (TextEncoder enc_state)
Maybe (TextDecoder dec_state)
Maybe TextEncoding
Maybe (MVar Handle__)
HandleType
BufferMode
Newline
IORef (dec_state, Buffer Word8)
IORef (BufferList CharBufElem)
IORef (Buffer CharBufElem)
IORef (Buffer Word8)
haDevice :: ()
haType :: Handle__ -> HandleType
haByteBuffer :: Handle__ -> IORef (Buffer Word8)
haBufferMode :: Handle__ -> BufferMode
haLastDecode :: ()
haCharBuffer :: Handle__ -> IORef (Buffer CharBufElem)
haBuffers :: Handle__ -> IORef (BufferList CharBufElem)
haEncoder :: ()
haDecoder :: ()
haCodec :: Handle__ -> Maybe TextEncoding
haInputNL :: Handle__ -> Newline
haOutputNL :: Handle__ -> Newline
haOtherSide :: Handle__ -> Maybe (MVar Handle__)
haOtherSide :: Maybe (MVar Handle__)
haOutputNL :: Newline
haInputNL :: Newline
haCodec :: Maybe TextEncoding
haDecoder :: Maybe (TextDecoder dec_state)
haEncoder :: Maybe (TextEncoder enc_state)
haBuffers :: IORef (BufferList CharBufElem)
haCharBuffer :: IORef (Buffer CharBufElem)
haLastDecode :: IORef (dec_state, Buffer Word8)
haBufferMode :: BufferMode
haByteBuffer :: IORef (Buffer Word8)
haType :: HandleType
haDevice :: dev
..} -> do
case dev -> Maybe FD
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast dev
haDevice of
Maybe FD
Nothing -> IOError -> IO a
forall a. IOError -> IO a
ioError (IOError -> String -> IOError
ioeSetErrorString (IOErrorType -> String -> Maybe Handle -> Maybe String -> IOError
mkIOError IOErrorType
IllegalOperation
String
"withFd" (Handle -> Maybe Handle
forall a. a -> Maybe a
Just Handle
h) Maybe String
forall a. Maybe a
Nothing)
String
"handle is not a file descriptor")
Just FD
fd -> Fd -> IO a
f (CInt -> Fd
Fd (CInt -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (FD -> CInt
FD.fdFD FD
fd)))
#else
withFd h f =
withHandle_ "withFd" h $ \ h_ ->
f (Fd (fromIntegral (haFD h_)))
#endif
#endif
#endif
sendFile :: Socket -> FilePath -> IO ()
sendFile :: Socket -> String -> IO ()
sendFile Socket
outs String
infp =
String -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile String
infp IOMode
ReadMode ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Handle
inp -> do
Integer
count <- Handle -> IO Integer
hFileSize Handle
inp
Socket -> Handle -> Integer -> Integer -> IO ()
sendFile'' Socket
outs Handle
inp Integer
0 Integer
count
sendFileIterWith :: (IO Iter -> IO a) -> Socket -> FilePath -> Integer -> IO a
sendFileIterWith :: (IO Iter -> IO a) -> Socket -> String -> Integer -> IO a
sendFileIterWith IO Iter -> IO a
stepper Socket
outs String
infp Integer
blockSize =
String -> IOMode -> (Handle -> IO a) -> IO a
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile String
infp IOMode
ReadMode ((Handle -> IO a) -> IO a) -> (Handle -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Handle
inp -> do
Integer
count <- Handle -> IO Integer
hFileSize Handle
inp
(IO Iter -> IO a)
-> Socket -> Handle -> Integer -> Integer -> Integer -> IO a
forall a.
(IO Iter -> IO a)
-> Socket -> Handle -> Integer -> Integer -> Integer -> IO a
sendFileIterWith'' IO Iter -> IO a
stepper Socket
outs Handle
inp Integer
blockSize Integer
0 Integer
count
sendFile' :: Socket -> FilePath -> Integer -> Integer -> IO ()
sendFile' :: Socket -> String -> Integer -> Integer -> IO ()
sendFile' Socket
outs String
infp Integer
offset Integer
count =
String -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile String
infp IOMode
ReadMode ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Handle
inp ->
Socket -> Handle -> Integer -> Integer -> IO ()
sendFile'' Socket
outs Handle
inp Integer
offset Integer
count
sendFileIterWith' :: (IO Iter -> IO a) -> Socket -> FilePath -> Integer -> Integer -> Integer -> IO a
sendFileIterWith' :: (IO Iter -> IO a)
-> Socket -> String -> Integer -> Integer -> Integer -> IO a
sendFileIterWith' IO Iter -> IO a
stepper Socket
outs String
infp Integer
blockSize Integer
offset Integer
count =
String -> IOMode -> (Handle -> IO a) -> IO a
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile String
infp IOMode
ReadMode ((Handle -> IO a) -> IO a) -> (Handle -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Handle
inp ->
(IO Iter -> IO a)
-> Socket -> Handle -> Integer -> Integer -> Integer -> IO a
forall a.
(IO Iter -> IO a)
-> Socket -> Handle -> Integer -> Integer -> Integer -> IO a
sendFileIterWith'' IO Iter -> IO a
stepper Socket
outs Handle
inp Integer
blockSize Integer
offset Integer
count
unsafeSendFile :: Handle -> FilePath -> IO ()
unsafeSendFile :: Handle -> String -> IO ()
unsafeSendFile Handle
outp String
infp =
String -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile String
infp IOMode
ReadMode ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Handle
inp -> do
Integer
count <- Handle -> IO Integer
hFileSize Handle
inp
Handle -> Handle -> Integer -> Integer -> IO ()
unsafeSendFile'' Handle
outp Handle
inp Integer
0 Integer
count
unsafeSendFileIterWith :: (IO Iter -> IO a) -> Handle -> FilePath -> Integer -> IO a
unsafeSendFileIterWith :: (IO Iter -> IO a) -> Handle -> String -> Integer -> IO a
unsafeSendFileIterWith IO Iter -> IO a
stepper Handle
outp String
infp Integer
blockSize =
String -> IOMode -> (Handle -> IO a) -> IO a
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile String
infp IOMode
ReadMode ((Handle -> IO a) -> IO a) -> (Handle -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Handle
inp -> do
Integer
count <- Handle -> IO Integer
hFileSize Handle
inp
(IO Iter -> IO a)
-> Handle -> Handle -> Integer -> Integer -> Integer -> IO a
forall a.
(IO Iter -> IO a)
-> Handle -> Handle -> Integer -> Integer -> Integer -> IO a
unsafeSendFileIterWith'' IO Iter -> IO a
stepper Handle
outp Handle
inp Integer
blockSize Integer
0 Integer
count
unsafeSendFile'
:: Handle
-> FilePath
-> Integer
-> Integer
-> IO ()
unsafeSendFile' :: Handle -> String -> Integer -> Integer -> IO ()
unsafeSendFile' Handle
outp String
infp Integer
offset Integer
count =
String -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile String
infp IOMode
ReadMode ((Handle -> IO ()) -> IO ()) -> (Handle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Handle
inp -> do
Handle -> Handle -> Integer -> Integer -> IO ()
unsafeSendFile'' Handle
outp Handle
inp Integer
offset Integer
count
unsafeSendFileIterWith'
:: (IO Iter -> IO a)
-> Handle
-> FilePath
-> Integer
-> Integer
-> Integer
-> IO a
unsafeSendFileIterWith' :: (IO Iter -> IO a)
-> Handle -> String -> Integer -> Integer -> Integer -> IO a
unsafeSendFileIterWith' IO Iter -> IO a
stepper Handle
outp String
infp Integer
blockSize Integer
offset Integer
count =
String -> IOMode -> (Handle -> IO a) -> IO a
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile String
infp IOMode
ReadMode ((Handle -> IO a) -> IO a) -> (Handle -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Handle
inp -> do
(IO Iter -> IO a)
-> Handle -> Handle -> Integer -> Integer -> Integer -> IO a
forall a.
(IO Iter -> IO a)
-> Handle -> Handle -> Integer -> Integer -> Integer -> IO a
unsafeSendFileIterWith'' IO Iter -> IO a
stepper Handle
outp Handle
inp Integer
blockSize Integer
offset Integer
count