| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.ByteArray.Builder.Small
Contents
Synopsis
- newtype Builder = Builder (forall s. MutableByteArray# s -> Int# -> Int# -> State# s -> (#State# s, Int##))
 - construct :: (forall s. MutableBytes s -> ST s (Maybe Int)) -> Builder
 - fromUnsafe :: forall n. KnownNat n => Builder n -> Builder
 - run :: Int -> Builder -> ByteArray
 - pasteST :: Builder -> MutableBytes s -> ST s (Maybe Int)
 - pasteIO :: Builder -> MutableBytes RealWorld -> IO (Maybe Int)
 - pasteGrowST :: Int -> Builder -> MutableByteArray s -> ST s (MutableByteArrayOffset s)
 - pasteGrowIO :: Int -> Builder -> MutableByteArray RealWorld -> IO (MutableByteArrayOffset RealWorld)
 - pasteArrayST :: MutableBytes s -> (a -> Builder) -> Vector a -> ST s (Vector a, MutableBytes s)
 - pasteArrayIO :: MutableBytes RealWorld -> (a -> Builder) -> Vector a -> IO (Vector a, MutableBytes RealWorld)
 - bytes :: Bytes -> Builder
 - bytearray :: ByteArray -> Builder
 - word64Dec :: Word64 -> Builder
 - int64Dec :: Int64 -> Builder
 - word64PaddedUpperHex :: Word64 -> Builder
 - word32PaddedUpperHex :: Word32 -> Builder
 - word16PaddedUpperHex :: Word16 -> Builder
 - word8PaddedUpperHex :: Word8 -> Builder
 - word64BE :: Word64 -> Builder
 - word32BE :: Word32 -> Builder
 - word16BE :: Word16 -> Builder
 
Unsafe Primitives
An unmaterialized sequence of bytes that may be pasted into a mutable byte array.
Constructors
| Builder (forall s. MutableByteArray# s -> Int# -> Int# -> State# s -> (#State# s, Int##)) | 
construct :: (forall s. MutableBytes s -> ST s (Maybe Int)) -> Builder Source #
Constructor for Builder that works on a function with lifted
 arguments instead of unlifted ones. This is just as unsafe as the
 actual constructor.
Evaluation
Run a builder. An accurate size hint is important for good performance. The size hint should be slightly larger than the actual size.
pasteST :: Builder -> MutableBytes s -> ST s (Maybe Int) Source #
Execute the builder, pasting its contents into a buffer.
 If the buffer is not large enough, this returns Nothing.
 Otherwise, it returns the index in the buffer that follows
 the payload just written.
Arguments
| :: Int | How many bytes to grow by at a time  | 
| -> Builder | |
| -> MutableByteArray s | Initial buffer, used linearly. Do not reuse this argument.  | 
| -> ST s (MutableByteArrayOffset s) | Final buffer that accomodated the builder.  | 
Paste the builder into the byte array starting at offset zero. This repeatedly reallocates the byte array if it cannot accomodate the builder, replaying the builder each time.
Arguments
| :: Int | How many bytes to grow by at a time  | 
| -> Builder | |
| -> MutableByteArray RealWorld | Initial buffer, used linearly. Do not reuse this argument.  | 
| -> IO (MutableByteArrayOffset RealWorld) | Final buffer that accomodated the builder.  | 
Variant of pasteGrowST that runs in IO.
Arguments
| :: MutableBytes s | Buffer  | 
| -> (a -> Builder) | Builder  | 
| -> Vector a | Elements to serialize  | 
| -> ST s (Vector a, MutableBytes s) | Shifted vector, shifted buffer  | 
Fold over a vector, applying the builder to each element until the buffer cannot accomodate any more.
Arguments
| :: MutableBytes RealWorld | Buffer  | 
| -> (a -> Builder) | Builder  | 
| -> Vector a | Elements to serialize  | 
| -> IO (Vector a, MutableBytes RealWorld) | Shifted vector, shifted buffer  | 
Variant of pasteArrayST that runs in IO.
Materialized Byte Sequences
Encode Integral Types
Human-Readable
word64Dec :: Word64 -> Builder Source #
Encodes an unsigned 64-bit integer as decimal. This encoding never starts with a zero unless the argument was zero.
int64Dec :: Int64 -> Builder Source #
Encodes a signed 64-bit integer as decimal. This encoding never starts with a zero unless the argument was zero. Negative numbers are preceded by a minus sign. Positive numbers are not preceded by anything.
word64PaddedUpperHex :: Word64 -> Builder Source #
Encode a 64-bit unsigned integer as hexadecimal, zero-padding
 the encoding to 16 digits. This uses uppercase for the alphabetical
 digits. For example, this encodes the number 1022 as 00000000000003FE.
word32PaddedUpperHex :: Word32 -> Builder Source #
Encode a 32-bit unsigned integer as hexadecimal, zero-padding
 the encoding to 8 digits. This uses uppercase for the alphabetical
 digits. For example, this encodes the number 1022 as 000003FE.
word16PaddedUpperHex :: Word16 -> Builder Source #
Encode a 16-bit unsigned integer as hexadecimal, zero-padding
 the encoding to 4 digits. This uses uppercase for the alphabetical
 digits. For example, this encodes the number 1022 as 03FE.
word8PaddedUpperHex :: Word8 -> Builder Source #
Encode a 8-bit unsigned integer as hexadecimal, zero-padding
 the encoding to 2 digits. This uses uppercase for the alphabetical
 digits. For example, this encodes the number 11 as 0B.
Machine-Readable
word64BE :: Word64 -> Builder Source #
Requires exactly 8 bytes. Dump the octets of a 64-bit word in a big-endian fashion.