proto3-wire-1.2.0: A low-level implementation of the Protocol Buffers (version 3) wire format

Safe HaskellNone
LanguageHaskell2010

Proto3.Wire.Reverse

Contents

Description

This module differs from the Data.ByteString.Builder module by writing the octets in reverse order, which lets us compute the length of a submessage by writing that submessage and measuring its length before we write a variadic integer prefix encoding that length.

Example use:

>>> Data.ByteString.Lazy.unpack (toLazyByteString (withLengthOf (word64Base128LEVar . fromIntegral) (word32BE 42 <> charUtf8 'λ')))
[6,0,0,0,42,206,187]
Synopsis

BuildR type

data BuildR Source #

Writes bytes in reverse order, updating the current state.

It is the responsibility of the execution context and buffer management primitives to ensure that the current buffer remains reachable during builder execution, though completed buffers may be copied to new storage at any time. Aside from those primitives, BuildR implementations may ignore that issue.

When combining BuildRs with <> we expect the best performance when associating to the left. For example foldl (<>) mempty, though unless your foldl iteration starts from the right there may still be issues. Consider using vectorBuildR instead of foldMap.

Instances
Show BuildR Source # 
Instance details

Defined in Proto3.Wire.Reverse.Internal

Semigroup BuildR Source # 
Instance details

Defined in Proto3.Wire.Reverse.Internal

Monoid BuildR Source # 
Instance details

Defined in Proto3.Wire.Reverse.Internal

Create BuildRs

etaBuildR :: (a -> BuildR) -> a -> BuildR Source #

Eta-expands a function that produces a BuildR, so that its input is not evaluated until the builder state is presented.

This odd combinator seems to help performance at times, though it may change behavior on nonterminating values of type a.

ensure :: Int -> BuildR -> BuildR Source #

Ensures that the current buffer has at least the given number of bytes before executing the given builder.

withLengthOf :: (Int -> BuildR) -> BuildR -> BuildR Source #

Executes the right builder, measuring how many bytes it writes, then provides that figure to the left builder.

byteString :: ByteString -> BuildR Source #

Convert a strict ByteString to a BuildR

byteString (x <> y) = byteString x <> byteString y

byteString mempty = mempty
>>> byteString "ABC"
Proto3.Wire.Reverse.lazyByteString "ABC"

lazyByteString :: ByteString -> BuildR Source #

Convert a lazy ByteString to a BuildR

Warning: evaluating the length will force the lazy ByteString's chunks, and they will remain allocated until you finish using the builder.

lazyByteString (x <> y) = lazyByteString x <> lazyByteString y

lazyByteString mempty = mempty
lazyByteString . toLazyByteString = id

toLazyByteString . lazyByteString = id
>>> lazyByteString "ABC"
Proto3.Wire.Reverse.lazyByteString "ABC"

shortByteString :: ShortByteString -> BuildR Source #

Convert a ShortByteString to a BuildR

shortByteString (x <> y) = shortByteString x <> shortByteString y

shortByteString mempty = mempty
>>> shortByteString "ABC"
Proto3.Wire.Reverse.lazyByteString "ABC"

word8 :: Word8 -> BuildR Source #

Convert a Word8 to a BuildR

>>> Data.ByteString.Lazy.unpack (toLazyByteString (word8 42))
[42]

int8 :: Int8 -> BuildR Source #

Convert a Int8 to a BuildR

>>> Data.ByteString.Lazy.unpack (toLazyByteString (int8 (-5)))
[251]

word16BE :: Word16 -> BuildR Source #

Convert a Word16 to a BuildR by storing the bytes in big-endian order

In other words, the most significant byte is stored first and the least significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (word16BE 42))
[0,42]

word16LE :: Word16 -> BuildR Source #

Convert a Word16 to a BuildR by storing the bytes in little-endian order

In other words, the least significant byte is stored first and the most significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (word16LE 42))
[42,0]

int16BE :: Int16 -> BuildR Source #

Convert an Int16 to a BuildR by storing the bytes in big-endian order

In other words, the most significant byte is stored first and the least significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (int16BE (-5)))
[255,251]

int16LE :: Int16 -> BuildR Source #

Convert an Int16 to a BuildR by storing the bytes in little-endian order

In other words, the least significant byte is stored first and the most significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (int16LE (-5)))
[251,255]

word32BE :: Word32 -> BuildR Source #

Convert a Word32 to a BuildR by storing the bytes in big-endian order

In other words, the most significant byte is stored first and the least significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32BE 42))
[0,0,0,42]

word32LE :: Word32 -> BuildR Source #

Convert a Word32 to a BuildR by storing the bytes in little-endian order

In other words, the least significant byte is stored first and the most significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32LE 42))
[42,0,0,0]

int32BE :: Int32 -> BuildR Source #

Convert an Int32 to a BuildR by storing the bytes in big-endian order

In other words, the most significant byte is stored first and the least significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (int32BE (-5)))
[255,255,255,251]

int32LE :: Int32 -> BuildR Source #

Convert an Int32 to a BuildR by storing the bytes in little-endian order

In other words, the least significant byte is stored first and the most significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (int32LE (-5)))
[251,255,255,255]

word64BE :: Word64 -> BuildR Source #

Convert a Word64 to a BuildR by storing the bytes in big-endian order

In other words, the most significant byte is stored first and the least significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64BE 42))
[0,0,0,0,0,0,0,42]

word64LE :: Word64 -> BuildR Source #

Convert a Word64 to a BuildR by storing the bytes in little-endian order

In other words, the least significant byte is stored first and the most significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64LE 42))
[42,0,0,0,0,0,0,0]

int64BE :: Int64 -> BuildR Source #

Convert an Int64 to a BuildR by storing the bytes in big-endian order

In other words, the most significant byte is stored first and the least significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (int64BE (-5)))
[255,255,255,255,255,255,255,251]

int64LE :: Int64 -> BuildR Source #

Convert an Int64 to a BuildR by storing the bytes in little-endian order

In other words, the least significant byte is stored first and the most significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (int64LE (-5)))
[251,255,255,255,255,255,255,255]

floatBE :: Float -> BuildR Source #

Convert a Float to a BuildR by storing the bytes in IEEE-754 format in big-endian order

In other words, the most significant byte is stored first and the least significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (floatBE 4.2))
[64,134,102,102]

floatLE :: Float -> BuildR Source #

Convert a Float to a BuildR by storing the bytes in IEEE-754 format in little-endian order

In other words, the least significant byte is stored first and the most significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (floatLE 4.2))
[102,102,134,64]

doubleBE :: Double -> BuildR Source #

Convert a Double to a BuildR by storing the bytes in IEEE-754 format in big-endian order

In other words, the most significant byte is stored first and the least significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (doubleBE 4.2))
[64,16,204,204,204,204,204,205]

doubleLE :: Double -> BuildR Source #

Convert a Double to a BuildR by storing the bytes in IEEE-754 format in little-endian order

In other words, the least significant byte is stored first and the most significant byte is stored last

>>> Data.ByteString.Lazy.unpack (toLazyByteString (doubleLE 4.2))
[205,204,204,204,204,204,16,64]

char7 :: Char -> BuildR Source #

Convert an ASCII Char to a BuildR

Careful: If you provide a Unicode character that is not part of the ASCII alphabet this will only encode the lowest 7 bits

>>> char7 ';'
Proto3.Wire.Reverse.lazyByteString ";"
>>> char7 'λ' -- Example of truncation
Proto3.Wire.Reverse.lazyByteString ";"

string7 :: String -> BuildR Source #

Convert an ASCII String to a BuildR

Careful: If you provide a Unicode String that has non-ASCII characters then this will only encode the lowest 7 bits of each character

string7 (x <> y) = string7 x <> string7 y

string7 mempty = mempty
>>> string7 "ABC"
Proto3.Wire.Reverse.lazyByteString "ABC"
>>> string7 "←↑→↓" -- Example of truncation
Proto3.Wire.Reverse.lazyByteString "\DLE\DC1\DC2\DC3"

char8 :: Char -> BuildR Source #

Convert an ISO/IEC 8859-1 Char to a BuildR

Careful: If you provide a Unicode character that is not part of the ISO/IEC 8859-1 alphabet then this will only encode the lowest 8 bits

>>> char8 ';'
Proto3.Wire.Reverse.lazyByteString ";"
>>> char8 'λ' -- Example of truncation
Proto3.Wire.Reverse.lazyByteString "\187"

string8 :: String -> BuildR Source #

Convert an ISO/IEC 8859-1 String to a BuildR

Careful: If you provide a Unicode String that has non-ISO/IEC 8859-1 characters then this will only encode the lowest 8 bits of each character

string8 (x <> y) = string8 x <> string8 y

string8 mempty = mempty
>>> string8 "ABC"
Proto3.Wire.Reverse.lazyByteString "ABC"
>>> string8 "←↑→↓" -- Example of truncation
Proto3.Wire.Reverse.lazyByteString "\144\145\146\147"

charUtf8 :: Char -> BuildR Source #

Convert a Unicode Char to a BuildR using a UTF-8 encoding

>>> charUtf8 'A'
Proto3.Wire.Reverse.lazyByteString "A"
>>> charUtf8 'λ'
Proto3.Wire.Reverse.lazyByteString "\206\187"
>>> charUtf8 (Data.Char.chr 0x7FF)
Proto3.Wire.Reverse.lazyByteString "\223\191"
>>> charUtf8 (Data.Char.chr 0x800)
Proto3.Wire.Reverse.lazyByteString "\224\160\128"
>>> charUtf8 (Data.Char.chr 0xFFFF)
Proto3.Wire.Reverse.lazyByteString "\239\191\191"
>>> charUtf8 (Data.Char.chr 0x10000)
Proto3.Wire.Reverse.lazyByteString "\240\144\128\128"
>>> charUtf8 (Data.Char.chr 0x10FFFF)
Proto3.Wire.Reverse.lazyByteString "\244\143\191\191"

stringUtf8 :: String -> BuildR Source #

Convert a Unicode String to a BuildR using a UTF-8 encoding

stringUtf8 (x <> y) = stringUtf8 x <> stringUtf8 y

stringUtf8 mempty = mempty
>>> stringUtf8 "ABC"
Proto3.Wire.Reverse.lazyByteString "ABC"
>>> stringUtf8 "←↑→↓"
Proto3.Wire.Reverse.lazyByteString "\226\134\144\226\134\145\226\134\146\226\134\147"
>>> Data.ByteString.Lazy.hPutStr System.IO.stdout (toLazyByteString (stringUtf8 "←↑→↓\n"))
←↑→↓

textUtf8 :: Text -> BuildR Source #

Convert a Unicode strict Text to a BuildR using a UTF-8 encoding

textUtf8 (x <> y) = textUtf8 x <> textUtf8 y

textUtf8 mempty = mempty
>>> textUtf8 "ABC"
Proto3.Wire.Reverse.lazyByteString "ABC"
>>> textUtf8 "←↑→↓"
Proto3.Wire.Reverse.lazyByteString "\226\134\144\226\134\145\226\134\146\226\134\147"

lazyTextUtf8 :: Text -> BuildR Source #

Convert a Unicode lazy Text to a BuildR using a UTF-8 encoding

lazyTextUtf8 (x <> y) = lazyTextUtf8 x <> lazyTextUtf8 y

lazyTextUtf8 mempty = mempty
>>> lazyTextUtf8 "ABC"
Proto3.Wire.Reverse.lazyByteString "ABC"
>>> lazyTextUtf8 "←↑→↓"
Proto3.Wire.Reverse.lazyByteString "\226\134\144\226\134\145\226\134\146\226\134\147"

wordBase128LEVar :: Word -> BuildR Source #

Convert a Word to a BuildR using this variable-length encoding:

  1. Convert the given value to a base 128 representation without unnecessary digits (that is, omit zero digits unless they are less significant than nonzero digits).
  2. Present those base-128 digits in order of increasing significance (that is, in little-endian order).
  3. Add 128 to every digit except the most significant digit, yielding a sequence of octets terminated by one that is <= 127.

This encoding is used in the wire format of Protocol Buffers version 3.

>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar 42))
[42]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar 5376))
[128,42]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar (Data.Bits.shiftL 1 7 - 1)))
[127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar (Data.Bits.shiftL 1 7)))
[128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar (Data.Bits.shiftL 1 14 - 1)))
[255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar (Data.Bits.shiftL 1 14)))
[128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar (Data.Bits.shiftL 1 21 - 1)))
[255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar (Data.Bits.shiftL 1 21)))
[128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar (Data.Bits.shiftL 1 28 - 1)))
[255,255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar (Data.Bits.shiftL 1 28)))
[128,128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar (Data.Bits.shiftL 1 32 - 1)))
[255,255,255,255,15]

wordBase128LEVar_inline :: Word -> BuildR Source #

Like wordBase128LEVar but inlined, which may bloat your code. On the other hand, inlining an application to a constant may shrink your code.

>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar_inline 42))
[42]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar_inline 5376))
[128,42]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar_inline (Data.Bits.shiftL 1 7 - 1)))
[127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar_inline (Data.Bits.shiftL 1 7)))
[128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar_inline (Data.Bits.shiftL 1 14 - 1)))
[255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar_inline (Data.Bits.shiftL 1 14)))
[128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar_inline (Data.Bits.shiftL 1 21 - 1)))
[255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar_inline (Data.Bits.shiftL 1 21)))
[128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar_inline (Data.Bits.shiftL 1 28 - 1)))
[255,255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar_inline (Data.Bits.shiftL 1 28)))
[128,128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (wordBase128LEVar_inline (Data.Bits.shiftL 1 32 - 1)))
[255,255,255,255,15]

word32Base128LEVar :: Word32 -> BuildR Source #

Convert a Word32 to a BuildR using this variable-length encoding:

  1. Convert the given value to a base 128 representation without unnecessary digits (that is, omit zero digits unless they are less significant than nonzero digits).
  2. Present those base-128 digits in order of increasing significance (that is, in little-endian order).
  3. Add 128 to every digit except the most significant digit, yielding a sequence of octets terminated by one that is <= 127.

This encoding is used in the wire format of Protocol Buffers version 3.

>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar 42))
[42]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar 5376))
[128,42]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar (Data.Bits.shiftL 1 7 - 1)))
[127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar (Data.Bits.shiftL 1 7)))
[128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar (Data.Bits.shiftL 1 14 - 1)))
[255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar (Data.Bits.shiftL 1 14)))
[128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar (Data.Bits.shiftL 1 21 - 1)))
[255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar (Data.Bits.shiftL 1 21)))
[128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar (Data.Bits.shiftL 1 28 - 1)))
[255,255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar (Data.Bits.shiftL 1 28)))
[128,128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar (Data.Bits.shiftL 1 32 - 1)))
[255,255,255,255,15]

word32Base128LEVar_inline :: Word32 -> BuildR Source #

Like word32Base128LEVar but inlined, which may bloat your code. On the other hand, inlining an application to a constant may shrink your code.

Currently word32Base128LEVar is fully inline, so this makes no difference, but in future we might make different default space/speed tradeoffs.

>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar_inline 42))
[42]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar_inline 5376))
[128,42]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar_inline (Data.Bits.shiftL 1 7 - 1)))
[127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar_inline (Data.Bits.shiftL 1 7)))
[128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar_inline (Data.Bits.shiftL 1 14 - 1)))
[255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar_inline (Data.Bits.shiftL 1 14)))
[128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar_inline (Data.Bits.shiftL 1 21 - 1)))
[255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar_inline (Data.Bits.shiftL 1 21)))
[128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar_inline (Data.Bits.shiftL 1 28 - 1)))
[255,255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar_inline (Data.Bits.shiftL 1 28)))
[128,128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word32Base128LEVar_inline (Data.Bits.shiftL 1 32 - 1)))
[255,255,255,255,15]

word64Base128LEVar :: Word64 -> BuildR Source #

Like word32Base128LEVar but for 64-bit inputs.

Inlines when the value fits within 32 bits, but see also word64Base128LEVar_inline, which always inlines.

>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar 42))
[42]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar 5376))
[128,42]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 7 - 1)))
[127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 7)))
[128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 14 - 1)))
[255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 14)))
[128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 21 - 1)))
[255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 21)))
[128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 28 - 1)))
[255,255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 28)))
[128,128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 32 - 1)))
[255,255,255,255,15]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 32)))
[128,128,128,128,16]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 56 - 1)))
[255,255,255,255,255,255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 56)))
[128,128,128,128,128,128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 60 - 1)))
[255,255,255,255,255,255,255,255,15]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 60)))
[128,128,128,128,128,128,128,128,16]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 63 - 1)))
[255,255,255,255,255,255,255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (Data.Bits.shiftL 1 63)))
[128,128,128,128,128,128,128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar (- (1 :: Data.Word.Word64))))
[255,255,255,255,255,255,255,255,255,1]

word64Base128LEVar_inline :: Word64 -> BuildR Source #

Like word64Base128LEVar but inlined, which may bloat your code. On the other hand, inlining an application to a constant may shrink your code.

>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline 42))
[42]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline 5376))
[128,42]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 7 - 1)))
[127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 7)))
[128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 14 - 1)))
[255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 14)))
[128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 21 - 1)))
[255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 21)))
[128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 28 - 1)))
[255,255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 28)))
[128,128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 32 - 1)))
[255,255,255,255,15]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 32)))
[128,128,128,128,16]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 56 - 1)))
[255,255,255,255,255,255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 56)))
[128,128,128,128,128,128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 60 - 1)))
[255,255,255,255,255,255,255,255,15]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 60)))
[128,128,128,128,128,128,128,128,16]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 63 - 1)))
[255,255,255,255,255,255,255,255,127]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (Data.Bits.shiftL 1 63)))
[128,128,128,128,128,128,128,128,128,1]
>>> Data.ByteString.Lazy.unpack (toLazyByteString (word64Base128LEVar_inline (- (1 :: Data.Word.Word64))))
[255,255,255,255,255,255,255,255,255,1]

vectorBuildR :: Vector v a => (a -> BuildR) -> v a -> BuildR Source #

Essentially foldMap, but iterates right to left for efficiency.

Consume BuildRs

runBuildR :: BuildR -> (Int, ByteString) Source #

Like toLazyByteString but also returns the total length of the lazy ByteString, which is computed as a side effect of encoding.

toLazyByteString :: BuildR -> ByteString Source #

Create a lazy ByteString from a BuildR

toLazyByteString (x <> y) = toLazyByteString x <> toLazyByteString y

toLazyByteString mempty = mempty
>>> toLazyByteString (stringUtf8 "ABC")
"ABC"

Helpful combinators

foldlRVector :: Vector v a => (b -> a -> b) -> b -> v a -> b Source #

Like foldl but iterates right-to-left, which is often useful when creating reverse builders.

Exported for testing purposes only.

testWithUnused :: (Int -> BuildR) -> BuildR Source #

Warning: Exported for testing purposes only.

Exported for testing purposes only.