{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralisedNewtypeDeriving #-}
{-# LANGUAGE PatternSynonyms #-}
{-# OPTIONS_HADDOCK not-home #-}
module Database.LSMTree.Internal.Serialise (
SerialiseKey
, SerialiseValue
, SerialisedKey (SerialisedKey, SerialisedKey')
, serialiseKey
, deserialiseKey
, sizeofKey
, sizeofKey16
, sizeofKey32
, sizeofKey64
, serialisedKey
, keyTopBits64
, SerialisedValue (SerialisedValue, SerialisedValue')
, serialiseValue
, deserialiseValue
, sizeofValue
, sizeofValue16
, sizeofValue32
, sizeofValue64
, serialisedValue
, SerialisedBlob (SerialisedBlob, SerialisedBlob')
, serialiseBlob
, deserialiseBlob
, sizeofBlob
, sizeofBlob64
, serialisedBlob
) where
import Control.DeepSeq (NFData)
import Data.BloomFilter.Hash (Hashable (..))
import qualified Data.ByteString.Builder as BB
import qualified Data.Vector.Primitive as VP
import Data.Word
import Database.LSMTree.Internal.RawBytes (RawBytes (..))
import qualified Database.LSMTree.Internal.RawBytes as RB
import Database.LSMTree.Internal.Serialise.Class (SerialiseKey,
SerialiseValue)
import qualified Database.LSMTree.Internal.Serialise.Class as Class
newtype SerialisedKey = SerialisedKey RawBytes
deriving stock Int -> SerialisedKey -> ShowS
[SerialisedKey] -> ShowS
SerialisedKey -> String
(Int -> SerialisedKey -> ShowS)
-> (SerialisedKey -> String)
-> ([SerialisedKey] -> ShowS)
-> Show SerialisedKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SerialisedKey -> ShowS
showsPrec :: Int -> SerialisedKey -> ShowS
$cshow :: SerialisedKey -> String
show :: SerialisedKey -> String
$cshowList :: [SerialisedKey] -> ShowS
showList :: [SerialisedKey] -> ShowS
Show
deriving newtype (SerialisedKey -> SerialisedKey -> Bool
(SerialisedKey -> SerialisedKey -> Bool)
-> (SerialisedKey -> SerialisedKey -> Bool) -> Eq SerialisedKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SerialisedKey -> SerialisedKey -> Bool
== :: SerialisedKey -> SerialisedKey -> Bool
$c/= :: SerialisedKey -> SerialisedKey -> Bool
/= :: SerialisedKey -> SerialisedKey -> Bool
Eq, Eq SerialisedKey
Eq SerialisedKey =>
(SerialisedKey -> SerialisedKey -> Ordering)
-> (SerialisedKey -> SerialisedKey -> Bool)
-> (SerialisedKey -> SerialisedKey -> Bool)
-> (SerialisedKey -> SerialisedKey -> Bool)
-> (SerialisedKey -> SerialisedKey -> Bool)
-> (SerialisedKey -> SerialisedKey -> SerialisedKey)
-> (SerialisedKey -> SerialisedKey -> SerialisedKey)
-> Ord SerialisedKey
SerialisedKey -> SerialisedKey -> Bool
SerialisedKey -> SerialisedKey -> Ordering
SerialisedKey -> SerialisedKey -> SerialisedKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SerialisedKey -> SerialisedKey -> Ordering
compare :: SerialisedKey -> SerialisedKey -> Ordering
$c< :: SerialisedKey -> SerialisedKey -> Bool
< :: SerialisedKey -> SerialisedKey -> Bool
$c<= :: SerialisedKey -> SerialisedKey -> Bool
<= :: SerialisedKey -> SerialisedKey -> Bool
$c> :: SerialisedKey -> SerialisedKey -> Bool
> :: SerialisedKey -> SerialisedKey -> Bool
$c>= :: SerialisedKey -> SerialisedKey -> Bool
>= :: SerialisedKey -> SerialisedKey -> Bool
$cmax :: SerialisedKey -> SerialisedKey -> SerialisedKey
max :: SerialisedKey -> SerialisedKey -> SerialisedKey
$cmin :: SerialisedKey -> SerialisedKey -> SerialisedKey
min :: SerialisedKey -> SerialisedKey -> SerialisedKey
Ord, Word64 -> SerialisedKey -> Word64
(Word64 -> SerialisedKey -> Word64) -> Hashable SerialisedKey
forall a. (Word64 -> a -> Word64) -> Hashable a
$chashSalt64 :: Word64 -> SerialisedKey -> Word64
hashSalt64 :: Word64 -> SerialisedKey -> Word64
Hashable, SerialisedKey -> ()
(SerialisedKey -> ()) -> NFData SerialisedKey
forall a. (a -> ()) -> NFData a
$crnf :: SerialisedKey -> ()
rnf :: SerialisedKey -> ()
NFData)
{-# COMPLETE SerialisedKey' #-}
pattern SerialisedKey' :: VP.Vector Word8 -> SerialisedKey
pattern $mSerialisedKey' :: forall {r}.
SerialisedKey -> (Vector Word8 -> r) -> ((# #) -> r) -> r
$bSerialisedKey' :: Vector Word8 -> SerialisedKey
SerialisedKey' pvec = SerialisedKey (RawBytes pvec)
{-# INLINE serialiseKey #-}
serialiseKey :: SerialiseKey k => k -> SerialisedKey
serialiseKey :: forall k. SerialiseKey k => k -> SerialisedKey
serialiseKey k
k = RawBytes -> SerialisedKey
SerialisedKey (k -> RawBytes
forall k. SerialiseKey k => k -> RawBytes
Class.serialiseKey k
k)
{-# INLINE deserialiseKey #-}
deserialiseKey :: SerialiseKey k => SerialisedKey -> k
deserialiseKey :: forall k. SerialiseKey k => SerialisedKey -> k
deserialiseKey (SerialisedKey RawBytes
bytes) = RawBytes -> k
forall k. SerialiseKey k => RawBytes -> k
Class.deserialiseKey RawBytes
bytes
{-# INLINE sizeofKey #-}
sizeofKey :: SerialisedKey -> Int
sizeofKey :: SerialisedKey -> Int
sizeofKey (SerialisedKey RawBytes
rb) = RawBytes -> Int
RB.size RawBytes
rb
{-# INLINE sizeofKey16 #-}
sizeofKey16 :: SerialisedKey -> Word16
sizeofKey16 :: SerialisedKey -> Word16
sizeofKey16 = Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word16)
-> (SerialisedKey -> Int) -> SerialisedKey -> Word16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SerialisedKey -> Int
sizeofKey
{-# INLINE sizeofKey32 #-}
sizeofKey32 :: SerialisedKey -> Word32
sizeofKey32 :: SerialisedKey -> Word32
sizeofKey32 = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32)
-> (SerialisedKey -> Int) -> SerialisedKey -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SerialisedKey -> Int
sizeofKey
{-# INLINE sizeofKey64 #-}
sizeofKey64 :: SerialisedKey -> Word64
sizeofKey64 :: SerialisedKey -> Word64
sizeofKey64 = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64)
-> (SerialisedKey -> Int) -> SerialisedKey -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SerialisedKey -> Int
sizeofKey
{-# INLINE serialisedKey #-}
serialisedKey :: SerialisedKey -> BB.Builder
serialisedKey :: SerialisedKey -> Builder
serialisedKey (SerialisedKey RawBytes
rb) = RawBytes -> Builder
RB.builder RawBytes
rb
{-# INLINE keyTopBits64 #-}
keyTopBits64 :: SerialisedKey -> Word64
keyTopBits64 :: SerialisedKey -> Word64
keyTopBits64 (SerialisedKey RawBytes
rb) = RawBytes -> Word64
RB.topBits64 RawBytes
rb
newtype SerialisedValue = SerialisedValue RawBytes
deriving stock Int -> SerialisedValue -> ShowS
[SerialisedValue] -> ShowS
SerialisedValue -> String
(Int -> SerialisedValue -> ShowS)
-> (SerialisedValue -> String)
-> ([SerialisedValue] -> ShowS)
-> Show SerialisedValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SerialisedValue -> ShowS
showsPrec :: Int -> SerialisedValue -> ShowS
$cshow :: SerialisedValue -> String
show :: SerialisedValue -> String
$cshowList :: [SerialisedValue] -> ShowS
showList :: [SerialisedValue] -> ShowS
Show
deriving newtype (SerialisedValue -> SerialisedValue -> Bool
(SerialisedValue -> SerialisedValue -> Bool)
-> (SerialisedValue -> SerialisedValue -> Bool)
-> Eq SerialisedValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SerialisedValue -> SerialisedValue -> Bool
== :: SerialisedValue -> SerialisedValue -> Bool
$c/= :: SerialisedValue -> SerialisedValue -> Bool
/= :: SerialisedValue -> SerialisedValue -> Bool
Eq, Eq SerialisedValue
Eq SerialisedValue =>
(SerialisedValue -> SerialisedValue -> Ordering)
-> (SerialisedValue -> SerialisedValue -> Bool)
-> (SerialisedValue -> SerialisedValue -> Bool)
-> (SerialisedValue -> SerialisedValue -> Bool)
-> (SerialisedValue -> SerialisedValue -> Bool)
-> (SerialisedValue -> SerialisedValue -> SerialisedValue)
-> (SerialisedValue -> SerialisedValue -> SerialisedValue)
-> Ord SerialisedValue
SerialisedValue -> SerialisedValue -> Bool
SerialisedValue -> SerialisedValue -> Ordering
SerialisedValue -> SerialisedValue -> SerialisedValue
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SerialisedValue -> SerialisedValue -> Ordering
compare :: SerialisedValue -> SerialisedValue -> Ordering
$c< :: SerialisedValue -> SerialisedValue -> Bool
< :: SerialisedValue -> SerialisedValue -> Bool
$c<= :: SerialisedValue -> SerialisedValue -> Bool
<= :: SerialisedValue -> SerialisedValue -> Bool
$c> :: SerialisedValue -> SerialisedValue -> Bool
> :: SerialisedValue -> SerialisedValue -> Bool
$c>= :: SerialisedValue -> SerialisedValue -> Bool
>= :: SerialisedValue -> SerialisedValue -> Bool
$cmax :: SerialisedValue -> SerialisedValue -> SerialisedValue
max :: SerialisedValue -> SerialisedValue -> SerialisedValue
$cmin :: SerialisedValue -> SerialisedValue -> SerialisedValue
min :: SerialisedValue -> SerialisedValue -> SerialisedValue
Ord, SerialisedValue -> ()
(SerialisedValue -> ()) -> NFData SerialisedValue
forall a. (a -> ()) -> NFData a
$crnf :: SerialisedValue -> ()
rnf :: SerialisedValue -> ()
NFData)
{-# COMPLETE SerialisedValue' #-}
pattern SerialisedValue' :: VP.Vector Word8 -> SerialisedValue
pattern $mSerialisedValue' :: forall {r}.
SerialisedValue -> (Vector Word8 -> r) -> ((# #) -> r) -> r
$bSerialisedValue' :: Vector Word8 -> SerialisedValue
SerialisedValue' pvec = (SerialisedValue (RawBytes pvec))
{-# INLINE serialiseValue #-}
serialiseValue :: SerialiseValue v => v -> SerialisedValue
serialiseValue :: forall v. SerialiseValue v => v -> SerialisedValue
serialiseValue v
v = RawBytes -> SerialisedValue
SerialisedValue (v -> RawBytes
forall v. SerialiseValue v => v -> RawBytes
Class.serialiseValue v
v)
{-# INLINE deserialiseValue #-}
deserialiseValue :: SerialiseValue v => SerialisedValue -> v
deserialiseValue :: forall v. SerialiseValue v => SerialisedValue -> v
deserialiseValue (SerialisedValue RawBytes
bytes) = RawBytes -> v
forall v. SerialiseValue v => RawBytes -> v
Class.deserialiseValue RawBytes
bytes
{-# INLINE sizeofValue #-}
sizeofValue :: SerialisedValue -> Int
sizeofValue :: SerialisedValue -> Int
sizeofValue (SerialisedValue RawBytes
rb) = RawBytes -> Int
RB.size RawBytes
rb
{-# INLINE sizeofValue16 #-}
sizeofValue16 :: SerialisedValue -> Word16
sizeofValue16 :: SerialisedValue -> Word16
sizeofValue16 = Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word16)
-> (SerialisedValue -> Int) -> SerialisedValue -> Word16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SerialisedValue -> Int
sizeofValue
{-# INLINE sizeofValue32 #-}
sizeofValue32 :: SerialisedValue -> Word32
sizeofValue32 :: SerialisedValue -> Word32
sizeofValue32 = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32)
-> (SerialisedValue -> Int) -> SerialisedValue -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SerialisedValue -> Int
sizeofValue
{-# INLINE sizeofValue64 #-}
sizeofValue64 :: SerialisedValue -> Word64
sizeofValue64 :: SerialisedValue -> Word64
sizeofValue64 = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64)
-> (SerialisedValue -> Int) -> SerialisedValue -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SerialisedValue -> Int
sizeofValue
{-# LANGUAGE serialisedValue #-}
serialisedValue :: SerialisedValue -> BB.Builder
serialisedValue :: SerialisedValue -> Builder
serialisedValue (SerialisedValue RawBytes
rb) = RawBytes -> Builder
RB.builder RawBytes
rb
newtype SerialisedBlob = SerialisedBlob RawBytes
deriving stock Int -> SerialisedBlob -> ShowS
[SerialisedBlob] -> ShowS
SerialisedBlob -> String
(Int -> SerialisedBlob -> ShowS)
-> (SerialisedBlob -> String)
-> ([SerialisedBlob] -> ShowS)
-> Show SerialisedBlob
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SerialisedBlob -> ShowS
showsPrec :: Int -> SerialisedBlob -> ShowS
$cshow :: SerialisedBlob -> String
show :: SerialisedBlob -> String
$cshowList :: [SerialisedBlob] -> ShowS
showList :: [SerialisedBlob] -> ShowS
Show
deriving newtype (SerialisedBlob -> SerialisedBlob -> Bool
(SerialisedBlob -> SerialisedBlob -> Bool)
-> (SerialisedBlob -> SerialisedBlob -> Bool) -> Eq SerialisedBlob
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SerialisedBlob -> SerialisedBlob -> Bool
== :: SerialisedBlob -> SerialisedBlob -> Bool
$c/= :: SerialisedBlob -> SerialisedBlob -> Bool
/= :: SerialisedBlob -> SerialisedBlob -> Bool
Eq, Eq SerialisedBlob
Eq SerialisedBlob =>
(SerialisedBlob -> SerialisedBlob -> Ordering)
-> (SerialisedBlob -> SerialisedBlob -> Bool)
-> (SerialisedBlob -> SerialisedBlob -> Bool)
-> (SerialisedBlob -> SerialisedBlob -> Bool)
-> (SerialisedBlob -> SerialisedBlob -> Bool)
-> (SerialisedBlob -> SerialisedBlob -> SerialisedBlob)
-> (SerialisedBlob -> SerialisedBlob -> SerialisedBlob)
-> Ord SerialisedBlob
SerialisedBlob -> SerialisedBlob -> Bool
SerialisedBlob -> SerialisedBlob -> Ordering
SerialisedBlob -> SerialisedBlob -> SerialisedBlob
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: SerialisedBlob -> SerialisedBlob -> Ordering
compare :: SerialisedBlob -> SerialisedBlob -> Ordering
$c< :: SerialisedBlob -> SerialisedBlob -> Bool
< :: SerialisedBlob -> SerialisedBlob -> Bool
$c<= :: SerialisedBlob -> SerialisedBlob -> Bool
<= :: SerialisedBlob -> SerialisedBlob -> Bool
$c> :: SerialisedBlob -> SerialisedBlob -> Bool
> :: SerialisedBlob -> SerialisedBlob -> Bool
$c>= :: SerialisedBlob -> SerialisedBlob -> Bool
>= :: SerialisedBlob -> SerialisedBlob -> Bool
$cmax :: SerialisedBlob -> SerialisedBlob -> SerialisedBlob
max :: SerialisedBlob -> SerialisedBlob -> SerialisedBlob
$cmin :: SerialisedBlob -> SerialisedBlob -> SerialisedBlob
min :: SerialisedBlob -> SerialisedBlob -> SerialisedBlob
Ord, SerialisedBlob -> ()
(SerialisedBlob -> ()) -> NFData SerialisedBlob
forall a. (a -> ()) -> NFData a
$crnf :: SerialisedBlob -> ()
rnf :: SerialisedBlob -> ()
NFData)
{-# COMPLETE SerialisedBlob' #-}
pattern SerialisedBlob' :: VP.Vector Word8 -> SerialisedBlob
pattern $mSerialisedBlob' :: forall {r}.
SerialisedBlob -> (Vector Word8 -> r) -> ((# #) -> r) -> r
$bSerialisedBlob' :: Vector Word8 -> SerialisedBlob
SerialisedBlob' pvec = (SerialisedBlob (RawBytes pvec))
{-# INLINE serialiseBlob #-}
serialiseBlob :: SerialiseValue v => v -> SerialisedBlob
serialiseBlob :: forall v. SerialiseValue v => v -> SerialisedBlob
serialiseBlob v
v = RawBytes -> SerialisedBlob
SerialisedBlob (v -> RawBytes
forall v. SerialiseValue v => v -> RawBytes
Class.serialiseValue v
v)
{-# INLINE deserialiseBlob #-}
deserialiseBlob :: SerialiseValue v => SerialisedBlob -> v
deserialiseBlob :: forall v. SerialiseValue v => SerialisedBlob -> v
deserialiseBlob (SerialisedBlob RawBytes
bytes) = RawBytes -> v
forall v. SerialiseValue v => RawBytes -> v
Class.deserialiseValue RawBytes
bytes
{-# INLINE sizeofBlob #-}
sizeofBlob :: SerialisedBlob -> Int
sizeofBlob :: SerialisedBlob -> Int
sizeofBlob (SerialisedBlob RawBytes
rb) = RawBytes -> Int
RB.size RawBytes
rb
{-# INLINE sizeofBlob64 #-}
sizeofBlob64 :: SerialisedBlob -> Word64
sizeofBlob64 :: SerialisedBlob -> Word64
sizeofBlob64 = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64)
-> (SerialisedBlob -> Int) -> SerialisedBlob -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SerialisedBlob -> Int
sizeofBlob
{-# INLINE serialisedBlob #-}
serialisedBlob :: SerialisedBlob -> BB.Builder
serialisedBlob :: SerialisedBlob -> Builder
serialisedBlob (SerialisedBlob RawBytes
rb) = RawBytes -> Builder
RB.builder RawBytes
rb