{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE Trustworthy #-}
module Data.ByteString.Builder.Extra
(
toLazyByteStringWith
, AllocationStrategy
, safeStrategy
, untrimmedStrategy
, smallChunkSize
, defaultChunkSize
, byteStringCopy
, byteStringInsert
, byteStringThreshold
, lazyByteStringCopy
, lazyByteStringInsert
, lazyByteStringThreshold
, flush
, BufferWriter
, Next(..)
, runBuilder
, intHost
, int16Host
, int32Host
, int64Host
, wordHost
, word16Host
, word32Host
, word64Host
, floatHost
, doubleHost
) where
import Data.ByteString.Builder.Internal
( Builder, toLazyByteStringWith
, AllocationStrategy, safeStrategy, untrimmedStrategy
, smallChunkSize, defaultChunkSize, flush
, byteStringCopy, byteStringInsert, byteStringThreshold
, lazyByteStringCopy, lazyByteStringInsert, lazyByteStringThreshold )
import qualified Data.ByteString.Builder.Internal as I
import qualified Data.ByteString.Builder.Prim as P
import qualified Data.ByteString.Internal as S
import Foreign
type BufferWriter = Ptr Word8 -> Int -> IO (Int, Next)
data Next =
Done
| More !Int BufferWriter
| Chunk !S.ByteString BufferWriter
runBuilder :: Builder -> BufferWriter
runBuilder :: Builder -> BufferWriter
runBuilder = BuildStep () -> BufferWriter
run forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> BuildStep ()
I.runBuilder
where
bytesWritten :: Ptr b -> Ptr a -> Int
bytesWritten Ptr b
startPtr Ptr a
endPtr = Ptr a
endPtr forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr b
startPtr
run :: I.BuildStep () -> BufferWriter
run :: BuildStep () -> BufferWriter
run BuildStep ()
step = \Ptr Word8
buf Int
len ->
let doneH :: Ptr a -> () -> m (Int, Next)
doneH Ptr a
endPtr () =
let !wc :: Int
wc = forall a b. Ptr a -> Ptr b -> Int
bytesWritten Ptr Word8
buf Ptr a
endPtr
next :: Next
next = Next
Done
in forall (m :: * -> *) a. Monad m => a -> m a
return (Int
wc, Next
next)
bufferFullH :: Ptr a -> Int -> BuildStep () -> m (Int, Next)
bufferFullH Ptr a
endPtr Int
minReq BuildStep ()
step' =
let !wc :: Int
wc = forall a b. Ptr a -> Ptr b -> Int
bytesWritten Ptr Word8
buf Ptr a
endPtr
next :: Next
next = Int -> BufferWriter -> Next
More Int
minReq (BuildStep () -> BufferWriter
run BuildStep ()
step')
in forall (m :: * -> *) a. Monad m => a -> m a
return (Int
wc, Next
next)
insertChunkH :: Ptr a -> ByteString -> BuildStep () -> m (Int, Next)
insertChunkH Ptr a
endPtr ByteString
bs BuildStep ()
step' =
let !wc :: Int
wc = forall a b. Ptr a -> Ptr b -> Int
bytesWritten Ptr Word8
buf Ptr a
endPtr
next :: Next
next = ByteString -> BufferWriter -> Next
Chunk ByteString
bs (BuildStep () -> BufferWriter
run BuildStep ()
step')
in forall (m :: * -> *) a. Monad m => a -> m a
return (Int
wc, Next
next)
br :: BufferRange
br = Ptr Word8 -> Ptr Word8 -> BufferRange
I.BufferRange Ptr Word8
buf (Ptr Word8
buf forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
len)
in forall a b.
BuildStep a
-> (Ptr Word8 -> a -> IO b)
-> (Ptr Word8 -> Int -> BuildStep a -> IO b)
-> (Ptr Word8 -> ByteString -> BuildStep a -> IO b)
-> BufferRange
-> IO b
I.fillWithBuildStep BuildStep ()
step forall {m :: * -> *} {a}. Monad m => Ptr a -> () -> m (Int, Next)
doneH forall {m :: * -> *} {a}.
Monad m =>
Ptr a -> Int -> BuildStep () -> m (Int, Next)
bufferFullH forall {m :: * -> *} {a}.
Monad m =>
Ptr a -> ByteString -> BuildStep () -> m (Int, Next)
insertChunkH BufferRange
br
{-# INLINE intHost #-}
intHost :: Int -> Builder
intHost :: Int -> Builder
intHost = forall a. FixedPrim a -> a -> Builder
P.primFixed FixedPrim Int
P.intHost
{-# INLINE int16Host #-}
int16Host :: Int16 -> Builder
int16Host :: Int16 -> Builder
int16Host = forall a. FixedPrim a -> a -> Builder
P.primFixed FixedPrim Int16
P.int16Host
{-# INLINE int32Host #-}
int32Host :: Int32 -> Builder
int32Host :: Int32 -> Builder
int32Host = forall a. FixedPrim a -> a -> Builder
P.primFixed FixedPrim Int32
P.int32Host
{-# INLINE int64Host #-}
int64Host :: Int64 -> Builder
int64Host :: Int64 -> Builder
int64Host = forall a. FixedPrim a -> a -> Builder
P.primFixed FixedPrim Int64
P.int64Host
{-# INLINE wordHost #-}
wordHost :: Word -> Builder
wordHost :: Word -> Builder
wordHost = forall a. FixedPrim a -> a -> Builder
P.primFixed FixedPrim Word
P.wordHost
{-# INLINE word16Host #-}
word16Host :: Word16 -> Builder
word16Host :: Word16 -> Builder
word16Host = forall a. FixedPrim a -> a -> Builder
P.primFixed FixedPrim Word16
P.word16Host
{-# INLINE word32Host #-}
word32Host :: Word32 -> Builder
word32Host :: Word32 -> Builder
word32Host = forall a. FixedPrim a -> a -> Builder
P.primFixed FixedPrim Word32
P.word32Host
{-# INLINE word64Host #-}
word64Host :: Word64 -> Builder
word64Host :: Word64 -> Builder
word64Host = forall a. FixedPrim a -> a -> Builder
P.primFixed FixedPrim Word64
P.word64Host
{-# INLINE floatHost #-}
floatHost :: Float -> Builder
floatHost :: Float -> Builder
floatHost = forall a. FixedPrim a -> a -> Builder
P.primFixed FixedPrim Float
P.floatHost
{-# INLINE doubleHost #-}
doubleHost :: Double -> Builder
doubleHost :: Double -> Builder
doubleHost = forall a. FixedPrim a -> a -> Builder
P.primFixed FixedPrim Double
P.doubleHost