[Haskell-cafe] test socket buffer full

Alberto G. Corona agocorona at gmail.com
Thu Sep 17 17:17:19 UTC 2015


I came up with this implementation below, that  theoretically flush the
buffer non blocking



hPutBufNonBlocking handle ptr count
  | count == 0 = return 0
  | count <  0 = error "negative chunk size"
  | otherwise =
    wantWritableHandle "hPutBuf" handle $
      \ h_ at Handle__{..} -> bufWriteNonBlocking h_ (castPtr ptr) count False



bufWriteNonBlocking :: Handle__-> Ptr Word8 -> Int -> Bool -> IO Int
bufWriteNonBlocking h_ at Handle__{..} ptr count can_block =
  seq count $ do  -- strictness hack
  old_buf at Buffer{  bufR=w, bufSize=size }  <- readIORef haByteBuffer
  -- print (size,w, count)
  old_buf'@Buffer{  bufR=w', bufSize = size' } <-
        if size - w <= count
          then   do
            (written,old_buf') <- Buffered.flushWriteBuffer0 haDevice
old_buf
            writeIORef haByteBuffer old_buf'
            print (size , written,w, count)
            print (bufSize old_buf', bufR old_buf')
            return old_buf'
          else return old_buf

  let count'= if size' - w' > count then count else size' - w'
  writeChunkNonBlocking h_ (castPtr ptr) count'
  writeIORef haByteBuffer old_buf'{ bufR = w' + count' }

  return count'



writeChunkNonBlocking h_ at Handle__{..} ptr bytes
  | Just fd <- cast haDevice  =  RawIO.writeNonBlocking (fd::FD) ptr bytes
  | otherwise = error "Todo: hPutBuf"

But:

flushWriteBuffer0
<http://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.IO.BufferedIO.html#flushWriteBuffer0>
 :: dev
<http://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.IO.BufferedIO.html#local-1627535594>
 -> Buffer
<http://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.IO.Buffer.html#Buffer>
 Word8
<http://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.Word.html#Word8>
 -> IO (Int, Buffer
<http://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.IO.Buffer.html#Buffer>
 Word8
<http://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.Word.html#Word8>
)

-- | Flush data from the supplied write buffer out to the device  --
without blocking.  Returns the number of bytes written and the  --
remaining buffer.

should flush  the send buffer as much as possible without waiting for
enough available space in the device/receiving side to empty the send buffer

but it blocks as well (at least using sockets), and waits until the whole
send buffer is emptied, just like ffunshWriteBuffer.

So it is not possible for the application to know if both buffers are
full.  It can be ckecked if the send buffer is full before flushing, but
the device buffers and the receiving buffer may be  empty, and the
receiving process idle. In the other side, if the buffer is flushed, since
it blocks, the send buffer will appear empty after blocking for some time.
So the process can do nothing to detect the congestion condition and it
will be non responsive to other events.

Can fusshWriteBuffer0 and hPutBufNonBlocking be fixed?

2015-09-17 16:08 GMT+02:00 Alberto G. Corona <agocorona at gmail.com>:

> It could be, since this module is general for any kind of buffered IO
>
>
> 2015-09-17 16:04 GMT+02:00 Brandon Allbery <allbery.b at gmail.com>:
>
>> On Thu, Sep 17, 2015 at 10:01 AM, Alberto G. Corona <agocorona at gmail.com>
>> wrote:
>>
>>> since the flush uses flushWriteBuffer
>>> <https://hackage.haskell.org/package/base-4.8.1.0/docs/src/GHC.IO.BufferedIO.html#flushWriteBuffer>
>>>
>>> , that blocks,  hPutBuffNonBlocking does the same than hPutBuff and the
>>> buffer congestion can not be detected.
>>>
>>
>> Hm. I wonder if this is the DynamicLog bug we've been fighting with in
>> xmonad, too. (pipe full -> xmonad locks up, blocked on pipe write)
>>
>> --
>> brandon s allbery kf8nh                               sine nomine
>> associates
>> allbery.b at gmail.com
>> ballbery at sinenomine.net
>> unix, openafs, kerberos, infrastructure, xmonad
>> http://sinenomine.net
>>
>
>
>
> --
> Alberto.
>



-- 
Alberto.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150917/0e048dfc/attachment.html>


More information about the Haskell-Cafe mailing list