| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.ByteArray.Builder
Contents
Synopsis
- data Builder
- fromBounded :: Nat n -> Builder n -> Builder
- run :: Int -> Builder -> Chunks
- bytes :: Bytes -> Builder
- copy :: Bytes -> Builder
- insert :: Bytes -> Builder
- byteArray :: ByteArray -> Builder
- shortByteString :: ShortByteString -> Builder
- shortTextUtf8 :: ShortText -> Builder
- shortTextJsonString :: ShortText -> Builder
- cstring :: CString -> Builder
- stringUtf8 :: String -> Builder
- word64Dec :: Word64 -> Builder
- word32Dec :: Word32 -> Builder
- word16Dec :: Word16 -> Builder
- word8Dec :: Word8 -> Builder
- wordDec :: Word -> Builder
- int64Dec :: Int64 -> Builder
- int32Dec :: Int32 -> Builder
- int16Dec :: Int16 -> Builder
- int8Dec :: Int8 -> Builder
- intDec :: Int -> Builder
- word64PaddedUpperHex :: Word64 -> Builder
- word32PaddedUpperHex :: Word32 -> Builder
- word16PaddedUpperHex :: Word16 -> Builder
- word16PaddedLowerHex :: Word16 -> Builder
- word16LowerHex :: Word16 -> Builder
- word16UpperHex :: Word16 -> Builder
- word8PaddedUpperHex :: Word8 -> Builder
- word8LowerHex :: Word8 -> Builder
- ascii :: Char -> Builder
- char :: Char -> Builder
- word8 :: Word8 -> Builder
- word64BE :: Word64 -> Builder
- word32BE :: Word32 -> Builder
- word16BE :: Word16 -> Builder
- int64BE :: Int64 -> Builder
- int32BE :: Int32 -> Builder
- int16BE :: Int16 -> Builder
- word64LE :: Word64 -> Builder
- word32LE :: Word32 -> Builder
- word16LE :: Word16 -> Builder
- int64LE :: Int64 -> Builder
- int32LE :: Int32 -> Builder
- int16LE :: Int16 -> Builder
- word8Array :: PrimArray Word8 -> Int -> Int -> Builder
- word16ArrayBE :: PrimArray Word16 -> Int -> Int -> Builder
- word32ArrayBE :: PrimArray Word32 -> Int -> Int -> Builder
- word64ArrayBE :: PrimArray Word64 -> Int -> Int -> Builder
- int64ArrayBE :: PrimArray Int64 -> Int -> Int -> Builder
- int32ArrayBE :: PrimArray Int32 -> Int -> Int -> Builder
- int16ArrayBE :: PrimArray Int16 -> Int -> Int -> Builder
- word16ArrayLE :: PrimArray Word16 -> Int -> Int -> Builder
- word32ArrayLE :: PrimArray Word32 -> Int -> Int -> Builder
- word64ArrayLE :: PrimArray Word64 -> Int -> Int -> Builder
- int64ArrayLE :: PrimArray Int64 -> Int -> Int -> Builder
- int32ArrayLE :: PrimArray Int32 -> Int -> Int -> Builder
- int16ArrayLE :: PrimArray Int16 -> Int -> Int -> Builder
- consLength32BE :: Builder -> Builder
- consLength64BE :: Builder -> Builder
- doubleDec :: Double -> Builder
- flush :: Int -> Builder
Bounded Primitives
An unmaterialized sequence of bytes that may be pasted into a mutable byte array.
fromBounded :: Nat n -> Builder n -> Builder Source #
Convert a bounded builder to an unbounded one. If the size
 is a constant, use Arithmetic.Nat.constant as the first argument
 to let GHC conjure up this value for you.
Evaluation
Run a builder.
Materialized Byte Sequences
copy :: Bytes -> Builder Source #
Create a builder from a byte sequence. This always results in a
 call to memcpy. This is beneficial when the byte sequence is
 known to be small (less than 256 bytes).
insert :: Bytes -> Builder Source #
Create a builder from a byte sequence. This never calls memcpy.
 Instead, it pushes a chunk that references the argument byte sequence.
 This wastes the remaining space in the active chunk, so it may adversely
 affect performance if used carelessly. See flush for a way to mitigate
 this problem. This functions is most beneficial when the byte sequence
 is known to be large (more than 8192 bytes).
shortByteString :: ShortByteString -> Builder Source #
Create a builder from a short bytestring.
shortTextUtf8 :: ShortText -> Builder Source #
Create a builder from text. The text will be UTF-8 encoded.
cstring :: CString -> Builder Source #
Create a builder from a NUL-terminated CString. This ignores any
 textual encoding, copying bytes until NUL is reached.
stringUtf8 :: String -> Builder Source #
Create a builder from a cons-list of Char. These
 are be UTF-8 encoded.
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.
word32Dec :: Word32 -> Builder Source #
Encodes an unsigned 16-bit integer as decimal. This encoding never starts with a zero unless the argument was zero.
word16Dec :: Word16 -> Builder Source #
Encodes an unsigned 16-bit integer as decimal. This encoding never starts with a zero unless the argument was zero.
word8Dec :: Word8 -> Builder Source #
Encodes an unsigned 8-bit integer as decimal. This encoding never starts with a zero unless the argument was zero.
wordDec :: Word -> Builder Source #
Encodes an unsigned machine-sized 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.
int32Dec :: Int32 -> Builder Source #
Encodes a signed 32-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.
int16Dec :: Int16 -> Builder Source #
Encodes a signed 16-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.
int8Dec :: Int8 -> Builder Source #
Encodes a signed 8-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.
intDec :: Int -> Builder Source #
Encodes a signed machine-sized 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.
Unsigned Words
64-bit
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.
32-bit
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.
16-bit
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.
word16PaddedLowerHex :: Word16 -> Builder Source #
Encode a 16-bit unsigned integer as hexadecimal, zero-padding
 the encoding to 4 digits. This uses lowercase for the alphabetical
 digits. For example, this encodes the number 1022 as 03fe.
word16LowerHex :: Word16 -> Builder Source #
Encode a 16-bit unsigned integer as hexadecimal without leading
 zeroes. This uses lowercase for the alphabetical digits. For
 example, this encodes the number 1022 as 3fe.
word16UpperHex :: Word16 -> Builder Source #
Encode a 16-bit unsigned integer as hexadecimal without leading
 zeroes. This uses uppercase for the alphabetical digits. For
 example, this encodes the number 1022 as 3FE.
8-bit
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.
word8LowerHex :: Word8 -> Builder Source #
Encode a 16-bit unsigned integer as hexadecimal without leading
 zeroes. This uses lowercase for the alphabetical digits. For
 example, this encodes the number 1022 as 3FE.
ascii :: Char -> Builder Source #
Encode an ASCII char. Precondition: Input must be an ASCII character. This is not checked.
Machine-Readable
One
Big Endian
word64BE :: Word64 -> Builder Source #
Requires exactly 8 bytes. Dump the octets of a 64-bit word in a big-endian fashion.
word32BE :: Word32 -> Builder Source #
Requires exactly 4 bytes. Dump the octets of a 32-bit word in a big-endian fashion.
word16BE :: Word16 -> Builder Source #
Requires exactly 2 bytes. Dump the octets of a 16-bit word in a big-endian fashion.
int64BE :: Int64 -> Builder Source #
Requires exactly 8 bytes. Dump the octets of a 64-bit signed integer in a big-endian fashion.
int32BE :: Int32 -> Builder Source #
Requires exactly 4 bytes. Dump the octets of a 32-bit signed integer in a big-endian fashion.
int16BE :: Int16 -> Builder Source #
Requires exactly 2 bytes. Dump the octets of a 16-bit signed integer in a big-endian fashion.
Little Endian
word64LE :: Word64 -> Builder Source #
Requires exactly 8 bytes. Dump the octets of a 64-bit word in a little-endian fashion.
word32LE :: Word32 -> Builder Source #
Requires exactly 4 bytes. Dump the octets of a 32-bit word in a little-endian fashion.
word16LE :: Word16 -> Builder Source #
Requires exactly 2 bytes. Dump the octets of a 16-bit word in a little-endian fashion.
int64LE :: Int64 -> Builder Source #
Requires exactly 8 bytes. Dump the octets of a 64-bit signed integer in a little-endian fashion.
int32LE :: Int32 -> Builder Source #
Requires exactly 4 bytes. Dump the octets of a 32-bit signed integer in a little-endian fashion.
int16LE :: Int16 -> Builder Source #
Requires exactly 2 bytes. Dump the octets of a 16-bit signed integer in a little-endian fashion.
Many
Big Endian
Little Endian
Prefixing with Length
consLength32BE :: Builder -> Builder Source #
Prefix a builder with its size in bytes. This size is presented as a big-endian 32-bit word. The need to prefix a builder with its length shows up a numbers of wire protocols including those of PostgreSQL and Apache Kafka. Note the equivalence:
forall (n :: Int) (x :: Builder). let sz = sizeofByteArray (run n (consLength32BE x)) consLength32BE x === word32BE (fromIntegral sz) <> x
However, using consLength32BE is much more efficient here
 since it only materializes the ByteArray once.
consLength64BE :: Builder -> Builder Source #
Prefix a builder with its size in bytes. This size is
 presented as a big-endian 64-bit word. See consLength32BE.
Encode Floating-Point Types
Human-Readable
doubleDec :: Double -> Builder Source #
Encode a double-floating-point number, using decimal notation or
 scientific notation depending on the magnitude. This has undefined
 behavior when representing +inf, -inf, and NaN. It will not
 crash, but the generated numbers will be nonsense.
Control
flush :: Int -> Builder Source #
Push the buffer currently being filled onto the chunk list, allocating a new active buffer of the requested size. This is helpful when a small builder is sandwhiched between two large zero-copy builders:
insert bigA <> flush 1 <> word8 0x42 <> insert bigB
Without flush 1, word8 0x42 would see the zero-byte active
 buffer that insert returned, decide that it needed more space,
 and allocate a 4080-byte buffer to which only a single byte
 would be written.