{-# 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.CmsgHdrimportNetwork.Socket.Posix.MsgHdrimportNetwork.Socket.Posix.IOVec{-# LINE 38 "Network/Socket/Buffer.hsc" #-}importNetwork.Socket.ImportsimportNetwork.Socket.InternalimportNetwork.Socket.NameimportNetwork.Socket.TypesimportNetwork.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::SocketAddresssa=>Socket-- (possibly) bound/connected Socket->Ptra->Int-- Data to send->sa->IOInt-- Number of Bytes sentsendBufTosptrnbytessa=withSocketAddresssa$\p_sasiz->fromIntegral<$>dowithFdSockets$\fd->doletsz=fromIntegralsizn=fromIntegralnbytesflags=0throwSocketErrorWaitWrites"Network.Socket.sendBufTo"$c_sendtofdptrnflagsp_sasz{-# 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 sentsendBufsstrlen=fromIntegral<$>do{-# LINE 95 "Network/Socket/Buffer.hsc" #-}withFdSockets$\fd->doletflags=0clen=fromIntegrallenthrowSocketErrorWaitWrites"Network.Socket.sendBuf"$c_sendfdstrclenflags{-# 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::SocketAddresssa=>Socket->Ptra->Int->IO(Int,sa)recvBufFromsptrnbytes|nbytes<=0=ioError(mkInvalidRecvArgError"Network.Socket.recvBufFrom")|otherwise=withNewSocketAddress$\ptr_sasz->alloca$\ptr_len->withFdSockets$\fd->dopokeptr_len(fromIntegralsz)letcnbytes=fromIntegralnbytesflags=0len<-throwSocketErrorWaitReads"Network.Socket.recvBufFrom"$c_recvfromfdptrcnbytesflagsptr_saptr_lensockaddr<-peekSocketAddressptr_sa`catchIOError`\_->getPeerNamesreturn(fromIntegrallen,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->IOIntrecvBufsptrnbytes|nbytes<=0=ioError(mkInvalidRecvArgError"Network.Socket.recvBuf")|otherwise=do{-# LINE 151 "Network/Socket/Buffer.hsc" #-}len<-withFdSockets$\fd->throwSocketErrorWaitReads"Network.Socket.recvBuf"$c_recvfd(castPtrptr)(fromIntegralnbytes)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->IOIntrecvBufNoWaitsptrnbytes=withFdSockets$\fd->do{-# LINE 183 "Network/Socket/Buffer.hsc" #-}r<-c_recvfd(castPtrptr)(fromIntegralnbytes)0{-flags-}ifr>=0thenreturn$fromIntegralrelsedoerr<-getErrnoiferr==eAGAIN||err==eWOULDBLOCKthenreturn(-1)elsereturn(-2){-# LINE 193 "Network/Socket/Buffer.hsc" #-}mkInvalidRecvArgError::String->IOErrormkInvalidRecvArgErrorloc=ioeSetErrorString(mkIOErrorInvalidArgumentlocNothingNothing)"non-positive length"-- | Send data to the socket using sendmsg(2).sendBufMsg::SocketAddresssa=>Socket-- ^ Socket->sa-- ^ Destination address->[(PtrWord8,Int)]-- ^ Data to be sent->[Cmsg]-- ^ Control messages->MsgFlag-- ^ Message flags->IOInt-- ^ The length actually sentsendBufMsgssabufsizscmsgsflags=dosz<-withSocketAddresssa$\addrPtraddrSize->{-# 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" #-}return$fromIntegralsz-- | 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::SocketAddresssa=>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 flagsrecvBufMsgsbufsizsclenflags=dowithNewSocketAddress$\addrPtraddrSize->allocaBytesclen$\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(MsgHdrsa)->CInt->IOCInt-- fixme CSsizeforeignimportccallunsafe"recvmsg"c_recvmsg::CInt->Ptr(MsgHdrsa)->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