| Portability | tested on GHC only | 
|---|---|
| Stability | experimental | 
| Maintainer | Simon Meier <iridcode@gmail.com> | 
Blaze.ByteString.Builder.Internal
Description
Implementation of the Builder monoid.
A standard library user must never import this module directly. Instead, he
 should import Blaze.ByteString.Builder, which re-exports the Builder type and
 its associated public functions defined in this module.
Developers of other libraries may import this module to gain access to the
 internal representation of builders. For example, in some cases, creating a
 Builder with a custom low-level BuildStep may improve performance
 considerably compared to the creating it using the public Builder
 combinators (e.g.,  in Blaze.ByteString.Builder.Write).
 Another example, is the use of fromWrite1ListModifyChunks to efficiently wire the
 Builder type with another library that generates lazy bytestrings.
In any case, whenever you import this module you must reference the full version of the 'blaze-builder' package in your cabal file, as the implementation and the guarantees given in this file may change in any version! The release notes will tell, if this was the case.
- newtype Builder = Builder (BuildStep -> BuildStep)
 - type BuildStep = Ptr Word8 -> Ptr Word8 -> IO BuildSignal
 - data  BuildSignal 
- = Done !(Ptr Word8)
 - | BufferFull !Int !(Ptr Word8) !BuildStep
 - | ModifyChunks !(Ptr Word8) !(ByteString -> ByteString) !BuildStep
 
 - flush :: Builder
 - toLazyByteStringWith :: Int -> Int -> Int -> Builder -> ByteString -> ByteString
 - toLazyByteString :: Builder -> ByteString
 - toByteString :: Builder -> ByteString
 - toByteStringIOWith :: Int -> (ByteString -> IO ()) -> Builder -> IO ()
 - toByteStringIO :: (ByteString -> IO ()) -> Builder -> IO ()
 - defaultBufferSize :: Int
 - defaultMinimalBufferSize :: Int
 - defaultMaximalCopySize :: Int
 
The Builder type
Intuitively, a builder denotes the construction of a lazy bytestring.
Builders can be created from primitive buffer manipulations using the
  abstraction provided by in Blaze.ByteString.Builder.Write. However for
 many Haskell values, there exist predefined functions doing that already. 
 For example, UTF-8 encoding WriteChar and String values is provided by the
 functions in Blaze.ByteString.Builder.Char.Utf8. Concatenating builders is done
 using their Monoid instance.
Semantically, builders are nothing special. They just denote a sequence of bytes. However, their representation is chosen such that this sequence of bytes can be efficiently (in terms of CPU cycles) computed in an incremental, chunk-wise fashion such that the average chunk-size is large. Note that the large average chunk size allows to make good use of cache prefetching in later processing steps (e.g. compression) or to reduce the sytem call overhead when writing the resulting lazy bytestring to a file or sending it over the network.
For precisely understanding the performance of a specific Builder,
 benchmarking is unavoidable. Moreover, it also helps to understand the
 implementation of builders and the predefined combinators. This should be
 amenable to the average Haskell programmer by reading the source code of
 Blaze.ByteString.Builder.Internal and the other modules of this library. 
The guiding implementation principle was to reduce the abstraction cost per
 output byte. We use continuation passing to achieve a constant time append.
 The output buffer is filled by the individual builders as long as possible.
 They call each other directly when they are done and control is returned to
 the driver (e.g., toLazyByteString) only when the buffer is full, a
 bytestring needs to be inserted directly, or no more bytes can be written.
 We also try to take the pressure off the cache by moving variables as far
 out of loops as possible. This leads to some duplication of code, but
 results in sometimes dramatic increases in performance. For example, see the
  function in Blaze.ByteString.Builder.Word.
fromWord8s
Arguments
| = Ptr Word8 | Pointer to the next free byte in the
 buffer. A   | 
| -> Ptr Word8 | Pointer to the first byte after the
 buffer.  A   | 
| -> IO BuildSignal | Signal to the driver about the next step to be taken.  | 
A BuildStep fills a buffer from the given start pointer as long as
 possible and returns control to the caller using a BuildSignal, once it is
 required.
data BuildSignal Source
A BuildSignal signals to the driver of the Builder execution the next
 step to be taken.
Constructors
| Done !(Ptr Word8) | 
  | 
| BufferFull !Int !(Ptr Word8) !BuildStep | 
 A driver must guarantee that the buffer used to call   | 
| ModifyChunks !(Ptr Word8) !(ByteString -> ByteString) !BuildStep | 
 This signal is used to insert bytestrings directly into the output stream. It can also be used to efficiently hand over control to another library for generating streams of strict bytestrings.  | 
Flushing the buffer
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
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.
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  is a 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.
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  is a 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.
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.
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
Default sizes
defaultBufferSize :: IntSource
Default size (~32kb) for the buffer that becomes a chunk of the output stream once it is filled.
defaultMinimalBufferSize :: IntSource
The minimal length (~4kb) a buffer must have before filling it and outputting it as a chunk of the output stream.
This size determines when a buffer is spilled after a flush or a direct
 bytestring insertion. It is also the size of the first chunk generated by
 toLazyByteString.
defaultMaximalCopySize :: IntSource
The maximal number of bytes for that copying is cheaper than direct
 insertion into the output stream. This takes into account the fragmentation
 that may occur in the output buffer due to the early flush implied by the
 direct bytestring insertion.
defaultMaximalCopySize= 2 *defaultMinimalBufferSize