{-# LINE 1 "Network/Socket/Buffer.hsc" #-}
{-# LANGUAGE CPP #-}
#include "HsNetDef.h"
{-# LINE 7 "Network/Socket/Buffer.hsc" #-}
module Network.Socket.Buffer (
sendBufTo
, sendBuf
, recvBufFrom
, recvBuf
, recvBufNoWait
) where
{-# LINE 17 "Network/Socket/Buffer.hsc" #-}
import Foreign.C.Error (getErrno, eAGAIN, eWOULDBLOCK)
{-# LINE 19 "Network/Socket/Buffer.hsc" #-}
import Foreign.Marshal.Alloc (alloca)
import GHC.IO.Exception (IOErrorType(InvalidArgument))
import System.IO.Error (mkIOError, ioeSetErrorString, catchIOError)
{-# LINE 26 "Network/Socket/Buffer.hsc" #-}
import Network.Socket.Imports
import Network.Socket.Internal
import Network.Socket.Name
import Network.Socket.Types
sendBufTo :: SocketAddress sa =>
Socket
-> Ptr a
-> Int
-> sa
-> IO Int
sendBufTo s ptr nbytes sa =
withSocketAddress sa $ \p_sa siz -> fromIntegral <$> do
withFdSocket s $ \fd -> do
let sz = fromIntegral siz
n = fromIntegral nbytes
flags = 0
throwSocketErrorWaitWrite s "Network.Socket.sendBufTo" $
c_sendto fd ptr n flags p_sa sz
{-# LINE 58 "Network/Socket/Buffer.hsc" #-}
sendBuf :: Socket
-> Ptr Word8
-> Int
-> IO Int
sendBuf s str len = fromIntegral <$> do
{-# LINE 77 "Network/Socket/Buffer.hsc" #-}
withFdSocket s $ \fd -> do
let flags = 0
clen = fromIntegral len
throwSocketErrorWaitWrite s "Network.Socket.sendBuf" $
c_send fd str clen flags
{-# LINE 83 "Network/Socket/Buffer.hsc" #-}
recvBufFrom :: SocketAddress sa => Socket -> Ptr a -> Int -> IO (Int, sa)
recvBufFrom s ptr nbytes
| nbytes <= 0 = ioError (mkInvalidRecvArgError "Network.Socket.recvBufFrom")
| otherwise = withNewSocketAddress $ \ptr_sa sz -> alloca $ \ptr_len ->
withFdSocket s $ \fd -> do
poke ptr_len (fromIntegral sz)
let cnbytes = fromIntegral nbytes
flags = 0
len <- throwSocketErrorWaitRead s "Network.Socket.recvBufFrom" $
c_recvfrom fd ptr cnbytes flags ptr_sa ptr_len
sockaddr <- peekSocketAddress ptr_sa
`catchIOError` \_ -> getPeerName s
return (fromIntegral len, sockaddr)
recvBuf :: Socket -> Ptr Word8 -> Int -> IO Int
recvBuf s ptr nbytes
| nbytes <= 0 = ioError (mkInvalidRecvArgError "Network.Socket.recvBuf")
| otherwise = do
{-# LINE 133 "Network/Socket/Buffer.hsc" #-}
len <- withFdSocket s $ \fd ->
throwSocketErrorWaitRead s "Network.Socket.recvBuf" $
c_recv fd (castPtr ptr) (fromIntegral nbytes) 0
{-# LINE 137 "Network/Socket/Buffer.hsc" #-}
return $ fromIntegral len
recvBufNoWait :: Socket -> Ptr Word8 -> Int -> IO Int
recvBufNoWait s ptr nbytes = withFdSocket s $ \fd -> do
{-# LINE 165 "Network/Socket/Buffer.hsc" #-}
r <- c_recv fd (castPtr ptr) (fromIntegral nbytes) 0
if r >= 0 then
return $ fromIntegral r
else do
err <- getErrno
if err == eAGAIN || err == eWOULDBLOCK then
return (-1)
else
return (-2)
{-# LINE 175 "Network/Socket/Buffer.hsc" #-}
mkInvalidRecvArgError :: String -> IOError
mkInvalidRecvArgError loc = ioeSetErrorString (mkIOError
InvalidArgument
loc Nothing Nothing) "non-positive length"
{-# LINE 182 "Network/Socket/Buffer.hsc" #-}
foreign import ccall unsafe "send"
c_send :: CInt -> Ptr a -> CSize -> CInt -> IO CInt
{-# LINE 190 "Network/Socket/Buffer.hsc" #-}
foreign import ccall unsafe "recv"
c_recv :: CInt -> Ptr CChar -> CSize -> CInt -> IO CInt
foreign import CALLCONV SAFE_ON_WIN "sendto"
c_sendto :: CInt -> Ptr a -> CSize -> CInt -> Ptr sa -> CInt -> IO CInt
foreign import CALLCONV SAFE_ON_WIN "recvfrom"
c_recvfrom :: CInt -> Ptr a -> CSize -> CInt -> Ptr sa -> Ptr CInt -> IO CInt