Safe Haskell | None |
---|---|
Language | Haskell2010 |
An efficient implementation of ByteString builder.
In many cases, this module works as a drop-in replacement for
Data.ByteString.Builder, and should improve speed. However, one caveat
applies: when using toLazyByteString
, if you consume the result
in a bound thread, performance degrades significantly. See the
documentation for toLazyByteString
for details.
Sometimes performance can be greatly improved by inserting calls to
rebuild
to your program. See the documentation for rebuild
for
details.
- data Builder
- toLazyByteString :: Builder -> ByteString
- toLazyByteStringWith :: Int -> Int -> Builder -> ByteString
- toStrictByteString :: Builder -> ByteString
- hPutBuilder :: Handle -> Builder -> IO ()
- rebuild :: Builder -> Builder
- primBounded :: BoundedPrim a -> a -> Builder
- primFixed :: FixedPrim a -> a -> Builder
- byteString :: ByteString -> Builder
- byteStringInsert :: ByteString -> Builder
- byteStringCopy :: ByteString -> Builder
- byteStringThreshold :: Int -> ByteString -> Builder
- int8 :: Int8 -> Builder
- word8 :: Word8 -> Builder
- int16LE :: Int16 -> Builder
- int32LE :: Int32 -> Builder
- int64LE :: Int64 -> Builder
- word16LE :: Word16 -> Builder
- word32LE :: Word32 -> Builder
- word64LE :: Word64 -> Builder
- floatLE :: Float -> Builder
- doubleLE :: Double -> Builder
- int16BE :: Int16 -> Builder
- int32BE :: Int32 -> Builder
- int64BE :: Int64 -> Builder
- word16BE :: Word16 -> Builder
- word32BE :: Word32 -> Builder
- word64BE :: Word64 -> Builder
- floatBE :: Float -> Builder
- doubleBE :: Double -> Builder
- intHost :: Int -> Builder
- int16Host :: Int16 -> Builder
- int32Host :: Int32 -> Builder
- int64Host :: Int64 -> Builder
- wordHost :: Word -> Builder
- word16Host :: Word16 -> Builder
- word32Host :: Word32 -> Builder
- word64Host :: Word64 -> Builder
- floatHost :: Float -> Builder
- doubleHost :: Double -> Builder
- intDec :: Int -> Builder
- int8Dec :: Int8 -> Builder
- int16Dec :: Int16 -> Builder
- int32Dec :: Int32 -> Builder
- int64Dec :: Int64 -> Builder
- wordDec :: Word -> Builder
- word8Dec :: Word8 -> Builder
- word16Dec :: Word16 -> Builder
- word32Dec :: Word32 -> Builder
- word64Dec :: Word64 -> Builder
- integerDec :: Integer -> Builder
- floatDec :: Double -> Builder
- doubleDec :: Double -> Builder
- wordHex :: Word -> Builder
- word8Hex :: Word8 -> Builder
- word16Hex :: Word16 -> Builder
- word32Hex :: Word32 -> Builder
- word64Hex :: Word64 -> Builder
- int8HexFixed :: Int8 -> Builder
- int16HexFixed :: Int16 -> Builder
- int32HexFixed :: Int32 -> Builder
- int64HexFixed :: Int64 -> Builder
- word8HexFixed :: Word8 -> Builder
- word16HexFixed :: Word16 -> Builder
- word32HexFixed :: Word32 -> Builder
- word64HexFixed :: Word64 -> Builder
- floatHexFixed :: Float -> Builder
- doubleHexFixed :: Double -> Builder
- charUtf8 :: Char -> Builder
- stringUtf8 :: String -> Builder
- char7 :: Char -> Builder
- string7 :: String -> Builder
- char8 :: Char -> Builder
- string8 :: String -> Builder
The type
Builder
is an auxiliary type for efficiently generating a long
ByteString
. It is isomorphic to lazy ByteString
, but offers
constant-time concatanation via <>
.
Use toLazyByteString
to turn a Builder
into a ByteString
Running a builder
toLazyByteString :: Builder -> ByteString Source
Turn a Builder
into a lazy ByteString
.
Performance hint: when the resulting ByteString
does not fit
in one chunk, this function forks a thread. Due to this, the performance
degrades sharply if you use this function from a bound thread. Note in
particular that the main thread is a bound thread when you use ghc
-threaded
.
To avoid this problem, do one of these:
- Make sure the resulting
ByteString
is consumed in an unbound thread. Consider usingrunInUnboundThread
for this. - Use other function to run the
Builder
instead. Functions that don't return a lazyByteString
do not have this issue. - Link your program without
-threaded
.
toLazyByteStringWith :: Int -> Int -> Builder -> ByteString Source
Like toLazyByteString
, but allows the user to specify the initial
and the subsequent desired buffer sizes.
toStrictByteString :: Builder -> ByteString Source
Turn a Builder
into a strict ByteString
.
Performance tuning
rebuild :: Builder -> Builder Source
is equivalent to rebuild
bb
, but it allows GHC to assume
that b
will be run at most once. This can enable various
optimizations that greately improve performance.
There are two types of typical situations where a use of rebuild
is often a win:
- When constructing a builder using a recursive function. e.g.
rebuild $ foldr ...
. - When constructing a builder using a conditional expression. e.g.
rebuild $ case x of ...
Basic builders
primBounded :: BoundedPrim a -> a -> Builder Source
Turn a value of type a
into a Builder
, using the given BoundedPrim
.
byteString :: ByteString -> Builder Source
Turn a ByteString
to a Builder
.
byteStringInsert :: ByteString -> Builder Source
Turn a ByteString
to a Builder
. When possible, the given
ByteString
will not be copied, and inserted directly into the output
instead.
byteStringCopy :: ByteString -> Builder Source
Turn a ByteString
to a Builder
. The ByteString
will be copied
to the buffer, regardless of the size.
byteStringThreshold :: Int -> ByteString -> Builder Source
Turn a ByteString
to a Builder
. If the size of the ByteString
is larger than the given threshold, avoid copying it as much
as possible.
Single byte
Little endian
Big endian
Host-dependent size and byte order, non-portable
word16Host :: Word16 -> Builder Source
word32Host :: Word32 -> Builder Source
word64Host :: Word64 -> Builder Source
doubleHost :: Double -> Builder Source
Decimal
integerDec :: Integer -> Builder Source
Hexadecimal
Fixed-width hexadecimal
int8HexFixed :: Int8 -> Builder Source
int16HexFixed :: Int16 -> Builder Source
int32HexFixed :: Int32 -> Builder Source
int64HexFixed :: Int64 -> Builder Source
word8HexFixed :: Word8 -> Builder Source
word16HexFixed :: Word16 -> Builder Source
word32HexFixed :: Word32 -> Builder Source
word64HexFixed :: Word64 -> Builder Source
floatHexFixed :: Float -> Builder Source
doubleHexFixed :: Double -> Builder Source
UTF-8
stringUtf8 :: String -> Builder Source