{-# LINE 1 "Network/Socket/Buffer.hsc" #-}{-# LANGUAGE CPP #-} #include "HsNetDef.h" {-# LINE 7 "Network/Socket/Buffer.hsc" #-}moduleNetwork.Socket.Buffer(sendBufTo ,sendBuf ,recvBufFrom ,recvBuf ,recvBufNoWait ,sendBufMsg ,recvBufMsg )where{-# LINE 19 "Network/Socket/Buffer.hsc" #-}importForeign.C.Error(getErrno,eAGAIN,eWOULDBLOCK){-# LINE 23 "Network/Socket/Buffer.hsc" #-}importForeign.Marshal.Alloc(alloca,allocaBytes)importForeign.Marshal.Utils(with)importGHC.IO.Exception(IOErrorType(InvalidArgument))importSystem.IO.Error(mkIOError,ioeSetErrorString,catchIOError){-# LINE 34 "Network/Socket/Buffer.hsc" #-}importNetwork.Socket.Posix.CmsgHdr importNetwork.Socket.Posix.MsgHdr importNetwork.Socket.Posix.IOVec {-# LINE 38 "Network/Socket/Buffer.hsc" #-}importNetwork.Socket.Imports importNetwork.Socket.Internal importNetwork.Socket.Name importNetwork.Socket.Types importNetwork.Socket.Flag {-# LINE 49 "Network/Socket/Buffer.hsc" #-}-- | Send data to the socket. The recipient can be specified-- explicitly, so the socket need not be in a connected state.-- Returns the number of bytes sent. Applications are responsible for-- ensuring that all data has been sent.sendBufTo ::SocketAddress sa =>Socket -- (possibly) bound/connected Socket->Ptra ->Int-- Data to send->sa ->IOInt-- Number of Bytes sentsendBufTo :: forall sa a. SocketAddress sa => Socket -> Ptr a -> Int -> sa -> IO Int sendBufTo Socket s Ptr a ptr Int nbytes sa sa =sa -> (Ptr sa -> Int -> IO Int) -> IO Int forall sa a. SocketAddress sa => sa -> (Ptr sa -> Int -> IO a) -> IO a withSocketAddress sa sa ((Ptr sa -> Int -> IO Int) -> IO Int) -> (Ptr sa -> Int -> IO Int) -> IO Int forall a b. (a -> b) -> a -> b $\Ptr sa p_sa Int siz ->CInt -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral(CInt -> Int) -> IO CInt -> IO Int forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>doSocket -> (CInt -> IO CInt) -> IO CInt forall r. Socket -> (CInt -> IO r) -> IO r withFdSocket Socket s ((CInt -> IO CInt) -> IO CInt) -> (CInt -> IO CInt) -> IO CInt forall a b. (a -> b) -> a -> b $\CInt fd ->doletsz :: CInt sz =Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegralInt siz n :: CSize n =Int -> CSize forall a b. (Integral a, Num b) => a -> b fromIntegralInt nbytes flags :: CInt flags =CInt 0Socket -> String -> IO CInt -> IO CInt forall a. (Eq a, Num a) => Socket -> String -> IO a -> IO a throwSocketErrorWaitWrite Socket s String "Network.Socket.sendBufTo"(IO CInt -> IO CInt) -> IO CInt -> IO CInt forall a b. (a -> b) -> a -> b $CInt -> Ptr a -> CSize -> CInt -> Ptr sa -> CInt -> IO CInt forall a sa. CInt -> Ptr a -> CSize -> CInt -> Ptr sa -> CInt -> IO CInt c_sendto CInt fd Ptr a ptr CSize n CInt flags Ptr sa p_sa CInt sz {-# LINE 76 "Network/Socket/Buffer.hsc" #-}-- | Send data to the socket. The socket must be connected to a remote-- socket. Returns the number of bytes sent. Applications are-- responsible for ensuring that all data has been sent.sendBuf ::Socket -- Bound/Connected Socket->PtrWord8-- Pointer to the data to send->Int-- Length of the buffer->IOInt-- Number of Bytes sentsendBuf :: Socket -> Ptr Word8 -> Int -> IO Int sendBuf Socket s Ptr Word8 str Int len =CInt -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral(CInt -> Int) -> IO CInt -> IO Int forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$>do{-# LINE 95 "Network/Socket/Buffer.hsc" #-}Socket -> (CInt -> IO CInt) -> IO CInt forall r. Socket -> (CInt -> IO r) -> IO r withFdSocket Socket s ((CInt -> IO CInt) -> IO CInt) -> (CInt -> IO CInt) -> IO CInt forall a b. (a -> b) -> a -> b $\CInt fd ->doletflags :: CInt flags =CInt 0clen :: CSize clen =Int -> CSize forall a b. (Integral a, Num b) => a -> b fromIntegralInt len Socket -> String -> IO CInt -> IO CInt forall a. (Eq a, Num a) => Socket -> String -> IO a -> IO a throwSocketErrorWaitWrite Socket s String "Network.Socket.sendBuf"(IO CInt -> IO CInt) -> IO CInt -> IO CInt forall a b. (a -> b) -> a -> b $CInt -> Ptr Word8 -> CSize -> CInt -> IO CInt forall a. CInt -> Ptr a -> CSize -> CInt -> IO CInt c_send CInt fd Ptr Word8 str CSize clen CInt flags {-# LINE 101 "Network/Socket/Buffer.hsc" #-}-- | Receive data from the socket, writing it into buffer instead of-- creating a new string. The socket need not be in a connected-- state. Returns @(nbytes, address)@ where @nbytes@ is the number of-- bytes received and @address@ is a 'SockAddr' representing the-- address of the sending socket.---- If the first return value is zero, it means EOF.---- For 'Stream' sockets, the second return value would be invalid.---- NOTE: blocking on Windows unless you compile with -threaded (see-- GHC ticket #1129)recvBufFrom ::SocketAddress sa =>Socket ->Ptra ->Int->IO(Int,sa )recvBufFrom :: forall sa a. SocketAddress sa => Socket -> Ptr a -> Int -> IO (Int, sa) recvBufFrom Socket s Ptr a ptr Int nbytes |Int nbytes Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <=Int 0=IOError -> IO (Int, sa) forall a. IOError -> IO a ioError(String -> IOError mkInvalidRecvArgError String "Network.Socket.recvBufFrom")|Bool otherwise=(Ptr sa -> Int -> IO (Int, sa)) -> IO (Int, sa) forall sa a. SocketAddress sa => (Ptr sa -> Int -> IO a) -> IO a withNewSocketAddress ((Ptr sa -> Int -> IO (Int, sa)) -> IO (Int, sa)) -> (Ptr sa -> Int -> IO (Int, sa)) -> IO (Int, sa) forall a b. (a -> b) -> a -> b $\Ptr sa ptr_sa Int sz ->(Ptr CInt -> IO (Int, sa)) -> IO (Int, sa) forall a b. Storable a => (Ptr a -> IO b) -> IO b alloca((Ptr CInt -> IO (Int, sa)) -> IO (Int, sa)) -> (Ptr CInt -> IO (Int, sa)) -> IO (Int, sa) forall a b. (a -> b) -> a -> b $\Ptr CInt ptr_len ->Socket -> (CInt -> IO (Int, sa)) -> IO (Int, sa) forall r. Socket -> (CInt -> IO r) -> IO r withFdSocket Socket s ((CInt -> IO (Int, sa)) -> IO (Int, sa)) -> (CInt -> IO (Int, sa)) -> IO (Int, sa) forall a b. (a -> b) -> a -> b $\CInt fd ->doPtr CInt -> CInt -> IO () forall a. Storable a => Ptr a -> a -> IO () pokePtr CInt ptr_len (Int -> CInt forall a b. (Integral a, Num b) => a -> b fromIntegralInt sz )letcnbytes :: CSize cnbytes =Int -> CSize forall a b. (Integral a, Num b) => a -> b fromIntegralInt nbytes flags :: CInt flags =CInt 0CInt len <-Socket -> String -> IO CInt -> IO CInt forall a. (Eq a, Num a) => Socket -> String -> IO a -> IO a throwSocketErrorWaitRead Socket s String "Network.Socket.recvBufFrom"(IO CInt -> IO CInt) -> IO CInt -> IO CInt forall a b. (a -> b) -> a -> b $CInt -> Ptr a -> CSize -> CInt -> Ptr sa -> Ptr CInt -> IO CInt forall a sa. CInt -> Ptr a -> CSize -> CInt -> Ptr sa -> Ptr CInt -> IO CInt c_recvfrom CInt fd Ptr a ptr CSize cnbytes CInt flags Ptr sa ptr_sa Ptr CInt ptr_len sa sockaddr <-Ptr sa -> IO sa forall sa. SocketAddress sa => Ptr sa -> IO sa peekSocketAddress Ptr sa ptr_sa IO sa -> (IOError -> IO sa) -> IO sa forall a. IO a -> (IOError -> IO a) -> IO a `catchIOError`\IOError _->Socket -> IO sa forall sa. SocketAddress sa => Socket -> IO sa getPeerName Socket s (Int, sa) -> IO (Int, sa) forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(CInt -> Int forall a b. (Integral a, Num b) => a -> b fromIntegralCInt len ,sa sockaddr )-- | Receive data from the socket. The socket must be in a connected-- state. This function may return fewer bytes than specified. If the-- message is longer than the specified length, it may be discarded-- depending on the type of socket. This function may block until a-- message arrives.---- Considering hardware and network realities, the maximum number of-- bytes to receive should be a small power of 2, e.g., 4096.---- The return value is the length of received data. Zero means-- EOF. Historical note: Version 2.8.x.y or earlier,-- an EOF error was thrown. This was changed in version 3.0.recvBuf ::Socket ->PtrWord8->Int->IOIntrecvBuf :: Socket -> Ptr Word8 -> Int -> IO Int recvBuf Socket s Ptr Word8 ptr Int nbytes |Int nbytes Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <=Int 0=IOError -> IO Int forall a. IOError -> IO a ioError(String -> IOError mkInvalidRecvArgError String "Network.Socket.recvBuf")|Bool otherwise=do{-# LINE 151 "Network/Socket/Buffer.hsc" #-}CInt len <-Socket -> (CInt -> IO CInt) -> IO CInt forall r. Socket -> (CInt -> IO r) -> IO r withFdSocket Socket s ((CInt -> IO CInt) -> IO CInt) -> (CInt -> IO CInt) -> IO CInt forall a b. (a -> b) -> a -> b $\CInt fd ->Socket -> String -> IO CInt -> IO CInt forall a. (Eq a, Num a) => Socket -> String -> IO a -> IO a throwSocketErrorWaitRead Socket s String "Network.Socket.recvBuf"(IO CInt -> IO CInt) -> IO CInt -> IO CInt forall a b. (a -> b) -> a -> b $CInt -> Ptr CChar -> CSize -> CInt -> IO CInt c_recv CInt fd (Ptr Word8 -> Ptr CChar forall a b. Ptr a -> Ptr b castPtrPtr Word8 ptr )(Int -> CSize forall a b. (Integral a, Num b) => a -> b fromIntegralInt nbytes )CInt 0{-flags-}{-# LINE 155 "Network/Socket/Buffer.hsc" #-}return$fromIntegrallen-- | Receive data from the socket. This function returns immediately-- even if data is not available. In other words, IO manager is NOT-- involved. The length of data is returned if received.-- -1 is returned in the case of EAGAIN or EWOULDBLOCK.-- -2 is returned in other error cases.recvBufNoWait ::Socket ->PtrWord8->Int->IOIntrecvBufNoWait :: Socket -> Ptr Word8 -> Int -> IO Int recvBufNoWait Socket s Ptr Word8 ptr Int nbytes =Socket -> (CInt -> IO Int) -> IO Int forall r. Socket -> (CInt -> IO r) -> IO r withFdSocket Socket s ((CInt -> IO Int) -> IO Int) -> (CInt -> IO Int) -> IO Int forall a b. (a -> b) -> a -> b $\CInt fd ->do{-# LINE 183 "Network/Socket/Buffer.hsc" #-}CInt r <-CInt -> Ptr CChar -> CSize -> CInt -> IO CInt c_recv CInt fd (Ptr Word8 -> Ptr CChar forall a b. Ptr a -> Ptr b castPtrPtr Word8 ptr )(Int -> CSize forall a b. (Integral a, Num b) => a -> b fromIntegralInt nbytes )CInt 0{-flags-}ifCInt r CInt -> CInt -> Bool forall a. Ord a => a -> a -> Bool >=CInt 0thenInt -> IO Int forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(Int -> IO Int) -> Int -> IO Int forall a b. (a -> b) -> a -> b $CInt -> Int forall a b. (Integral a, Num b) => a -> b fromIntegralCInt r elsedoErrno err <-IO Errno getErrnoifErrno err Errno -> Errno -> Bool forall a. Eq a => a -> a -> Bool ==Errno eAGAINBool -> Bool -> Bool ||Errno err Errno -> Errno -> Bool forall a. Eq a => a -> a -> Bool ==Errno eWOULDBLOCKthenInt -> IO Int forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(-Int 1)elseInt -> IO Int forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(-Int 2){-# LINE 193 "Network/Socket/Buffer.hsc" #-}mkInvalidRecvArgError ::String->IOErrormkInvalidRecvArgError :: String -> IOError mkInvalidRecvArgError String loc =IOError -> String -> IOError ioeSetErrorString(IOErrorType -> String -> Maybe Handle -> Maybe String -> IOError mkIOErrorIOErrorType InvalidArgumentString loc Maybe Handle forall a. Maybe a NothingMaybe String forall a. Maybe a Nothing)String "non-positive length"-- | Send data to the socket using sendmsg(2).sendBufMsg ::SocketAddress sa =>Socket -- ^ Socket->sa -- ^ Destination address->[(PtrWord8,Int)]-- ^ Data to be sent->[Cmsg ]-- ^ Control messages->MsgFlag -- ^ Message flags->IOInt-- ^ The length actually sentsendBufMsg :: forall sa. SocketAddress sa => Socket -> sa -> [(Ptr Word8, Int)] -> [Cmsg] -> MsgFlag -> IO Int sendBufMsg Socket s sa sa [(Ptr Word8, Int)] bufsizs [Cmsg] cmsgs MsgFlag flags =doCInt sz <-sa -> (Ptr sa -> Int -> IO CInt) -> IO CInt forall sa a. SocketAddress sa => sa -> (Ptr sa -> Int -> IO a) -> IO a withSocketAddress sa sa ((Ptr sa -> Int -> IO CInt) -> IO CInt) -> (Ptr sa -> Int -> IO CInt) -> IO CInt forall a b. (a -> b) -> a -> b $\Ptr sa addrPtr Int addrSize ->{-# LINE 210 "Network/Socket/Buffer.hsc" #-}withIOVecbufsizs$\(iovsPtr,iovsLen)->do{-# LINE 214 "Network/Socket/Buffer.hsc" #-}withCmsgscmsgs$\ctrlPtrctrlLen->doletmsgHdr=MsgHdr{msgName=addrPtr,msgNameLen=fromIntegraladdrSize{-# LINE 219 "Network/Socket/Buffer.hsc" #-},msgIov=iovsPtr,msgIovLen=fromIntegraliovsLen{-# LINE 225 "Network/Socket/Buffer.hsc" #-},msgCtrl=castPtrctrlPtr,msgCtrlLen=fromIntegralctrlLen,msgFlags=0}cflags=fromMsgFlagflagswithFdSockets$\fd->withmsgHdr$\msgHdrPtr->throwSocketErrorWaitWrites"Network.Socket.Buffer.sendMsg"${-# LINE 234 "Network/Socket/Buffer.hsc" #-}c_sendmsgfdmsgHdrPtrcflags{-# LINE 239 "Network/Socket/Buffer.hsc" #-}Int -> IO Int forall a. a -> IO a forall (m :: * -> *) a. Monad m => a -> m a return(Int -> IO Int) -> Int -> IO Int forall a b. (a -> b) -> a -> b $CInt -> Int forall a b. (Integral a, Num b) => a -> b fromIntegralCInt sz -- | Receive data from the socket using recvmsg(2). The supplied-- buffers are filled in order, with subsequent buffers used only-- after all the preceding buffers are full. If the message is short-- enough some of the supplied buffers may remain unused.recvBufMsg ::SocketAddress sa =>Socket -- ^ Socket->[(PtrWord8,Int)]-- ^ A list of (buffer, buffer-length) pairs.-- If the total length is not large enough,-- 'MSG_TRUNC' is returned->Int-- ^ The buffer size for control messages.-- If the length is not large enough,-- 'MSG_CTRUNC' is returned->MsgFlag -- ^ Message flags->IO(sa ,Int,[Cmsg ],MsgFlag )-- ^ Source address, total bytes received, control messages and message flagsrecvBufMsg :: forall sa. SocketAddress sa => Socket -> [(Ptr Word8, Int)] -> Int -> MsgFlag -> IO (sa, Int, [Cmsg], MsgFlag) recvBufMsg Socket s [(Ptr Word8, Int)] bufsizs Int clen MsgFlag flags =do(Ptr sa -> Int -> IO (sa, Int, [Cmsg], MsgFlag)) -> IO (sa, Int, [Cmsg], MsgFlag) forall sa a. SocketAddress sa => (Ptr sa -> Int -> IO a) -> IO a withNewSocketAddress ((Ptr sa -> Int -> IO (sa, Int, [Cmsg], MsgFlag)) -> IO (sa, Int, [Cmsg], MsgFlag)) -> (Ptr sa -> Int -> IO (sa, Int, [Cmsg], MsgFlag)) -> IO (sa, Int, [Cmsg], MsgFlag) forall a b. (a -> b) -> a -> b $\Ptr sa addrPtr Int addrSize ->Int -> (Ptr Any -> IO (sa, Int, [Cmsg], MsgFlag)) -> IO (sa, Int, [Cmsg], MsgFlag) forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytesInt clen ((Ptr Any -> IO (sa, Int, [Cmsg], MsgFlag)) -> IO (sa, Int, [Cmsg], MsgFlag)) -> (Ptr Any -> IO (sa, Int, [Cmsg], MsgFlag)) -> IO (sa, Int, [Cmsg], MsgFlag) forall a b. (a -> b) -> a -> b $\Ptr Any ctrlPtr ->{-# LINE 259 "Network/Socket/Buffer.hsc" #-}withIOVecbufsizs$\(iovsPtr,iovsLen)->doletmsgHdr=MsgHdr{msgName=addrPtr,msgNameLen=fromIntegraladdrSize,msgIov=iovsPtr,msgIovLen=fromIntegraliovsLen,msgCtrl=castPtrctrlPtr,msgCtrlLen=fromIntegralclen,msgFlags=0{-# LINE 279 "Network/Socket/Buffer.hsc" #-}}_cflags=fromMsgFlagflagswithFdSockets$\fd->dowithmsgHdr$\msgHdrPtr->dolen<-(fmapfromIntegral)<$>{-# LINE 285 "Network/Socket/Buffer.hsc" #-}throwSocketErrorWaitReads"Network.Socket.Buffer.recvmsg"$c_recvmsgfdmsgHdrPtr_cflags{-# LINE 293 "Network/Socket/Buffer.hsc" #-}sockaddr<-peekSocketAddressaddrPtr`catchIOError`\_->getPeerNameshdr<-peekmsgHdrPtrcmsgs<-parseCmsgsmsgHdrPtrletflags'=MsgFlag$fromIntegral$msgFlagshdrreturn(sockaddr,len,cmsgs,flags'){-# LINE 300 "Network/Socket/Buffer.hsc" #-}foreignimportccallunsafe"send"c_send::CInt->Ptra->CSize->CInt->IOCIntforeignimportccallunsafe"sendmsg"c_sendmsg ::CInt->Ptr(MsgHdr sa )->CInt->IOCInt-- fixme CSsizeforeignimportccallunsafe"recvmsg"c_recvmsg ::CInt->Ptr(MsgHdr sa )->CInt->IOCInt{-# LINE 317 "Network/Socket/Buffer.hsc" #-}foreignimportccallunsafe"recv"c_recv ::CInt->PtrCChar->CSize->CInt->IOCIntforeignimportCALLCONVSAFE_ON_WIN"sendto"c_sendto ::CInt->Ptra ->CSize->CInt->Ptrsa ->CInt->IOCIntforeignimportCALLCONVSAFE_ON_WIN"recvfrom"c_recvfrom ::CInt->Ptra ->CSize->CInt->Ptrsa ->PtrCInt->IOCInt