Is there a non-blocking version of hGetArray?

Tomasz Zielonka t.zielonka at students.mimuw.edu.pl
Sat Oct 2 08:04:19 EDT 2004


On Fri, Oct 01, 2004 at 09:34:36PM +0100, Simon Marlow wrote:
> 
> Not currently, but I could probably implement the equivalent
> (hGetArrayNonBlocking).

It is perhaps not closely related, but could we also have Network.Socket
recvFrom / sendTo working on raw buffers?

I've attached a proposed implementation. It moves most of code to
recvBufFrom and sendBufTo, and changes recvFrom / sendTo to use the
*Buf* functions.

It would be nice if these functions could be used to implement efficient
recvFromArray / sendToArray (without copying), but I don't know if it's
possible to get the pointer from MutableByteArray. Is there a danger
that GC invalidates the pointer?

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
-------------- next part --------------
--- libraries/network/Network/Socket.hsc	2003-10-20 13:18:30.000000000 +0200
+++ Socket.hsc	2004-10-02 13:53:40.000000000 +0200
@@ -74,7 +74,10 @@
     socketToHandle,	-- :: Socket -> IOMode -> IO Handle
 
     sendTo,		-- :: Socket -> String -> SockAddr -> IO Int
+    sendBufTo,          -- :: Socket -> Ptr CChar -> Int -> SockAddr -> IO Int
+
     recvFrom,		-- :: Socket -> Int -> IO (String, Int, SockAddr)
+    recvBufFrom,        -- :: Socket -> Int -> Ptr CChar -> IO (Int, SockAddr)
     
     send,		-- :: Socket -> String -> IO Int
     recv,		-- :: Socket -> Int    -> IO String
@@ -626,22 +629,36 @@
        -> SockAddr
        -> IO Int	-- Number of Bytes sent
 
-sendTo (MkSocket s _family _stype _protocol status) xs addr = do
- withSockAddr addr $ \p_addr sz -> do
+sendTo sock xs addr = do
  withCString xs $ \str -> do
+   sendBufTo sock str (length xs) addr
+
+sendBufTo :: Socket	      -- (possibly) bound/connected Socket
+          -> Ptr CChar -> Int -- Data to send
+          -> SockAddr
+          -> IO Int	      -- Number of Bytes sent
+
+sendBufTo (MkSocket s _family _stype _protocol status) ptr nbytes addr = do
+ withSockAddr addr $ \p_addr sz -> do
    liftM fromIntegral $
 #if !defined(__HUGS__)
      throwErrnoIfMinus1Retry_repeatOnBlock "sendTo"
 	(threadWaitWrite (fromIntegral s)) $
 #endif
-	c_sendto s str (fromIntegral $ length xs) 0{-flags-} 
+	c_sendto s ptr (fromIntegral $ nbytes) 0{-flags-} 
 			p_addr (fromIntegral sz)
 
 recvFrom :: Socket -> Int -> IO (String, Int, SockAddr)
-recvFrom sock@(MkSocket s _family _stype _protocol status) nbytes
+recvFrom sock nbytes =
+  allocaBytes nbytes $ \ptr -> do
+    (len, sockaddr) <- recvBufFrom sock nbytes ptr
+    str <- peekCStringLen (ptr, len)
+    return (str, len, sockaddr)
+
+recvBufFrom :: Socket -> Int -> Ptr CChar -> IO (Int, SockAddr)
+recvBufFrom sock@(MkSocket s _family _stype _protocol status) nbytes ptr
  | nbytes <= 0 = ioError (mkInvalidRecvArgError "Network.Socket.recvFrom")
  | otherwise   = 
-  allocaBytes nbytes $ \ptr -> do
     withNewSockAddr AF_INET $ \ptr_addr sz -> do
       alloca $ \ptr_len -> do
       	poke ptr_len (fromIntegral sz)
@@ -665,8 +682,7 @@
 		   getPeerName sock
 		else
 		   peekSockAddr ptr_addr 
-           str <- peekCStringLen (ptr,len')
-           return (str, len', sockaddr)
+           return (len', sockaddr)
 
 -----------------------------------------------------------------------------
 -- send & recv


More information about the Glasgow-haskell-users mailing list