Skip to content

Commit

Permalink
fixed bug: empty chunks were output (again)
Browse files Browse the repository at this point in the history
  • Loading branch information
meiersi committed Dec 6, 2010
1 parent a49d441 commit 4ca9406
Showing 1 changed file with 14 additions and 6 deletions.
20 changes: 14 additions & 6 deletions Blaze/ByteString/Builder/Internal.hs
Expand Up @@ -50,6 +50,8 @@ module Blaze.ByteString.Builder.Internal (

import Foreign

import Control.Monad (unless)

import qualified Data.ByteString as S
import qualified Data.ByteString.Internal as S
import qualified Data.ByteString.Lazy as L
Expand Down Expand Up @@ -99,6 +101,12 @@ defaultMaximalCopySize = 2 * defaultMinimalBufferSize
------------------------------------------------------------------------------
-- Flushing and running a Builder
------------------------------------------------------------------------------

-- | Prepend the chunk if it is non-empty.
{-# INLINE nonEmptyChunk #-}
nonEmptyChunk :: S.ByteString -> L.ByteString -> L.ByteString
nonEmptyChunk bs lbs | S.null bs = lbs
| otherwise = L.Chunk bs lbs


-- | Output all data written in the current buffer and start a new chunk.
Expand Down Expand Up @@ -189,10 +197,10 @@ toLazyByteStringWith bufSize minBufSize firstBufSize (Builder b) k =

InsertByteString pf' bs nextStep
| pf' == pf ->
return $ L.Chunk bs (S.inlinePerformIO $ fillNewBuffer bufSize nextStep)
return $ nonEmptyChunk bs (S.inlinePerformIO $ fillNewBuffer bufSize nextStep)
| otherwise ->
return $ L.Chunk (mkbs pf')
(L.Chunk bs (S.inlinePerformIO $ fillNewBuffer bufSize nextStep))
(nonEmptyChunk bs (S.inlinePerformIO $ fillNewBuffer bufSize nextStep))

-- allocate and fill a new buffer
fillNewBuffer !size !step0 = do
Expand Down Expand Up @@ -221,13 +229,13 @@ toLazyByteStringWith bufSize minBufSize firstBufSize (Builder b) k =

InsertByteString pf' bs nextStep
| pf' == pf ->
return $ L.Chunk bs (S.inlinePerformIO $ fill pf' nextStep)
return $ nonEmptyChunk bs (S.inlinePerformIO $ fill pf' nextStep)
| minBufSize < pe `minusPtr` pf' ->
return $ L.Chunk (mkbs pf')
(L.Chunk bs (S.inlinePerformIO $ fill pf' nextStep))
(nonEmptyChunk bs (S.inlinePerformIO $ fill pf' nextStep))
| otherwise ->
return $ L.Chunk (mkbs pf')
(L.Chunk bs (S.inlinePerformIO $ fillNewBuffer bufSize nextStep))
(nonEmptyChunk bs (S.inlinePerformIO $ fillNewBuffer bufSize nextStep))


-- | Extract the lazy 'L.ByteString' from the builder by running it with default
Expand Down Expand Up @@ -321,7 +329,7 @@ toByteStringIOWith bufSize io (Builder b) =

InsertByteString pf' bs nextStep -> do
io $ S.PS fpbuf 0 (pf' `minusPtr` pf)
io bs
unless (S.null bs) (io bs)
fillBuffer bufSize nextStep

-- | Run the builder with a 'defaultBufferSize'd buffer and execute the given
Expand Down

0 comments on commit 4ca9406

Please sign in to comment.