module Database.Haskey.Store.Class (
StoreM(..)
, arbitrarySearch
, calculateMaxKeySize
, calculateMaxValueSize
, ZeroEncoded(..)
) where
import Prelude hiding (max, min, pred)
import Control.Applicative (Applicative)
import Control.Monad.Trans
import Control.Monad.Trans.Reader (ReaderT)
import Control.Monad.Trans.State (StateT)
import Data.Binary (Binary(..), Get)
import Data.Proxy
import Data.Typeable (Typeable)
import Data.Word (Word8, Word64)
import qualified Data.Map as M
import Data.BTree.Impure
import Data.BTree.Impure.Structures
import Data.BTree.Primitives
class (Applicative m, Monad m) => StoreM hnd m | m -> hnd where
openHandle :: hnd -> m ()
lockHandle :: hnd -> m ()
releaseHandle :: hnd -> m ()
flushHandle :: hnd -> m ()
closeHandle :: hnd -> m ()
removeHandle :: hnd -> m ()
nodePageSize :: (Key key, Value val)
=> m (Height height -> Node height key val -> PageSize)
maxPageSize :: m PageSize
maxKeySize :: m Word64
maxKeySize = do
f <- nodePageSize
fmax <- maxPageSize
return $ calculateMaxKeySize fmax (f zeroHeight)
maxValueSize :: m Word64
maxValueSize = do
f <- nodePageSize
key <- maxKeySize
fmax <- maxPageSize
return $ calculateMaxValueSize fmax key (f zeroHeight)
getNodePage :: (Key key, Value val)
=> hnd
-> Height height
-> Proxy key
-> Proxy val
-> NodeId height key val
-> m (Node height key val)
putNodePage :: (Key key, Value val)
=> hnd
-> Height height
-> NodeId height key val
-> Node height key val
-> m ()
getOverflow :: (Value val)
=> hnd
-> Proxy val
-> m val
putOverflow :: (Value val)
=> hnd
-> val
-> m ()
listOverflows :: hnd -> m [hnd]
instance StoreM hnd m => StoreM hnd (StateT s m) where
openHandle = lift. openHandle
lockHandle = lift. lockHandle
releaseHandle = lift. releaseHandle
flushHandle = lift. flushHandle
closeHandle = lift. closeHandle
removeHandle = lift. closeHandle
nodePageSize = lift nodePageSize
maxPageSize = lift maxPageSize
maxKeySize = lift maxKeySize
maxValueSize = lift maxValueSize
getNodePage = ((((lift.).).).). getNodePage
putNodePage = (((lift.).).). putNodePage
getOverflow = (lift.). getOverflow
putOverflow = (lift.). putOverflow
listOverflows = lift. listOverflows
instance StoreM hnd m => StoreM hnd (ReaderT s m) where
openHandle = lift. openHandle
lockHandle = lift. lockHandle
releaseHandle = lift. releaseHandle
flushHandle = lift. flushHandle
closeHandle = lift. closeHandle
removeHandle = lift. closeHandle
nodePageSize = lift nodePageSize
maxPageSize = lift maxPageSize
maxKeySize = lift maxKeySize
maxValueSize = lift maxValueSize
getNodePage = ((((lift.).).).). getNodePage
putNodePage = (((lift.).).). putNodePage
getOverflow = (lift.). getOverflow
putOverflow = (lift.). putOverflow
listOverflows = lift. listOverflows
calculateMaxKeySize :: PageSize
-> (Node 'Z ZeroEncoded ZeroEncoded -> PageSize)
-> Word64
calculateMaxKeySize fmax f = arbitrarySearch 2 pred fmax
where
pred n = f (Leaf $ kvs n)
kvs n = M.fromList
[(ZeroEncoded n i, RawValue $ ZeroEncoded n i) | i <- [1..4]]
calculateMaxValueSize :: PageSize
-> Word64
-> (Node 'Z ZeroEncoded ZeroEncoded -> PageSize)
-> Word64
calculateMaxValueSize fmax keySize f = arbitrarySearch 2 pred fmax
where
pred n = f (Leaf $ kvs n)
kvs n = M.fromList
[(ZeroEncoded keySize i, RawValue $ ZeroEncoded n i) | i <- [1..4]]
arbitrarySearch :: (Ord v, Integral n) => n -> (n -> v) -> v -> n
arbitrarySearch start f fmax = go start
where
go n =
let s = f n in
if s == fmax
then n
else if s > fmax
then search (n `quot` 2) n
else go (n*2)
search min max
| max min == 1 = min
| otherwise
=
let c = min + ((max min) `quot` 2)
s = f c in
if s == fmax
then c
else if s > fmax
then search min c
else search c max
data ZeroEncoded = ZeroEncoded { getZeroEncoded :: Word64
, getZeroEncodedValue :: Word64 }
deriving (Eq, Ord, Show, Typeable)
instance Binary ZeroEncoded where
put (ZeroEncoded 0 _) = error "must be >0"
put (ZeroEncoded 1 0) = put (255 :: Word8)
put (ZeroEncoded 1 _) = error "value too large"
put (ZeroEncoded n v) = put byte >> put (ZeroEncoded (n1) v')
where
byte = fromIntegral $ v `rem` 255 :: Word8
v' = v `quot` 255
get = do
byte <- get :: Get Word8
case byte of
0 -> return (ZeroEncoded 1 0)
_ -> do
next <- get
return $ ZeroEncoded (getZeroEncoded next + 1) 0
instance Key ZeroEncoded where
instance Value ZeroEncoded where