small-bytearray-builder-0.1.0.0: Serialize to a small byte arrays

Safe HaskellNone
LanguageHaskell2010

Data.ByteArray.Builder.Small.Unsafe

Contents

Description

The functions in this module do not check to see if there is enough space in the buffer.

Synopsis

Builder

newtype Builder :: Nat -> Type where Source #

A builder parameterized by the maximum number of bytes it uses when executed.

Constructors

Builder :: (forall s. MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##)) -> Builder n 

construct :: (forall s. MutableByteArray s -> Int -> ST s Int) -> Builder n 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.

Execute

run Source #

Arguments

:: KnownNat n 
=> Builder n

Builder

-> ByteArray 

Execute the builder. This function is safe.

pasteST :: Builder n -> MutableByteArray s -> Int -> ST s Int Source #

This function does not enforce the known upper bound on the size. It is up to the user to do this.

pasteIO :: Builder n -> MutableByteArray RealWorld -> Int -> IO Int Source #

This function does not enforce the known upper bound on the size. It is up to the user to do this.

Combine

append :: Builder n -> Builder m -> Builder (n + m) Source #

Concatenate two builders.

Encode Integral Types

word64Dec :: Word64 -> Builder 19 Source #

Requires up to 19 bytes. Encodes an unsigned 64-bit integer as decimal. This encoding never starts with a zero unless the argument was zero.

word64PaddedUpperHex :: Word64 -> Builder 16 Source #

Requires exactly 16 bytes. Encodes 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 8 Source #

Requires exactly 8 bytes. Encodes a 32-bit unsigned integer as hexadecimal, zero-padding the encoding to 8 digits. This uses uppercase for the alphabetical digits.