module Data.BTree.Primitives.Index where
import Control.Applicative ((<$>))
import Control.Monad.Identity (runIdentity)
import Data.Binary (Binary(..), Put)
import Data.Bits ((.|.), shiftL, shiftR)
import Data.Foldable (Foldable)
import Data.Monoid
import Data.Traversable (Traversable)
import Data.Vector (Vector)
import Data.Word (Word8, Word32)
import qualified Data.Map as M
import qualified Data.Vector as V
import Data.BTree.Primitives.Exception
import Data.BTree.Utils.List (safeLast)
import Data.BTree.Utils.Vector (isStrictlyIncreasing, vecUncons, vecUnsnoc)
data Index key node = Index !(Vector key) !(Vector node)
deriving (Eq, Functor, Foldable, Show, Traversable)
instance (Binary k, Binary n) => Binary (Index k n) where
put (Index keys nodes) = do
encodeSize $ fromIntegral (V.length keys)
V.mapM_ put keys
V.mapM_ put nodes
where
encodeSize :: Word32 -> Put
encodeSize s = put msb1 >> put msb2 >> put msb3
where
msb1 = fromIntegral $ s `shiftR` 16 :: Word8
msb2 = fromIntegral $ s `shiftR` 8 :: Word8
msb3 = fromIntegral s :: Word8
get = do
numKeys <- decodeSize <$> get
keys <- V.replicateM (fromIntegral numKeys) get
values <- V.replicateM (fromIntegral numKeys + 1) get
return $ Index keys values
where
decodeSize :: (Word8, Word8, Word8) -> Word32
decodeSize (msb1, msb2, msb3) = msb1' .|. msb2' .|. msb3'
where
msb1' = (fromIntegral msb1 :: Word32) `shiftL` 16
msb2' = (fromIntegral msb2 :: Word32) `shiftL` 8
msb3' = fromIntegral msb3 :: Word32
indexNumKeys :: Index key val -> Int
indexNumKeys (Index keys _vals) = V.length keys
indexNumVals :: Index key val -> Int
indexNumVals (Index _keys vals) = V.length vals
validIndex :: Ord key => Index key node -> Bool
validIndex (Index keys nodes) =
V.length keys + 1 == V.length nodes &&
isStrictlyIncreasing keys
validIndexSize :: Ord key => Int -> Int -> Index key node -> Bool
validIndexSize minIdxKeys maxIdxKeys idx@(Index keys _) =
validIndex idx && V.length keys >= minIdxKeys && V.length keys <= maxIdxKeys
splitIndexAt :: Int -> Index key val -> (Index key val, key, Index key val)
splitIndexAt numLeftKeys (Index keys vals)
| (leftKeys, middleKeyAndRightKeys) <- V.splitAt numLeftKeys keys
, (leftVals, rightVals) <- V.splitAt (numLeftKeys+1) vals
= case vecUncons middleKeyAndRightKeys of
Just (middleKey,rightKeys) ->
(Index leftKeys leftVals, middleKey, Index rightKeys rightVals)
Nothing -> throw $
TreeAlgorithmError "splitIndex" "cannot split an empty index"
extendedIndex :: Int -> (Index k b -> a) -> Index k b -> Index k a
extendedIndex maxIdxKeys f = go
where
maxIdxVals = maxIdxKeys + 1
go index
| numVals <= maxIdxVals
= singletonIndex (f index)
| numVals <= 2*maxIdxVals
= case splitIndexAt (div numVals 2 1) index of
(leftIndex, middleKey, rightIndex) ->
indexFromList [middleKey] [f leftIndex, f rightIndex]
| otherwise
= case splitIndexAt maxIdxKeys index of
(leftIndex, middleKey, rightIndex) ->
mergeIndex (singletonIndex (f leftIndex))
middleKey (go rightIndex)
where
numVals = indexNumVals index
extendIndexPred :: (a -> Bool) ->
(Index k b -> a) -> Index k b -> Maybe (Index k a)
extendIndexPred p f = go
where
go index
| let indexEnc = f index
, p indexEnc
= Just (singletonIndex indexEnc)
| indexNumKeys index <= 2
=
throw KeyTooLargeError
| otherwise
= do
let numKeys = indexNumKeys index
(leftEnc, (middleKey, right)) <- safeLast $
takeWhile (p . fst)
[ (leftEnc, (middleKey, right))
| i <- [1..numKeys2]
, let (left,middleKey,right) = splitIndexAt i index
leftEnc = f left
]
rightEnc <- go right
return $! mergeIndex (singletonIndex leftEnc) middleKey rightEnc
mergeIndex :: Index key val -> key -> Index key val -> Index key val
mergeIndex (Index leftKeys leftVals) middleKey (Index rightKeys rightVals) =
Index
(leftKeys <> V.singleton middleKey <> rightKeys)
(leftVals <> rightVals)
indexFromList :: [key] -> [val] -> Index key val
indexFromList ks vs = Index (V.fromList ks) (V.fromList vs)
singletonIndex :: val -> Index key val
singletonIndex = Index V.empty . V.singleton
fromSingletonIndex :: Index key val -> Maybe val
fromSingletonIndex (Index _keys vals) =
if V.length vals == 1 then Just $! V.unsafeHead vals else Nothing
bindIndex :: Index k a -> (a -> Index k b) -> Index k b
bindIndex idx f = runIdentity $ bindIndexM idx (return . f)
bindIndexM :: (Functor m, Monad m)
=> Index k a
-> (a -> m (Index k b))
-> m (Index k b)
bindIndexM (Index ks vs) f = case vecUncons vs of
Just (v, vtail) -> do
i <- f v
V.foldM' g i (V.zip ks vtail)
where
g acc (k , w) = mergeIndex acc k <$> f w
Nothing ->
throw $ TreeAlgorithmError "bindIndexM" "cannot bind an empty Index"
data IndexCtx key val = IndexCtx
{ indexCtxLeftKeys :: !(Vector key)
, indexCtxRightKeys :: !(Vector key)
, indexCtxLeftVals :: !(Vector val)
, indexCtxRightVals :: !(Vector val)
}
deriving (Functor, Foldable, Show, Traversable)
putVal :: IndexCtx key val -> val -> Index key val
putVal ctx val =
Index
(indexCtxLeftKeys ctx <> indexCtxRightKeys ctx)
(indexCtxLeftVals ctx <> V.singleton val <> indexCtxRightVals ctx)
putIdx :: IndexCtx key val -> Index key val -> Index key val
putIdx ctx (Index keys vals) =
Index
(indexCtxLeftKeys ctx <> keys <> indexCtxRightKeys ctx)
(indexCtxLeftVals ctx <> vals <> indexCtxRightVals ctx)
valView :: Ord key => key -> Index key val -> (IndexCtx key val, val)
valView key (Index keys vals)
| (leftKeys,rightKeys) <- V.span (<=key) keys
, n <- V.length leftKeys
, (leftVals,valAndRightVals) <- V.splitAt n vals
, Just (val,rightVals) <- vecUncons valAndRightVals
= ( IndexCtx
{ indexCtxLeftKeys = leftKeys
, indexCtxRightKeys = rightKeys
, indexCtxLeftVals = leftVals
, indexCtxRightVals = rightVals
},
val
)
| otherwise
= throw $ TreeAlgorithmError "valView" "cannot split an empty index"
valViewMin :: Index key val -> (IndexCtx key val, val)
valViewMin (Index keys vals)
| Just (val, rightVals) <- vecUncons vals
= ( IndexCtx
{ indexCtxLeftKeys = V.empty
, indexCtxRightKeys = keys
, indexCtxLeftVals = V.empty
, indexCtxRightVals = rightVals
},
val
)
| otherwise
= throw $ TreeAlgorithmError "valViewMin" "cannot split an empty index"
valViewMax :: Index key val -> (IndexCtx key val, val)
valViewMax (Index keys vals)
| Just (leftVals, val) <- vecUnsnoc vals
= ( IndexCtx
{ indexCtxLeftKeys = keys
, indexCtxRightKeys = V.empty
, indexCtxLeftVals = leftVals
, indexCtxRightVals = V.empty
},
val
)
| otherwise
= throw $ TreeAlgorithmError "valViewMax" "cannot split an empty index"
distribute :: Ord k => M.Map k v -> Index k node -> Index k (M.Map k v, node)
distribute kvs (Index keys nodes)
| a <- V.imap rangeTail (Nothing `V.cons` V.map Just keys)
, b <- V.map (uncurry rangeHead) (V.zip (V.map Just keys `V.snoc` Nothing) a)
= Index keys b
where
rangeTail idx Nothing = (kvs, nodes V.! idx)
rangeTail idx (Just key) = (takeWhile' (>= key) kvs, nodes V.! idx)
rangeHead Nothing (tail', node) = (tail', node)
rangeHead (Just key) (tail', node) = (takeWhile' (< key) tail', node)
takeWhile' :: (k -> Bool) -> M.Map k v -> M.Map k v
takeWhile' p = fst . M.partitionWithKey (\k _ -> p k)
leftView :: IndexCtx key val -> Maybe (IndexCtx key val, val, key)
leftView ctx = do
(leftVals, leftVal) <- vecUnsnoc (indexCtxLeftVals ctx)
(leftKeys, leftKey) <- vecUnsnoc (indexCtxLeftKeys ctx)
return (ctx { indexCtxLeftKeys = leftKeys
, indexCtxLeftVals = leftVals
}, leftVal, leftKey)
rightView :: IndexCtx key val -> Maybe (key, val, IndexCtx key val)
rightView ctx = do
(rightVal, rightVals) <- vecUncons (indexCtxRightVals ctx)
(rightKey, rightKeys) <- vecUncons (indexCtxRightKeys ctx)
return (rightKey, rightVal,
ctx { indexCtxRightKeys = rightKeys
, indexCtxRightVals = rightVals
})