| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Haskus.Binary.Serialize.Buffer
Contents
Description
Serializer into a mutable buffer
>>>let w = do putWord8 0x01 ; putWord32BE 0x23456789 ; putWord32BE 0xAABBCCDD>>>b <- newBuffer 10>>>void $ runBufferPut b 0 overflowBufferFail w>>>xs <- forM [0..4] (bufferReadWord8IO b)>>>xs == [0x01,0x23,0x45,0x67,0x89]True
>>>b <- newBuffer 2 -- small buffer>>>(_,b',_) <- runBufferPut b 0 overflowBufferDouble w>>>xs <- forM [0..4] (bufferReadWord8IO b')>>>xs == [0x01,0x23,0x45,0x67,0x89]True>>>bufferSizeIO b'16
Synopsis
- newtype BufferPutT b m a = BufferPutT (StateT (BufferPutState m b) m a)
- type BufferPut b a = BufferPutT b Identity a
- getPutOffset :: Monad m => BufferPutT b m Word
- getPutBuffer :: Monad m => BufferPutT b m b
- setPutOffset :: Monad m => Word -> BufferPutT b m ()
- runBufferPut :: Monad m => b -> Word -> OverflowStrategy m b -> BufferPutT b m a -> m (a, b, Word)
- liftBufferPut :: Monad m => m a -> BufferPutT b m a
- newtype BufferGetT b m a = BufferGetT (StateT (BufferGetState m b) m a)
- type BufferGet b a = BufferGetT b Identity a
- getGetOffset :: Monad m => BufferGetT b m Word
- getGetBuffer :: Monad m => BufferGetT b m b
- setGetOffset :: Monad m => Word -> BufferGetT b m ()
- runBufferGet :: Monad m => b -> Word -> OverflowStrategy m b -> BufferGetT b m a -> m (a, b, Word)
- liftBufferGet :: Monad m => m a -> BufferGetT b m a
- newtype OverflowStrategy m b = OverflowStrategy (BufferOverflow b -> m (b, Word))
- data BufferOverflow b = BufferOverflow {- overflowBuffer :: b
- overflowOffset :: Word
- overflowRequired :: Word
 
- getPutOverflowStrategy :: Monad m => BufferPutT b m (OverflowStrategy m b)
- getGetOverflowStrategy :: Monad m => BufferGetT b m (OverflowStrategy m b)
- overflowBufferFail :: MonadFail m => OverflowStrategy m b
- overflowBufferDouble :: MonadIO m => OverflowStrategy m BufferM
- overflowBufferDoublePinned :: MonadIO m => Maybe Word -> OverflowStrategy m BufferMP
- overflowBufferAdd :: MonadIO m => Word -> OverflowStrategy m BufferM
- overflowBufferAddPinned :: MonadIO m => Maybe Word -> Word -> OverflowStrategy m BufferMP
Put
newtype BufferPutT b m a Source #
A Put monad than fails when there is not enough space in the target buffer
Constructors
| BufferPutT (StateT (BufferPutState m b) m a) | 
Instances
type BufferPut b a = BufferPutT b Identity a Source #
getPutOffset :: Monad m => BufferPutT b m Word Source #
Get current offset
getPutBuffer :: Monad m => BufferPutT b m b Source #
Get buffer
setPutOffset :: Monad m => Word -> BufferPutT b m () Source #
Get current offset
runBufferPut :: Monad m => b -> Word -> OverflowStrategy m b -> BufferPutT b m a -> m (a, b, Word) Source #
Run a buffer put
liftBufferPut :: Monad m => m a -> BufferPutT b m a Source #
Lift into BufferPutT
Get
newtype BufferGetT b m a Source #
A Get monad over a Buffer
Constructors
| BufferGetT (StateT (BufferGetState m b) m a) | 
Instances
type BufferGet b a = BufferGetT b Identity a Source #
getGetOffset :: Monad m => BufferGetT b m Word Source #
Get current offset
getGetBuffer :: Monad m => BufferGetT b m b Source #
Get buffer
setGetOffset :: Monad m => Word -> BufferGetT b m () Source #
Get current offset
runBufferGet :: Monad m => b -> Word -> OverflowStrategy m b -> BufferGetT b m a -> m (a, b, Word) Source #
Run a buffer get
liftBufferGet :: Monad m => m a -> BufferGetT b m a Source #
Lift into BufferGetT
Buffer overflow
newtype OverflowStrategy m b Source #
Action to perform when the buffer isn't large enough to contain the required data (extend the buffer, flush the data, etc.)
The returned buffer and offset replace the current ones.
Constructors
| OverflowStrategy (BufferOverflow b -> m (b, Word)) | 
data BufferOverflow b Source #
Buffer extension information
Constructors
| BufferOverflow | |
| Fields 
 | |
getPutOverflowStrategy :: Monad m => BufferPutT b m (OverflowStrategy m b) Source #
Get extend strategy
getGetOverflowStrategy :: Monad m => BufferGetT b m (OverflowStrategy m b) Source #
Get extend strategy
overflowBufferFail :: MonadFail m => OverflowStrategy m b Source #
Buffer overflow strategy: fails when there isn't enough space left
overflowBufferDouble :: MonadIO m => OverflowStrategy m BufferM Source #
Buffer extend strategy: double the buffer size each time and copy the original contents in it
overflowBufferDoublePinned :: MonadIO m => Maybe Word -> OverflowStrategy m BufferMP Source #
Buffer extend strategy: double the buffer size each time and copy the original contents in it
overflowBufferAdd :: MonadIO m => Word -> OverflowStrategy m BufferM Source #
Buffer extend strategy: add the given size each time and copy the original contents in it
overflowBufferAddPinned :: MonadIO m => Maybe Word -> Word -> OverflowStrategy m BufferMP Source #
Buffer extend strategy: add the given size each time and copy the original contents in it