{-# LANGUAGE CPP, BangPatterns #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Blaze.ByteString.Builder
(
B.Builder
, module Blaze.ByteString.Builder.Int
, module Blaze.ByteString.Builder.Word
, module Blaze.ByteString.Builder.ByteString
, B.flush
, B.toLazyByteString
, toLazyByteStringWith
, toByteString
, toByteStringIO
, toByteStringIOWith
, W.Write
, W.fromWrite
, W.fromWriteSingleton
, W.fromWriteList
, writeToByteString
, W.writeStorable
, W.fromStorable
, W.fromStorables
) where
import Control.Monad(unless)
#if __GLASGOW_HASKELL__ >= 702
import Foreign
import qualified Foreign.ForeignPtr.Unsafe as Unsafe
#else
import Foreign as Unsafe
#endif
import qualified Blaze.ByteString.Builder.Internal.Write as W
import Blaze.ByteString.Builder.ByteString
import Blaze.ByteString.Builder.Word
import Blaze.ByteString.Builder.Int
import Data.ByteString.Builder ( Builder )
import qualified Data.ByteString.Builder as B
import qualified Data.ByteString.Builder.Extra as B
import qualified Data.ByteString as S
import qualified Data.ByteString.Internal as S
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Lazy.Internal as L
#if __GLASGOW_HASKELL__ >= 702
import System.IO.Unsafe (unsafeDupablePerformIO)
#else
unsafeDupablePerformIO :: IO a -> a
unsafeDupablePerformIO = unsafePerformIO
#endif
withBS :: S.ByteString -> (ForeignPtr Word8 -> Int -> Int -> a) -> a
#if MIN_VERSION_bytestring(0,11,0)
withBS :: forall a. ByteString -> (ForeignPtr Word8 -> Int -> Int -> a) -> a
withBS (S.BS ForeignPtr Word8
fptr Int
len) ForeignPtr Word8 -> Int -> Int -> a
f = ForeignPtr Word8 -> Int -> Int -> a
f ForeignPtr Word8
fptr Int
0 Int
len
#else
withBS (S.PS fptr offset len) f = f fptr offset len
#endif
mkBS :: ForeignPtr Word8 -> Int -> S.ByteString
#if MIN_VERSION_bytestring(0,11,0)
mkBS :: ForeignPtr Word8 -> Int -> ByteString
mkBS ForeignPtr Word8
fptr Int
len = ForeignPtr Word8 -> Int -> ByteString
S.BS ForeignPtr Word8
fptr Int
len
#else
mkBS fptr len = S.PS fptr 0 len
#endif
packChunks :: L.ByteString -> S.ByteString
packChunks :: ByteString -> ByteString
packChunks ByteString
lbs = do
Int -> (Ptr Word8 -> IO ()) -> ByteString
S.unsafeCreate (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int64 -> Int) -> Int64 -> Int
forall a b. (a -> b) -> a -> b
$ ByteString -> Int64
L.length ByteString
lbs) (ByteString -> Ptr Word8 -> IO ()
forall {b}. ByteString -> Ptr b -> IO ()
copyChunks ByteString
lbs)
where
copyChunks :: ByteString -> Ptr b -> IO ()
copyChunks !ByteString
L.Empty !Ptr b
_pf = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
copyChunks !(L.Chunk ByteString
bs ByteString
lbs') !Ptr b
pf = ByteString -> (ForeignPtr Word8 -> Int -> Int -> IO ()) -> IO ()
forall a. ByteString -> (ForeignPtr Word8 -> Int -> Int -> a) -> a
withBS ByteString
bs ((ForeignPtr Word8 -> Int -> Int -> IO ()) -> IO ())
-> (ForeignPtr Word8 -> Int -> Int -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
fpbuf Int
o Int
l -> do
ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
fpbuf ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
pbuf ->
Ptr b -> Ptr b -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytes Ptr b
pf (Ptr Word8
pbuf Ptr Word8 -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
o) Int
l
ByteString -> Ptr b -> IO ()
copyChunks ByteString
lbs' (Ptr b
pf Ptr b -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
l)
toByteString :: Builder -> S.ByteString
toByteString :: Builder -> ByteString
toByteString = ByteString -> ByteString
packChunks (ByteString -> ByteString)
-> (Builder -> ByteString) -> Builder -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
B.toLazyByteString
defaultBufferSize :: Int
defaultBufferSize :: Int
defaultBufferSize = Int
32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
1024 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
overhead
where overhead :: Int
overhead = Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int -> Int
forall a. Storable a => a -> Int
sizeOf (Int
forall a. HasCallStack => a
undefined :: Int)
toByteStringIO :: (S.ByteString -> IO ()) -> Builder -> IO ()
toByteStringIO :: (ByteString -> IO ()) -> Builder -> IO ()
toByteStringIO = Int -> (ByteString -> IO ()) -> Builder -> IO ()
toByteStringIOWith Int
defaultBufferSize
toByteStringIOWith :: Int
-> (S.ByteString -> IO ())
-> Builder
-> IO ()
toByteStringIOWith :: Int -> (ByteString -> IO ()) -> Builder -> IO ()
toByteStringIOWith !Int
bufSize ByteString -> IO ()
io Builder
builder = do
Int -> IO (ForeignPtr Word8)
forall a. Int -> IO (ForeignPtr a)
S.mallocByteString Int
bufSize IO (ForeignPtr Word8) -> (ForeignPtr Word8 -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= BufferWriter -> Int -> ForeignPtr Word8 -> IO ()
getBuffer (Builder -> BufferWriter
B.runBuilder Builder
builder) Int
bufSize
where
getBuffer :: BufferWriter -> Int -> ForeignPtr Word8 -> IO ()
getBuffer BufferWriter
writer !Int
size ForeignPtr Word8
fp = do
let !ptr :: Ptr Word8
ptr = ForeignPtr Word8 -> Ptr Word8
forall a. ForeignPtr a -> Ptr a
Unsafe.unsafeForeignPtrToPtr ForeignPtr Word8
fp
(Int
bytes, Next
next) <- BufferWriter
writer Ptr Word8
ptr Int
size
case Next
next of
Next
B.Done -> ByteString -> IO ()
io (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$! ForeignPtr Word8 -> Int -> ByteString
mkBS ForeignPtr Word8
fp Int
bytes
B.More Int
req BufferWriter
writer' -> do
ByteString -> IO ()
io (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$! ForeignPtr Word8 -> Int -> ByteString
mkBS ForeignPtr Word8
fp Int
bytes
let !size' :: Int
size' = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
bufSize Int
req
Int -> IO (ForeignPtr Word8)
forall a. Int -> IO (ForeignPtr a)
S.mallocByteString Int
size' IO (ForeignPtr Word8) -> (ForeignPtr Word8 -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= BufferWriter -> Int -> ForeignPtr Word8 -> IO ()
getBuffer BufferWriter
writer' Int
size'
B.Chunk ByteString
bs' BufferWriter
writer' -> do
if Int
bytes Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then do
ByteString -> IO ()
io (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$! ForeignPtr Word8 -> Int -> ByteString
mkBS ForeignPtr Word8
fp Int
bytes
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ByteString -> Bool
S.null ByteString
bs') (ByteString -> IO ()
io ByteString
bs')
Int -> IO (ForeignPtr Word8)
forall a. Int -> IO (ForeignPtr a)
S.mallocByteString Int
bufSize IO (ForeignPtr Word8) -> (ForeignPtr Word8 -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= BufferWriter -> Int -> ForeignPtr Word8 -> IO ()
getBuffer BufferWriter
writer' Int
bufSize
else do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ByteString -> Bool
S.null ByteString
bs') (ByteString -> IO ()
io ByteString
bs')
BufferWriter -> Int -> ForeignPtr Word8 -> IO ()
getBuffer BufferWriter
writer' Int
size ForeignPtr Word8
fp
toLazyByteStringWith
:: Int
-> Int
-> Int
-> Builder
-> L.ByteString
-> L.ByteString
toLazyByteStringWith :: Int -> Int -> Int -> Builder -> ByteString -> ByteString
toLazyByteStringWith Int
bufSize Int
_minBufSize Int
firstBufSize Builder
builder ByteString
k =
AllocationStrategy -> ByteString -> Builder -> ByteString
B.toLazyByteStringWith (Int -> Int -> AllocationStrategy
B.safeStrategy Int
firstBufSize Int
bufSize) ByteString
k Builder
builder
writeToByteString :: W.Write -> S.ByteString
writeToByteString :: Write -> ByteString
writeToByteString !Write
w = IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ do
ForeignPtr Word8
fptr <- Int -> IO (ForeignPtr Word8)
forall a. Int -> IO (ForeignPtr a)
S.mallocByteString (Write -> Int
W.getBound Write
w)
Int
len <- ForeignPtr Word8 -> (Ptr Word8 -> IO Int) -> IO Int
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
fptr ((Ptr Word8 -> IO Int) -> IO Int)
-> (Ptr Word8 -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr -> do
Ptr Word8
end <- Write -> Ptr Word8 -> IO (Ptr Word8)
W.runWrite Write
w Ptr Word8
ptr
Int -> IO Int
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> IO Int) -> Int -> IO Int
forall a b. (a -> b) -> a -> b
$! Ptr Word8
end Ptr Word8 -> Ptr Word8 -> Int
forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word8
ptr
ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$! ForeignPtr Word8 -> Int -> Int -> ByteString
S.fromForeignPtr ForeignPtr Word8
fptr Int
0 Int
len
{-# INLINE writeToByteString #-}