Safe Haskell | None |
---|---|
Language | Haskell2010 |
A ByteBuffer
is a simple buffer for bytes. It supports two
operations: refilling with the contents of a ByteString
, and
consuming a fixed number of bytes.
It is implemented as a pointer, together with counters that keep track
of the offset and the number of bytes in the buffer. Note that the
counters are simple IORef
s, so ByteBuffer
s are not thread-safe!
A ByteBuffer
is constructed by new
with a given starting length,
and will grow (by repeatedly multiplying its size by 1.5) whenever it
is being fed a ByteString
that is too large.
Synopsis
- type ByteBuffer = IORef (Either ByteBufferException BBRef)
- new :: MonadIO m => Maybe Int -> m ByteBuffer
- free :: MonadIO m => ByteBuffer -> m ()
- with :: (MonadIO m, MonadBaseControl IO m) => Maybe Int -> (ByteBuffer -> m a) -> m a
- totalSize :: MonadIO m => ByteBuffer -> m Int
- isEmpty :: MonadIO m => ByteBuffer -> m Bool
- availableBytes :: MonadIO m => ByteBuffer -> m Int
- copyByteString :: MonadIO m => ByteBuffer -> ByteString -> m ()
- fillFromFd :: MonadIO m => ByteBuffer -> Fd -> Int -> m Int
- consume :: MonadIO m => ByteBuffer -> Int -> m (Either Int ByteString)
- unsafeConsume :: MonadIO m => ByteBuffer -> Int -> m (Either Int (Ptr Word8))
- data ByteBufferException = ByteBufferException {
- _bbeLocation :: !String
- _bbeException :: !String
Documentation
type ByteBuffer = IORef (Either ByteBufferException BBRef) Source #
Allocation and Deallocation
:: MonadIO m | |
=> Maybe Int | Size of buffer to allocate. If |
-> m ByteBuffer | The byte buffer. |
Allocates a new ByteBuffer with a given buffer size filling from the given FillBuffer.
Note that ByteBuffer
s created with new
have to be deallocated
explicitly using free
. For automatic deallocation, consider
using with
instead.
free :: MonadIO m => ByteBuffer -> m () Source #
Free a byte buffer.
:: (MonadIO m, MonadBaseControl IO m) | |
=> Maybe Int | Initial length of the |
-> (ByteBuffer -> m a) | |
-> m a |
Perform some action with a bytebuffer, with automatic allocation and deallocation.
Query for number of available bytes
availableBytes :: MonadIO m => ByteBuffer -> m Int Source #
Number of available bytes in a ByteBuffer
(that is, bytes that
have been copied to, but not yet read from the ByteBuffer
.
Feeding new input
copyByteString :: MonadIO m => ByteBuffer -> ByteString -> m () Source #
Copy the contents of a ByteString
to a ByteBuffer
.
If necessary, the ByteBuffer
is enlarged and/or already consumed
bytes are dropped.
fillFromFd :: MonadIO m => ByteBuffer -> Fd -> Int -> m Int Source #
Will read at most n bytes from the given Fd
, in a non-blocking
fashion. This function is intended to be used with non-blocking Socket
s,
such the ones created by the network
package.
Returns how many bytes could be read non-blockingly.
Consuming bytes from the buffer
consume :: MonadIO m => ByteBuffer -> Int -> m (Either Int ByteString) Source #
As unsafeConsume
, but instead of returning a Ptr
into the
contents of the ByteBuffer
, it returns a ByteString
containing
the next n
bytes in the buffer. This involves allocating a new
ByteString
and copying the n
bytes to it.
:: MonadIO m | |
=> ByteBuffer | |
-> Int | n |
-> m (Either Int (Ptr Word8)) | Will be |
Try to get a pointer to n
bytes from the ByteBuffer
.
Note that the pointer should be used before any other actions are
performed on the ByteBuffer
. It points to some address within the
buffer, so operations such as enlarging the buffer or feeding it
new data will change the data the pointer points to. This is why
this function is called unsafe.
Exceptions
data ByteBufferException Source #
Exception that is thrown when an invalid ByteBuffer
is being used that is no longer valid.
A ByteBuffer
is considered to be invalid if
- it has explicitly been freed
- an Exception has occured during an operation that modified it
ByteBufferException | |
|
Instances
Eq ByteBufferException Source # | |
Defined in System.IO.ByteBuffer (==) :: ByteBufferException -> ByteBufferException -> Bool # (/=) :: ByteBufferException -> ByteBufferException -> Bool # | |
Show ByteBufferException Source # | |
Defined in System.IO.ByteBuffer showsPrec :: Int -> ByteBufferException -> ShowS # show :: ByteBufferException -> String # showList :: [ByteBufferException] -> ShowS # | |
Exception ByteBufferException Source # | |
Defined in System.IO.ByteBuffer |