| Portability | tested on GHC only | 
|---|---|
| Stability | experimental | 
| Maintainer | Simon Meier <iridcode@gmail.com> | 
Blaze.ByteString.Builder
Description
Blaze.ByteString.Builder is the main module, which you should import as a user
 of the blaze-builder library.
import Blaze.ByteString.Builder
It provides you with a type Builder that allows to efficiently construct
 lazy bytestrings with a large average chunk size.
Intuitively, a Builder denotes the construction of a part of a lazy
 bytestring. Builders can either be created using one of the primitive
 combinators in Blaze.ByteString.Builder.Write or by using one of the predefined
 combinators for standard Haskell values (see the exposed modules of this
 package).  Concatenation of builders is done using mappend from the
 Monoid typeclass.
Here is a small example that serializes a list of strings using the UTF-8 encoding.
import Blaze.ByteString.Builder.Char.Utf8
strings :: [String] strings = replicate 10000 "Hello there!"
The function fromStringBuilder denoting the UTF-8 encoded
 argument. Hence, UTF-8 encoding and concatenating all strings can be done
 follows.
concatenation :: Builder concatenation = mconcat $ map fromString strings
The function toLazyByteString  can be used to execute a Builder and
 obtain the resulting lazy bytestring.
result :: L.ByteString result = toLazyByteString concatenation
The result is a lazy bytestring containing 10000 repetitions of the string
 "Hello there!" encoded using UTF-8. The corresponding 120000 bytes are
 distributed among three chunks of 32kb and a last chunk of 6kb.
A note on history. This serialization library was inspired by the
 Data.Binary.Builder module provided by the binary package. It was
 originally developed with the specific needs of the blaze-html package in
 mind. Since then it has been restructured to serve as a drop-in replacement
 for Data.Binary.Builder, which it improves upon both in speed as well as
 expressivity.
- data Builder
- module Blaze.ByteString.Builder.Int
- module Blaze.ByteString.Builder.Word
- module Blaze.ByteString.Builder.ByteString
- flush :: Builder
- toLazyByteString :: Builder -> ByteString
- toLazyByteStringWith :: Int -> Int -> Int -> Builder -> ByteString -> ByteString
- toByteString :: Builder -> ByteString
- toByteStringIO :: (ByteString -> IO ()) -> Builder -> IO ()
- toByteStringIOWith :: Int -> (ByteString -> IO ()) -> Builder -> IO ()
- data Write
- fromWrite :: Write -> Builder
- fromWriteSingleton :: (a -> Write) -> a -> Builder
- fromWriteList :: (a -> Write) -> [a] -> Builder
- writeStorable :: Storable a => a -> Write
- fromStorable :: Storable a => a -> Builder
- fromStorables :: Storable a => [a] -> Builder
The Builder type
Creating builders
module Blaze.ByteString.Builder.Int
Output all data written in the current buffer and start a new chunk.
The use uf this function depends on how the resulting bytestrings are
 consumed. flush is possibly not very useful in non-interactive scenarios.
 However, it is kept for compatibility with the builder provided by
 Data.Binary.Builder.
When using toLazyByteString to extract a lazy ByteString from a
 Builder, this means that a new chunk will be started in the resulting lazy
 ByteString. The remaining part of the buffer is spilled, if the
 reamining free space is smaller than the minimal desired buffer size.
Executing builders
toLazyByteString :: Builder -> ByteStringSource
Extract the lazy ByteString from the builder by running it with default
 buffer sizes. Use this function, if you do not have any special
 considerations with respect to buffer sizes.
toLazyByteStringb =toLazyByteStringWithdefaultBufferSizedefaultMinimalBufferSizedefaultFirstBufferSizeb L.empty
Note that toLazyByteStringMonoid homomorphism.
toLazyByteString mempty == mempty toLazyByteString (x `mappend` y) == toLazyByteString x `mappend` toLazyByteString y
However, in the second equation, the left-hand-side is generally faster to execute.
Arguments
| :: Int | Buffer size (upper-bounds the resulting chunk size). | 
| -> Int | Minimal free buffer space for continuing filling
 the same buffer after a  | 
| -> Int | Size of the first buffer to be used and copied for larger resulting sequences | 
| -> Builder | Builder to run. | 
| -> ByteString | Lazy bytestring to output after the builder is finished. | 
| -> ByteString | Resulting lazy bytestring | 
Run a Builder with the given buffer sizes.
Use this function for integrating the Builder type with other libraries
 that generate lazy bytestrings.
Note that the builders should guarantee that on average the desired chunk size is attained. Builders may decide to start a new buffer and not completely fill the existing buffer, if this is faster. However, they should not spill too much of the buffer, if they cannot compensate for it.
A call toLazyByteStringWith bufSize minBufSize firstBufSize will generate
 a lazy bytestring according to the following strategy. First, we allocate
 a buffer of size firstBufSize and start filling it. If it overflows, we
 allocate a buffer of size minBufSize and copy the first buffer to it in
 order to avoid generating a too small chunk. Finally, every next buffer will
 be of size bufSize. This, slow startup strategy is required to achieve
 good speed for short (<200 bytes) resulting bytestrings, as for them the
 allocation cost is of a large buffer cannot be compensated. Moreover, this
 strategy also allows us to avoid spilling too much memory for short
 resulting bytestrings.
Note that setting firstBufSize >= minBufSize implies that the first buffer
 is no longer copied but allocated and filled directly. Hence, setting
 firstBufSize = bufSize means that all chunks will use an underlying buffer
 of size bufSize. This is recommended, if you know that you always output
 more than minBufSize bytes.
toByteString :: Builder -> ByteStringSource
Run the builder to construct a strict bytestring containing the sequence of bytes denoted by the builder. This is done by first serializing to a lazy bytestring and then packing its chunks to a appropriately sized strict bytestring.
toByteString = packChunks . toLazyByteString
Note that toByteStringMonoid homomorphism.
toByteString mempty == mempty toByteString (x `mappend` y) == toByteString x `mappend` toByteString y
However, in the second equation, the left-hand-side is generally faster to execute.
toByteStringIO :: (ByteString -> IO ()) -> Builder -> IO ()Source
Run the builder with a defaultBufferSized buffer and execute the given
 IO action whenever the buffer is full or gets flushed.
toByteStringIO=toByteStringIOWithdefaultBufferSize
This is a Monoid homomorphism in the following sense.
toByteStringIO io mempty == return () toByteStringIO io (x `mappend` y) == toByteStringIO io x >> toByteStringIO io y
Arguments
| :: Int | Buffer size (upper bounds
 the number of bytes forced
 per call to the  | 
| -> (ByteString -> IO ()) | 
 | 
| -> Builder | 
 | 
| -> IO () | Resulting  | 
toByteStringIOWith bufSize io b runs the builder b with a buffer of
 at least the size bufSize and executes the IO action io whenever the
 buffer is full.
Compared to toLazyByteStringWith this function requires less allocation,
 as the output buffer is only allocated once at the start of the
 serialization and whenever something bigger than the current buffer size has
 to be copied into the buffer, which should happen very seldomly for the
 default buffer size of 32kb. Hence, the pressure on the garbage collector is
 reduced, which can be an advantage when building long sequences of bytes.
Writes
A write of a bounded number of bytes.
When defining a function write :: a -> Write for some a, then it is
 important to ensure that the bound on the number of bytes written is
 data-independent. Formally, 
forall x y. getBound (write x) = getBound (write y)
The idea is that this data-independent bound is specified such that the compiler can optimize the check, if there are enough free bytes in the buffer, to a single subtraction between the pointer to the next free byte and the pointer to the end of the buffer with this constant bound of the maximal number of bytes to be written.
fromWriteSingleton :: (a -> Write) -> a -> BuilderSource
fromWriteList :: (a -> Write) -> [a] -> BuilderSource
Construct a Builder writing a list of data one element at a time.
Writing Storables
writeStorable :: Storable a => a -> WriteSource
Write a storable value.
fromStorable :: Storable a => a -> BuilderSource
A builder that serializes a storable value. No alignment is done.
fromStorables :: Storable a => [a] -> BuilderSource
A builder that serializes a list of storable values by writing them consecutively. No alignment is done. Parsing information needs to be provided externally.