{-# LANGUAGE CPP #-}
module Network.Socket.ByteString.Lazy (
send
, sendAll
, sendWithFds
, getContents
, recv
) where
import Data.ByteString.Lazy.Internal (ByteString(..), defaultChunkSize)
import Network.Socket (ShutdownCmd (..), shutdown)
import Prelude hiding (getContents)
import System.IO.Unsafe (unsafeInterleaveIO)
import System.IO.Error (catchIOError)
import System.Posix.Types (Fd(..))
#if defined(mingw32_HOST_OS)
import Network.Socket.ByteString.Lazy.Windows (send, sendAll)
#else
import Network.Socket.ByteString.Lazy.Posix (send, sendAll)
#endif
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L
import qualified Network.Socket.ByteString as N
import Network.Socket.Imports
import Network.Socket.Types
sendWithFds :: Socket
-> ByteString
-> [Fd]
-> IO ()
sendWithFds :: Socket -> ByteString -> [Fd] -> IO ()
sendWithFds Socket
s ByteString
lbs [Fd]
fds = Socket -> [ByteString] -> [Fd] -> IO ()
N.sendManyWithFds Socket
s (ByteString -> [ByteString]
L.toChunks ByteString
lbs) [Fd]
fds
getContents
:: Socket
-> IO ByteString
getContents :: Socket -> IO ByteString
getContents Socket
s = IO ByteString
loop
where
loop :: IO ByteString
loop = IO ByteString -> IO ByteString
forall a. IO a -> IO a
unsafeInterleaveIO (IO ByteString -> IO ByteString) -> IO ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$ do
ByteString
sbs <- Socket -> Int -> IO ByteString
N.recv Socket
s Int
defaultChunkSize
if ByteString -> Bool
S.null ByteString
sbs
then do
Socket -> ShutdownCmd -> IO ()
shutdown Socket
s ShutdownCmd
ShutdownReceive IO () -> (IOError -> IO ()) -> IO ()
forall a. IO a -> (IOError -> IO a) -> IO a
`catchIOError` IO () -> IOError -> IO ()
forall a b. a -> b -> a
const (() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ())
ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
Empty
else ByteString -> ByteString -> ByteString
Chunk ByteString
sbs (ByteString -> ByteString) -> IO ByteString -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO ByteString
loop
recv
:: Socket
-> Int64
-> IO ByteString
recv :: Socket -> Int64 -> IO ByteString
recv Socket
s Int64
nbytes = ByteString -> ByteString
chunk (ByteString -> ByteString) -> IO ByteString -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Socket -> Int -> IO ByteString
N.recv Socket
s (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
nbytes)
where
chunk :: ByteString -> ByteString
chunk ByteString
k | ByteString -> Bool
S.null ByteString
k = ByteString
Empty
| Bool
otherwise = ByteString -> ByteString -> ByteString
Chunk ByteString
k ByteString
Empty