RE: Is there a non-blocking version of hGetArray?

2004-10-05 Thread Simon Marlow
On 02 October 2004 13:04, Tomasz Zielonka wrote:

 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.

Committed, thanks!
 
 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?

It is possible to get a Ptr from a MutableByteArray, but only if the
array was allocated pinned, and only if you make sure it lives across
any foreign calls (using touch#).  This is how Foreign.alloca works, for
example.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Is there a non-blocking version of hGetArray?

2004-10-03 Thread Peter Simons
Simon Marlow writes:

  I'm surprised if pointer access to memory is slower
  than unsafeRead.

You were right. Now that I have made some tests, the
problem turned out to be elsewhere. Pointer access is
not to blame. ;-)

Peter

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Is there a non-blocking version of hGetArray?

2004-10-02 Thread Tomasz Zielonka
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
--- libraries/network/Network/Socket.hsc2003-10-20 13:18:30.0 +0200
+++ Socket.hsc  2004-10-02 13:53:40.0 +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
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Is there a non-blocking version of hGetArray?

2004-10-02 Thread Tomasz Zielonka
On Sat, Oct 02, 2004 at 02:04:19PM +0200, Tomasz Zielonka wrote:
 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.

I reversed the order of ptr and nbytes parameters to recvFromBuf to
match the order used by hGetBuf and hPutBuf.

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
--- libraries/network/Network/Socket.hsc2003-10-20 13:18:30.0 +0200
+++ Socket.hsc  2004-10-02 14:04:19.0 +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 - Ptr CChar - Int - 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 ptr nbytes
+str - peekCStringLen (ptr, len)
+return (str, len, sockaddr)
+
+recvBufFrom :: Socket - Ptr CChar - Int - IO (Int, SockAddr)
+recvBufFrom sock@(MkSocket s _family _stype _protocol status) ptr nbytes
  | 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
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Is there a non-blocking version of hGetArray?

2004-10-01 Thread Simon Marlow
On 01 October 2004 08:45, Peter Simons wrote:

 I am a happy user of hGetBufNonBlocking, but I have come to
 realize that mutable arrays are nicer to work with than
 pointers, so I have considered using hGetArray instead. I
 do, however, depend on the fact that the function returns as
 soon as it has read data -- even if less than requested --,
 like hGetBufNonBlocking does.
 
 Is there currently a way to achieve this?

Not currently, but I could probably implement the equivalent
(hGetArrayNonBlocking).

 Am I right assuming that hGetBuf and hGetArray do not differ
 much performance-wise?

Hopefully not.

 One of the reasons I am curious about using mutable arrays
 is because of Data.Array.Base.unsafeRead, which seems to be
 a *lot* faster than accessing the memory through a pointer.
 Is there anything comparable for pointer access?

I'm surprised if pointer access to memory is slower than unsafeRead.
Could you post some code that we can peer at?

Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Is there a non-blocking version of hGetArray?

2004-10-01 Thread Peter Simons
Simon Marlow writes:

  Not currently, but I could probably implement the
  equivalent (hGetArrayNonBlocking).

If that were possible, I'd greatly appreciate it.


  I'm surprised if pointer access to memory is slower than
  unsafeRead. Could you post some code that we can peer at?

Not right now, sorry. It's just a suspicion I have, but I
haven't broken down the functions enough to be certain (or
to post an isolated test case). But I will look at this
further and let you know about it, once I have more
evidence. :-)

Thanks for helping, Simon.

Peter

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Is there a non-blocking version of hGetArray?

2004-10-01 Thread Peter Simons
Hi,

I am a happy user of hGetBufNonBlocking, but I have come to
realize that mutable arrays are nicer to work with than
pointers, so I have considered using hGetArray instead. I
do, however, depend on the fact that the function returns as
soon as it has read data -- even if less than requested --,
like hGetBufNonBlocking does.

Is there currently a way to achieve this?

Am I right assuming that hGetBuf and hGetArray do not differ
much performance-wise?

One of the reasons I am curious about using mutable arrays
is because of Data.Array.Base.unsafeRead, which seems to be
a *lot* faster than accessing the memory through a pointer.
Is there anything comparable for pointer access?

Peter

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users