Safe Haskell | None |
---|---|
Language | Haskell2010 |
The functions in this module do not check to see if there is enough space in the buffer.
Synopsis
- newtype Builder :: Nat -> Type where
- construct :: (forall s. MutableByteArray s -> Int -> ST s Int) -> Builder n
- run :: forall n. KnownNat n => Builder n -> ByteArray
- pasteST :: Builder n -> MutableByteArray s -> Int -> ST s Int
- pasteIO :: Builder n -> MutableByteArray RealWorld -> Int -> IO Int
- append :: Builder n -> Builder m -> Builder (n + m)
- word64Dec :: Word64 -> Builder 19
- int64Dec :: Int64 -> Builder 20
- word64PaddedUpperHex :: Word64 -> Builder 16
- word32PaddedUpperHex :: Word32 -> Builder 8
- word16PaddedUpperHex :: Word16 -> Builder 4
- word8PaddedUpperHex :: Word8 -> Builder 2
- word64BE :: Word64 -> Builder 8
- word32BE :: Word32 -> Builder 4
- word16BE :: Word16 -> Builder 2
Builder
newtype Builder :: Nat -> Type where Source #
A builder parameterized by the maximum number of bytes it uses when executed.
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
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
Encode Integral Types
Human-Readable
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.
int64Dec :: Int64 -> Builder 20 Source #
Requires up to 20 bytes. 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 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.
word16PaddedUpperHex :: Word16 -> Builder 4 Source #
Requires exactly 4 bytes. Encodes a 16-bit unsigned integer as hexadecimal, zero-padding the encoding to 4 digits. This uses uppercase for the alphabetical digits.
word8PaddedUpperHex :: Word8 -> Builder 2 Source #
Requires exactly 2 bytes. Encodes a 8-bit unsigned integer as hexadecimal, zero-padding the encoding to 2 digits. This uses uppercase for the alphabetical digits.
Machine-Readable
word64BE :: Word64 -> Builder 8 Source #
Requires exactly 8 bytes. Dump the octets of a 64-bit word in a big-endian fashion.