{-# OPTIONS_HADDOCK not-home #-}
module Database.LSMTree.Internal.PageAcc (
PageAcc (..),
newPageAcc,
resetPageAcc,
pageAccAddElem,
serialisePageAcc,
keysCountPageAcc,
indexKeyPageAcc,
entryWouldFitInPage,
sizeofEntry,
) where
import Control.Monad.ST.Strict (ST)
import Data.Bits (unsafeShiftL, (.|.))
import qualified Data.Primitive as P
import qualified Data.Vector as V
import qualified Data.Vector.Mutable as VM
import qualified Data.Vector.Primitive as VP
import Data.Word (Word16, Word32, Word64)
import Database.LSMTree.Internal.BitMath
import Database.LSMTree.Internal.BlobRef (BlobSpan (..))
import Database.LSMTree.Internal.Entry (Entry (..))
import Database.LSMTree.Internal.RawBytes (RawBytes (..))
import qualified Database.LSMTree.Internal.RawBytes as RB
import Database.LSMTree.Internal.RawPage
import Database.LSMTree.Internal.Serialise
data PageAcc s = PageAcc
{ forall s. PageAcc s -> MutablePrimArray s Int
paDir :: !(P.MutablePrimArray s Int)
, forall s. PageAcc s -> MutablePrimArray s Word64
paOpMap :: !(P.MutablePrimArray s Word64)
, forall s. PageAcc s -> MutablePrimArray s Word64
paBlobRefsMap :: !(P.MutablePrimArray s Word64)
, forall s. PageAcc s -> MutablePrimArray s Word64
paBlobRefs1 :: !(P.MutablePrimArray s Word64)
, forall s. PageAcc s -> MutablePrimArray s Word32
paBlobRefs2 :: !(P.MutablePrimArray s Word32)
, forall s. PageAcc s -> MVector s SerialisedKey
paKeys :: !(V.MVector s SerialisedKey)
, forall s. PageAcc s -> MVector s SerialisedValue
paValues :: !(V.MVector s SerialisedValue)
}
keysCountIdx :: Int
keysCountIdx :: Int
keysCountIdx = Int
0
{-# INLINE keysCountIdx #-}
blobRefCountIdx :: Int
blobRefCountIdx :: Int
blobRefCountIdx = Int
1
{-# INLINE blobRefCountIdx #-}
byteSizeIdx :: Int
byteSizeIdx :: Int
byteSizeIdx = Int
2
{-# INLINE byteSizeIdx #-}
keysSizeIdx :: Int
keysSizeIdx :: Int
keysSizeIdx = Int
3
{-# INLINE keysSizeIdx #-}
pageSize :: Int
pageSize :: Int
pageSize = Int
4096
{-# INLINE pageSize #-}
maxKeys :: Int
maxKeys :: Int
maxKeys = Int
759
{-# INLINE maxKeys #-}
maxOpMap :: Int
maxOpMap :: Int
maxOpMap = Int
24
{-# INLINE maxOpMap #-}
maxBlobRefsMap :: Int
maxBlobRefsMap :: Int
maxBlobRefsMap = Int
12
{-# INLINE maxBlobRefsMap #-}
sizeofEntry :: SerialisedKey -> Entry SerialisedValue b -> Int
sizeofEntry :: forall b. SerialisedKey -> Entry SerialisedValue b -> Int
sizeofEntry SerialisedKey
k Entry SerialisedValue b
Delete = SerialisedKey -> Int
sizeofKey SerialisedKey
k
sizeofEntry SerialisedKey
k (Mupdate SerialisedValue
v) = SerialisedKey -> Int
sizeofKey SerialisedKey
k Int -> Int -> Int
forall a. Num a => a -> a -> a
+ SerialisedValue -> Int
sizeofValue SerialisedValue
v
sizeofEntry SerialisedKey
k (Insert SerialisedValue
v) = SerialisedKey -> Int
sizeofKey SerialisedKey
k Int -> Int -> Int
forall a. Num a => a -> a -> a
+ SerialisedValue -> Int
sizeofValue SerialisedValue
v
sizeofEntry SerialisedKey
k (InsertWithBlob SerialisedValue
v b
_) = SerialisedKey -> Int
sizeofKey SerialisedKey
k Int -> Int -> Int
forall a. Num a => a -> a -> a
+ SerialisedValue -> Int
sizeofValue SerialisedValue
v Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
12
entryWouldFitInPage :: SerialisedKey -> Entry SerialisedValue b -> Bool
entryWouldFitInPage :: forall b. SerialisedKey -> Entry SerialisedValue b -> Bool
entryWouldFitInPage SerialisedKey
k Entry SerialisedValue b
e = SerialisedKey -> Entry SerialisedValue b -> Int
forall b. SerialisedKey -> Entry SerialisedValue b -> Int
sizeofEntry SerialisedKey
k Entry SerialisedValue b
e Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
32 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
pageSize
hasBlobRef :: Entry a b -> Bool
hasBlobRef :: forall a b. Entry a b -> Bool
hasBlobRef (InsertWithBlob a
_ b
_) = Bool
True
hasBlobRef Entry a b
_ = Bool
False
entryCrumb :: Entry SerialisedValue BlobSpan -> Word64
entryCrumb :: Entry SerialisedValue BlobSpan -> Word64
entryCrumb Insert {} = Word64
0
entryCrumb InsertWithBlob {} = Word64
0
entryCrumb Mupdate {} = Word64
1
entryCrumb Delete {} = Word64
2
entryValue :: Entry SerialisedValue BlobSpan -> SerialisedValue
entryValue :: Entry SerialisedValue BlobSpan -> SerialisedValue
entryValue (Insert SerialisedValue
v) = SerialisedValue
v
entryValue (InsertWithBlob SerialisedValue
v BlobSpan
_) = SerialisedValue
v
entryValue (Mupdate SerialisedValue
v) = SerialisedValue
v
entryValue Entry SerialisedValue BlobSpan
Delete = SerialisedValue
emptyValue
emptyValue :: SerialisedValue
emptyValue :: SerialisedValue
emptyValue = RawBytes -> SerialisedValue
SerialisedValue ([Word8] -> RawBytes
RB.pack [])
newPageAcc :: ST s (PageAcc s)
newPageAcc :: forall s. ST s (PageAcc s)
newPageAcc = do
MutablePrimArray s Int
paDir <- Int -> ST s (MutablePrimArray (PrimState (ST s)) Int)
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
Int -> m (MutablePrimArray (PrimState m) a)
P.newPrimArray Int
4
MutablePrimArray s Word64
paOpMap <- Int -> ST s (MutablePrimArray (PrimState (ST s)) Word64)
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
Int -> m (MutablePrimArray (PrimState m) a)
P.newPrimArray Int
maxOpMap
MutablePrimArray s Word64
paBlobRefsMap <- Int -> ST s (MutablePrimArray (PrimState (ST s)) Word64)
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
Int -> m (MutablePrimArray (PrimState m) a)
P.newPrimArray Int
maxBlobRefsMap
MutablePrimArray s Word64
paBlobRefs1 <- Int -> ST s (MutablePrimArray (PrimState (ST s)) Word64)
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
Int -> m (MutablePrimArray (PrimState m) a)
P.newPrimArray Int
maxKeys
MutablePrimArray s Word32
paBlobRefs2 <- Int -> ST s (MutablePrimArray (PrimState (ST s)) Word32)
forall (m :: * -> *) a.
(PrimMonad m, Prim a) =>
Int -> m (MutablePrimArray (PrimState m) a)
P.newPrimArray Int
maxKeys
MVector s SerialisedKey
paKeys <- Int -> ST s (MVector (PrimState (ST s)) SerialisedKey)
forall (m :: * -> *) a.
PrimMonad m =>
Int -> m (MVector (PrimState m) a)
VM.new Int
maxKeys
MVector s SerialisedValue
paValues <- Int -> ST s (MVector (PrimState (ST s)) SerialisedValue)
forall (m :: * -> *) a.
PrimMonad m =>
Int -> m (MVector (PrimState m) a)
VM.new Int
maxKeys
let page :: PageAcc s
page = PageAcc {MutablePrimArray s Int
MutablePrimArray s Word32
MutablePrimArray s Word64
MVector s SerialisedValue
MVector s SerialisedKey
paDir :: MutablePrimArray s Int
paOpMap :: MutablePrimArray s Word64
paBlobRefsMap :: MutablePrimArray s Word64
paBlobRefs1 :: MutablePrimArray s Word64
paBlobRefs2 :: MutablePrimArray s Word32
paKeys :: MVector s SerialisedKey
paValues :: MVector s SerialisedValue
paDir :: MutablePrimArray s Int
paOpMap :: MutablePrimArray s Word64
paBlobRefsMap :: MutablePrimArray s Word64
paBlobRefs1 :: MutablePrimArray s Word64
paBlobRefs2 :: MutablePrimArray s Word32
paKeys :: MVector s SerialisedKey
paValues :: MVector s SerialisedValue
..}
PageAcc s -> Int -> ST s ()
forall s. PageAcc s -> Int -> ST s ()
resetPageAccN PageAcc s
page Int
maxKeys
PageAcc s -> ST s (PageAcc s)
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return PageAcc s
page
dummyKey :: SerialisedKey
dummyKey :: SerialisedKey
dummyKey = RawBytes -> SerialisedKey
SerialisedKey RawBytes
forall a. Monoid a => a
mempty
dummyValue :: SerialisedValue
dummyValue :: SerialisedValue
dummyValue = RawBytes -> SerialisedValue
SerialisedValue RawBytes
forall a. Monoid a => a
mempty
resetPageAcc :: PageAcc s
-> ST s ()
resetPageAcc :: forall s. PageAcc s -> ST s ()
resetPageAcc PageAcc s
pa = do
!Int
n <- PageAcc s -> ST s Int
forall s. PageAcc s -> ST s Int
keysCountPageAcc PageAcc s
pa
PageAcc s -> Int -> ST s ()
forall s. PageAcc s -> Int -> ST s ()
resetPageAccN PageAcc s
pa Int
n
resetPageAccN :: PageAcc s -> Int -> ST s ()
resetPageAccN :: forall s. PageAcc s -> Int -> ST s ()
resetPageAccN PageAcc {MutablePrimArray s Int
MutablePrimArray s Word32
MutablePrimArray s Word64
MVector s SerialisedValue
MVector s SerialisedKey
paDir :: forall s. PageAcc s -> MutablePrimArray s Int
paOpMap :: forall s. PageAcc s -> MutablePrimArray s Word64
paBlobRefsMap :: forall s. PageAcc s -> MutablePrimArray s Word64
paBlobRefs1 :: forall s. PageAcc s -> MutablePrimArray s Word64
paBlobRefs2 :: forall s. PageAcc s -> MutablePrimArray s Word32
paKeys :: forall s. PageAcc s -> MVector s SerialisedKey
paValues :: forall s. PageAcc s -> MVector s SerialisedValue
paDir :: MutablePrimArray s Int
paOpMap :: MutablePrimArray s Word64
paBlobRefsMap :: MutablePrimArray s Word64
paBlobRefs1 :: MutablePrimArray s Word64
paBlobRefs2 :: MutablePrimArray s Word32
paKeys :: MVector s SerialisedKey
paValues :: MVector s SerialisedValue
..} !Int
n = do
MutablePrimArray (PrimState (ST s)) Int
-> Int -> Int -> Int -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
P.setPrimArray MutablePrimArray s Int
MutablePrimArray (PrimState (ST s)) Int
paDir Int
0 Int
4 Int
0
MutablePrimArray (PrimState (ST s)) Word64
-> Int -> Int -> Word64 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
P.setPrimArray MutablePrimArray s Word64
MutablePrimArray (PrimState (ST s)) Word64
paOpMap Int
0 Int
maxOpMap Word64
0
MutablePrimArray (PrimState (ST s)) Word64
-> Int -> Int -> Word64 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> Int -> a -> m ()
P.setPrimArray MutablePrimArray s Word64
MutablePrimArray (PrimState (ST s)) Word64
paBlobRefsMap Int
0 Int
maxBlobRefsMap Word64
0
MVector (PrimState (ST s)) SerialisedKey
-> SerialisedKey -> ST s ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> a -> m ()
VM.set (Int -> Int -> MVector s SerialisedKey -> MVector s SerialisedKey
forall s a. Int -> Int -> MVector s a -> MVector s a
VM.slice Int
0 Int
n MVector s SerialisedKey
paKeys) (SerialisedKey -> ST s ()) -> SerialisedKey -> ST s ()
forall a b. (a -> b) -> a -> b
$! SerialisedKey
dummyKey
MVector (PrimState (ST s)) SerialisedValue
-> SerialisedValue -> ST s ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> a -> m ()
VM.set (Int
-> Int -> MVector s SerialisedValue -> MVector s SerialisedValue
forall s a. Int -> Int -> MVector s a -> MVector s a
VM.slice Int
0 Int
n MVector s SerialisedValue
paValues) (SerialisedValue -> ST s ()) -> SerialisedValue -> ST s ()
forall a b. (a -> b) -> a -> b
$! SerialisedValue
dummyValue
MutablePrimArray (PrimState (ST s)) Int -> Int -> Int -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
P.writePrimArray MutablePrimArray s Int
MutablePrimArray (PrimState (ST s)) Int
paDir Int
byteSizeIdx Int
10
pageAccAddElem ::
PageAcc s
-> SerialisedKey
-> Entry SerialisedValue BlobSpan
-> ST s Bool
pageAccAddElem :: forall s.
PageAcc s
-> SerialisedKey -> Entry SerialisedValue BlobSpan -> ST s Bool
pageAccAddElem PageAcc {MutablePrimArray s Int
MutablePrimArray s Word32
MutablePrimArray s Word64
MVector s SerialisedValue
MVector s SerialisedKey
paDir :: forall s. PageAcc s -> MutablePrimArray s Int
paOpMap :: forall s. PageAcc s -> MutablePrimArray s Word64
paBlobRefsMap :: forall s. PageAcc s -> MutablePrimArray s Word64
paBlobRefs1 :: forall s. PageAcc s -> MutablePrimArray s Word64
paBlobRefs2 :: forall s. PageAcc s -> MutablePrimArray s Word32
paKeys :: forall s. PageAcc s -> MVector s SerialisedKey
paValues :: forall s. PageAcc s -> MVector s SerialisedValue
paDir :: MutablePrimArray s Int
paOpMap :: MutablePrimArray s Word64
paBlobRefsMap :: MutablePrimArray s Word64
paBlobRefs1 :: MutablePrimArray s Word64
paBlobRefs2 :: MutablePrimArray s Word32
paKeys :: MVector s SerialisedKey
paValues :: MVector s SerialisedValue
..} SerialisedKey
k Entry SerialisedValue BlobSpan
e
| SerialisedKey -> Entry SerialisedValue BlobSpan -> Int
forall b. SerialisedKey -> Entry SerialisedValue b -> Int
sizeofEntry SerialisedKey
k Entry SerialisedValue BlobSpan
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
pageSize = Bool -> ST s Bool
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
| Bool
otherwise = do
Int
n <- MutablePrimArray (PrimState (ST s)) Int -> Int -> ST s Int
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
P.readPrimArray MutablePrimArray s Int
MutablePrimArray (PrimState (ST s)) Int
paDir Int
keysCountIdx
Int
b <- MutablePrimArray (PrimState (ST s)) Int -> Int -> ST s Int
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
P.readPrimArray MutablePrimArray s Int
MutablePrimArray (PrimState (ST s)) Int
paDir Int
blobRefCountIdx
Int
s <- MutablePrimArray (PrimState (ST s)) Int -> Int -> ST s Int
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
P.readPrimArray MutablePrimArray s Int
MutablePrimArray (PrimState (ST s)) Int
paDir Int
byteSizeIdx
let !n' :: Int
n' = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
let !b' :: Int
b' = if Entry SerialisedValue BlobSpan -> Bool
forall a b. Entry a b -> Bool
hasBlobRef Entry SerialisedValue BlobSpan
e then Int
b Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 else Int
b
let !s' :: Int
s' = Int
s
Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if Int -> Int
forall a. (Bits a, Num a) => a -> a
mod64 Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
8 else Int
0)
Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (if Int -> Int
forall a. (Bits a, Num a) => a -> a
mod32 Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
8 else Int
0)
Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (case Int
n of { Int
0 -> Int
6; Int
1 -> Int
2; Int
_ -> Int
4 })
Int -> Int -> Int
forall a. Num a => a -> a -> a
+ SerialisedKey -> Entry SerialisedValue BlobSpan -> Int
forall b. SerialisedKey -> Entry SerialisedValue b -> Int
sizeofEntry SerialisedKey
k Entry SerialisedValue BlobSpan
e
if Int
s' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
pageSize Bool -> Bool -> Bool
||
Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
maxKeys
then Bool -> ST s Bool
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
else do
Int
ks <- MutablePrimArray (PrimState (ST s)) Int -> Int -> ST s Int
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
P.readPrimArray MutablePrimArray s Int
MutablePrimArray (PrimState (ST s)) Int
paDir Int
keysSizeIdx
let !ks' :: Int
ks' = Int
ks Int -> Int -> Int
forall a. Num a => a -> a -> a
+ SerialisedKey -> Int
sizeofKey SerialisedKey
k
MutablePrimArray (PrimState (ST s)) Int -> Int -> Int -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
P.writePrimArray MutablePrimArray s Int
MutablePrimArray (PrimState (ST s)) Int
paDir Int
keysCountIdx Int
n'
MutablePrimArray (PrimState (ST s)) Int -> Int -> Int -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
P.writePrimArray MutablePrimArray s Int
MutablePrimArray (PrimState (ST s)) Int
paDir Int
blobRefCountIdx Int
b'
MutablePrimArray (PrimState (ST s)) Int -> Int -> Int -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
P.writePrimArray MutablePrimArray s Int
MutablePrimArray (PrimState (ST s)) Int
paDir Int
keysSizeIdx Int
ks'
MutablePrimArray (PrimState (ST s)) Int -> Int -> Int -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
P.writePrimArray MutablePrimArray s Int
MutablePrimArray (PrimState (ST s)) Int
paDir Int
byteSizeIdx Int
s'
case Entry SerialisedValue BlobSpan
e of
InsertWithBlob SerialisedValue
_ (BlobSpan Word64
w64 Word32
w32) -> do
MutablePrimArray s Word64 -> Int -> ST s ()
forall s. MutablePrimArray s Word64 -> Int -> ST s ()
setBlobRef MutablePrimArray s Word64
paBlobRefsMap Int
n
MutablePrimArray (PrimState (ST s)) Word64
-> Int -> Word64 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
P.writePrimArray MutablePrimArray s Word64
MutablePrimArray (PrimState (ST s)) Word64
paBlobRefs1 Int
b Word64
w64
MutablePrimArray (PrimState (ST s)) Word32
-> Int -> Word32 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
P.writePrimArray MutablePrimArray s Word32
MutablePrimArray (PrimState (ST s)) Word32
paBlobRefs2 Int
b Word32
w32
Entry SerialisedValue BlobSpan
_ -> () -> ST s ()
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
MutablePrimArray s Word64 -> Int -> Word64 -> ST s ()
forall s. MutablePrimArray s Word64 -> Int -> Word64 -> ST s ()
setOperation MutablePrimArray s Word64
paOpMap Int
n (Entry SerialisedValue BlobSpan -> Word64
entryCrumb Entry SerialisedValue BlobSpan
e)
MVector (PrimState (ST s)) SerialisedKey
-> Int -> SerialisedKey -> ST s ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> a -> m ()
VM.write MVector s SerialisedKey
MVector (PrimState (ST s)) SerialisedKey
paKeys Int
n SerialisedKey
k
MVector (PrimState (ST s)) SerialisedValue
-> Int -> SerialisedValue -> ST s ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> a -> m ()
VM.write MVector s SerialisedValue
MVector (PrimState (ST s)) SerialisedValue
paValues Int
n (SerialisedValue -> ST s ()) -> SerialisedValue -> ST s ()
forall a b. (a -> b) -> a -> b
$! Entry SerialisedValue BlobSpan -> SerialisedValue
entryValue Entry SerialisedValue BlobSpan
e
Bool -> ST s Bool
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
setBlobRef :: P.MutablePrimArray s Word64 -> Int -> ST s ()
setBlobRef :: forall s. MutablePrimArray s Word64 -> Int -> ST s ()
setBlobRef MutablePrimArray s Word64
arr Int
i = do
let !j :: Int
j = Int -> Int
forall a. Bits a => a -> a
div64 Int
i
let !k :: Int
k = Int -> Int
forall a. (Bits a, Num a) => a -> a
mod64 Int
i
Word64
w64 <- MutablePrimArray (PrimState (ST s)) Word64 -> Int -> ST s Word64
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
P.readPrimArray MutablePrimArray s Word64
MutablePrimArray (PrimState (ST s)) Word64
arr Int
j
let w64' :: Word64
w64' = Word64
w64 Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
1 Int
k
MutablePrimArray (PrimState (ST s)) Word64
-> Int -> Word64 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
P.writePrimArray MutablePrimArray s Word64
MutablePrimArray (PrimState (ST s)) Word64
arr Int
j (Word64 -> ST s ()) -> Word64 -> ST s ()
forall a b. (a -> b) -> a -> b
$! Word64
w64'
setOperation :: P.MutablePrimArray s Word64 -> Int -> Word64 -> ST s ()
setOperation :: forall s. MutablePrimArray s Word64 -> Int -> Word64 -> ST s ()
setOperation MutablePrimArray s Word64
arr Int
i Word64
crumb = do
let !j :: Int
j = Int -> Int
forall a. Bits a => a -> a
div32 Int
i
let !k :: Int
k = Int -> Int
forall a. (Bits a, Num a) => a -> a
mod32 Int
i
Word64
w64 <- MutablePrimArray (PrimState (ST s)) Word64 -> Int -> ST s Word64
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
P.readPrimArray MutablePrimArray s Word64
MutablePrimArray (PrimState (ST s)) Word64
arr Int
j
let w64' :: Word64
w64' = Word64
w64 Word64 -> Word64 -> Word64
forall a. Bits a => a -> a -> a
.|. Word64 -> Int -> Word64
forall a. Bits a => a -> Int -> a
unsafeShiftL Word64
crumb (Int -> Int
forall a. Bits a => a -> a
mul2 Int
k)
MutablePrimArray (PrimState (ST s)) Word64
-> Int -> Word64 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> a -> m ()
P.writePrimArray MutablePrimArray s Word64
MutablePrimArray (PrimState (ST s)) Word64
arr Int
j (Word64 -> ST s ()) -> Word64 -> ST s ()
forall a b. (a -> b) -> a -> b
$! Word64
w64'
serialisePageAcc :: PageAcc s -> ST s RawPage
serialisePageAcc :: forall s. PageAcc s -> ST s RawPage
serialisePageAcc page :: PageAcc s
page@PageAcc {MutablePrimArray s Int
MutablePrimArray s Word32
MutablePrimArray s Word64
MVector s SerialisedValue
MVector s SerialisedKey
paDir :: forall s. PageAcc s -> MutablePrimArray s Int
paOpMap :: forall s. PageAcc s -> MutablePrimArray s Word64
paBlobRefsMap :: forall s. PageAcc s -> MutablePrimArray s Word64
paBlobRefs1 :: forall s. PageAcc s -> MutablePrimArray s Word64
paBlobRefs2 :: forall s. PageAcc s -> MutablePrimArray s Word32
paKeys :: forall s. PageAcc s -> MVector s SerialisedKey
paValues :: forall s. PageAcc s -> MVector s SerialisedValue
paDir :: MutablePrimArray s Int
paOpMap :: MutablePrimArray s Word64
paBlobRefsMap :: MutablePrimArray s Word64
paBlobRefs1 :: MutablePrimArray s Word64
paBlobRefs2 :: MutablePrimArray s Word32
paKeys :: MVector s SerialisedKey
paValues :: MVector s SerialisedValue
..} = do
Int
size <- MutablePrimArray (PrimState (ST s)) Int -> Int -> ST s Int
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
P.readPrimArray MutablePrimArray s Int
MutablePrimArray (PrimState (ST s)) Int
paDir Int
keysCountIdx
case Int
size of
Int
0 -> RawPage -> ST s RawPage
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return RawPage
emptyRawPage
Int
_ -> Int -> PageAcc s -> ST s RawPage
forall s. Int -> PageAcc s -> ST s RawPage
serialisePageAccN Int
size PageAcc s
page
serialisePageAccN :: forall s. Int -> PageAcc s -> ST s RawPage
serialisePageAccN :: forall s. Int -> PageAcc s -> ST s RawPage
serialisePageAccN Int
size PageAcc {MutablePrimArray s Int
MutablePrimArray s Word32
MutablePrimArray s Word64
MVector s SerialisedValue
MVector s SerialisedKey
paDir :: forall s. PageAcc s -> MutablePrimArray s Int
paOpMap :: forall s. PageAcc s -> MutablePrimArray s Word64
paBlobRefsMap :: forall s. PageAcc s -> MutablePrimArray s Word64
paBlobRefs1 :: forall s. PageAcc s -> MutablePrimArray s Word64
paBlobRefs2 :: forall s. PageAcc s -> MutablePrimArray s Word32
paKeys :: forall s. PageAcc s -> MVector s SerialisedKey
paValues :: forall s. PageAcc s -> MVector s SerialisedValue
paDir :: MutablePrimArray s Int
paOpMap :: MutablePrimArray s Word64
paBlobRefsMap :: MutablePrimArray s Word64
paBlobRefs1 :: MutablePrimArray s Word64
paBlobRefs2 :: MutablePrimArray s Word32
paKeys :: MVector s SerialisedKey
paValues :: MVector s SerialisedValue
..} = do
Int
b <- MutablePrimArray (PrimState (ST s)) Int -> Int -> ST s Int
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
P.readPrimArray MutablePrimArray s Int
MutablePrimArray (PrimState (ST s)) Int
paDir Int
blobRefCountIdx
Int
ks <- MutablePrimArray (PrimState (ST s)) Int -> Int -> ST s Int
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
P.readPrimArray MutablePrimArray s Int
MutablePrimArray (PrimState (ST s)) Int
paDir Int
keysSizeIdx
let ko0 :: Int
!ko0 :: Int
ko0 = Int
8
Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
forall a. Bits a => a -> a
mul8 (Int -> Int
forall a. (Bits a, Num a) => a -> a
ceilDiv64 Int
size Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
forall a. (Bits a, Num a) => a -> a
ceilDiv64 (Int -> Int
forall a. Bits a => a -> a
mul2 Int
size))
Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
forall a. Bits a => a -> a
mul8 Int
b Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
forall a. Bits a => a -> a
mul4 Int
b
let vo0 :: Int
!vo0 :: Int
vo0 = Int
ko0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
forall a. Bits a => a -> a
mul2 Int
size
let kd0 :: Int
!kd0 :: Int
kd0 = Int
vo0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ if Int
size Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 then Int
6 else Int -> Int
forall a. Bits a => a -> a
mul2 (Int
size Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
let vd0 :: Int
!vd0 :: Int
vd0 = Int
kd0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
ks
MutableByteArray s
ba <- Int -> ST s (MutableByteArray (PrimState (ST s)))
forall (m :: * -> *).
PrimMonad m =>
Int -> m (MutableByteArray (PrimState m))
P.newByteArray Int
pageSize :: ST s (P.MutableByteArray s)
MutableByteArray (PrimState (ST s))
-> Int -> Int -> Word8 -> ST s ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> Int -> Int -> Word8 -> m ()
P.fillByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
ba Int
0 Int
pageSize Word8
0
MutableByteArray (PrimState (ST s)) -> Int -> Word16 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
P.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
ba Int
0 (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
size :: Word16)
MutableByteArray (PrimState (ST s)) -> Int -> Word16 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
P.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
ba Int
1 (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
b :: Word16)
MutableByteArray (PrimState (ST s)) -> Int -> Word16 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
P.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
ba Int
2 (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ko0 :: Word16)
let !blobRefMapSize :: Int
blobRefMapSize = Int -> Int
forall a. Bits a => a -> a
mul8 (Int -> Int
forall a. (Bits a, Num a) => a -> a
ceilDiv64 Int
size)
let !opMapSize :: Int
opMapSize = Int -> Int
forall a. Bits a => a -> a
mul8 (Int -> Int
forall a. (Bits a, Num a) => a -> a
ceilDiv64 (Int -> Int
forall a. Bits a => a -> a
mul2 Int
size))
MutableByteArray (PrimState (ST s))
-> Int
-> MutableByteArray (PrimState (ST s))
-> Int
-> Int
-> ST s ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> MutableByteArray (PrimState m) -> Int -> Int -> m ()
P.copyMutableByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
ba Int
8 (MutablePrimArray s Word64 -> MutableByteArray s
forall s a. MutablePrimArray s a -> MutableByteArray s
primToByte MutablePrimArray s Word64
paBlobRefsMap) Int
0 Int
blobRefMapSize
MutableByteArray (PrimState (ST s))
-> Int
-> MutableByteArray (PrimState (ST s))
-> Int
-> Int
-> ST s ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> MutableByteArray (PrimState m) -> Int -> Int -> m ()
P.copyMutableByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
ba (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
blobRefMapSize) (MutablePrimArray s Word64 -> MutableByteArray s
forall s a. MutablePrimArray s a -> MutableByteArray s
primToByte MutablePrimArray s Word64
paOpMap) Int
0 Int
opMapSize
MutableByteArray (PrimState (ST s))
-> Int
-> MutableByteArray (PrimState (ST s))
-> Int
-> Int
-> ST s ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> MutableByteArray (PrimState m) -> Int -> Int -> m ()
P.copyMutableByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
ba (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
blobRefMapSize Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
opMapSize) (MutablePrimArray s Word64 -> MutableByteArray s
forall s a. MutablePrimArray s a -> MutableByteArray s
primToByte MutablePrimArray s Word64
paBlobRefs1) Int
0 (Int -> Int
forall a. Bits a => a -> a
mul8 Int
b)
MutableByteArray (PrimState (ST s))
-> Int
-> MutableByteArray (PrimState (ST s))
-> Int
-> Int
-> ST s ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> MutableByteArray (PrimState m) -> Int -> Int -> m ()
P.copyMutableByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
ba (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
blobRefMapSize Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
opMapSize Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
forall a. Bits a => a -> a
mul8 Int
b) (MutablePrimArray s Word32 -> MutableByteArray s
forall s a. MutablePrimArray s a -> MutableByteArray s
primToByte MutablePrimArray s Word32
paBlobRefs2) Int
0 (Int -> Int
forall a. Bits a => a -> a
mul4 Int
b)
let loop :: Int -> Int -> Int -> Int -> Int -> ST s ()
loop :: Int -> Int -> Int -> Int -> Int -> ST s ()
loop !Int
i !Int
ko !Int
vo !Int
kd !Int
vd
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
size = do
MutableByteArray (PrimState (ST s)) -> Int -> Word16 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
P.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
ba (Int -> Int
forall a. Bits a => a -> a
div2 Int
vo) (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
vd :: Word16)
| Bool
otherwise = do
SerialisedKey (RawBytes (VP.Vector Int
koff Int
klen ByteArray
kba)) <- MVector (PrimState (ST s)) SerialisedKey
-> Int -> ST s SerialisedKey
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> m a
VM.read MVector s SerialisedKey
MVector (PrimState (ST s)) SerialisedKey
paKeys Int
i
SerialisedValue (RawBytes (VP.Vector Int
voff Int
vlen ByteArray
vba)) <- MVector (PrimState (ST s)) SerialisedValue
-> Int -> ST s SerialisedValue
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> m a
VM.read MVector s SerialisedValue
MVector (PrimState (ST s)) SerialisedValue
paValues Int
i
MutableByteArray (PrimState (ST s)) -> Int -> Word16 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
P.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
ba (Int -> Int
forall a. Bits a => a -> a
div2 Int
ko) (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
kd :: Word16)
MutableByteArray (PrimState (ST s)) -> Int -> Word16 -> ST s ()
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutableByteArray (PrimState m) -> Int -> a -> m ()
P.writeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
ba (Int -> Int
forall a. Bits a => a -> a
div2 Int
vo) (Int -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
vd :: Word16)
MutableByteArray (PrimState (ST s))
-> Int -> ByteArray -> Int -> Int -> ST s ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
P.copyByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
ba Int
kd ByteArray
kba Int
koff Int
klen
MutableByteArray (PrimState (ST s))
-> Int -> ByteArray -> Int -> Int -> ST s ()
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m)
-> Int -> ByteArray -> Int -> Int -> m ()
P.copyByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
ba Int
vd ByteArray
vba Int
voff Int
vlen
Int -> Int -> Int -> Int -> Int -> ST s ()
loop (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Int
ko Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) (Int
vo Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) (Int
kd Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
klen) (Int
vd Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
vlen)
Int -> Int -> Int -> Int -> Int -> ST s ()
loop Int
0 Int
ko0 Int
vo0 Int
kd0 Int
vd0
ByteArray
ba' <- MutableByteArray (PrimState (ST s)) -> ST s ByteArray
forall (m :: * -> *).
PrimMonad m =>
MutableByteArray (PrimState m) -> m ByteArray
P.unsafeFreezeByteArray MutableByteArray s
MutableByteArray (PrimState (ST s))
ba
RawPage -> ST s RawPage
forall a. a -> ST s a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteArray -> Int -> RawPage
makeRawPage ByteArray
ba' Int
0)
keysCountPageAcc :: PageAcc s -> ST s Int
keysCountPageAcc :: forall s. PageAcc s -> ST s Int
keysCountPageAcc PageAcc {MutablePrimArray s Int
paDir :: forall s. PageAcc s -> MutablePrimArray s Int
paDir :: MutablePrimArray s Int
paDir} = MutablePrimArray (PrimState (ST s)) Int -> Int -> ST s Int
forall a (m :: * -> *).
(Prim a, PrimMonad m) =>
MutablePrimArray (PrimState m) a -> Int -> m a
P.readPrimArray MutablePrimArray s Int
MutablePrimArray (PrimState (ST s)) Int
paDir Int
keysCountIdx
indexKeyPageAcc :: PageAcc s -> Int -> ST s SerialisedKey
indexKeyPageAcc :: forall s. PageAcc s -> Int -> ST s SerialisedKey
indexKeyPageAcc PageAcc {MVector s SerialisedKey
paKeys :: forall s. PageAcc s -> MVector s SerialisedKey
paKeys :: MVector s SerialisedKey
paKeys} Int
ix = MVector (PrimState (ST s)) SerialisedKey
-> Int -> ST s SerialisedKey
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> m a
VM.read MVector s SerialisedKey
MVector (PrimState (ST s)) SerialisedKey
paKeys Int
ix
primToByte :: P.MutablePrimArray s a -> P.MutableByteArray s
primToByte :: forall s a. MutablePrimArray s a -> MutableByteArray s
primToByte (P.MutablePrimArray MutableByteArray# s
ba) = MutableByteArray# s -> MutableByteArray s
forall s. MutableByteArray# s -> MutableByteArray s
P.MutableByteArray MutableByteArray# s
ba