module Database.Franz.Writer.Simple (
Franz.WriterHandle,
openWriter,
Franz.closeWriter,
withWriter,
write,
Franz.flush,
Franz.getLastSeqNo,
ToFastBuilder(..)
) where
import Data.Proxy
import qualified Database.Franz.Writer as Franz
import qualified Data.ByteString.FastBuilder as BB
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
openWriter :: FilePath -> IO (Franz.WriterHandle Proxy)
openWriter :: FilePath -> IO (WriterHandle Proxy)
openWriter = Proxy FilePath -> FilePath -> IO (WriterHandle Proxy)
forall (f :: * -> *).
Foldable f =>
f FilePath -> FilePath -> IO (WriterHandle f)
Franz.openWriter Proxy FilePath
forall k (t :: k). Proxy t
Proxy
withWriter :: FilePath -> (Franz.WriterHandle Proxy -> IO a) -> IO a
withWriter :: FilePath -> (WriterHandle Proxy -> IO a) -> IO a
withWriter = Proxy FilePath -> FilePath -> (WriterHandle Proxy -> IO a) -> IO a
forall (f :: * -> *) a.
Foldable f =>
f FilePath -> FilePath -> (WriterHandle f -> IO a) -> IO a
Franz.withWriter Proxy FilePath
forall k (t :: k). Proxy t
Proxy
class ToFastBuilder a where
toFastBuilder :: a -> BB.Builder
instance ToFastBuilder B.ByteString where
toFastBuilder :: ByteString -> Builder
toFastBuilder = ByteString -> Builder
BB.byteString
instance ToFastBuilder BL.ByteString where
toFastBuilder :: ByteString -> Builder
toFastBuilder = (ByteString -> Builder) -> [ByteString] -> Builder
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ByteString -> Builder
BB.byteString ([ByteString] -> Builder)
-> (ByteString -> [ByteString]) -> ByteString -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString]
BL.toChunks
instance ToFastBuilder BB.Builder where
toFastBuilder :: Builder -> Builder
toFastBuilder = Builder -> Builder
forall a. a -> a
id
write :: Franz.WriterHandle Proxy
-> BB.Builder
-> IO Int
write :: WriterHandle Proxy -> Builder -> IO Int
write WriterHandle Proxy
h = WriterHandle Proxy -> Proxy Int64 -> Builder -> IO Int
forall (f :: * -> *).
Foldable f =>
WriterHandle f -> f Int64 -> Builder -> IO Int
Franz.write WriterHandle Proxy
h Proxy Int64
forall k (t :: k). Proxy t
Proxy (Builder -> IO Int) -> (Builder -> Builder) -> Builder -> IO Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Builder
forall a. ToFastBuilder a => a -> Builder
toFastBuilder
{-# INLINE write #-}