module Data.BTree.Primitives.Ids where
import Data.BTree.Primitives.Height
import Data.BTree.Primitives.Key
import Data.BTree.Primitives.Value
import Data.Binary (Binary)
import Data.Hashable (Hashable)
import Data.Typeable (Typeable)
import Data.Word
import Numeric (showHex)
newtype PageId = PageId { fromPageId :: Word64 }
deriving (Eq, Ord, Binary, Num, Value, Key, Typeable)
type OverflowId = (TxId, Word32)
newtype PageCount = PageCount { fromPageCount :: Word64 }
deriving (Eq, Ord, Binary, Num, Enum, Typeable)
newtype PageSize = PageSize { fromPageSize :: Word32 }
deriving (Eq, Ord, Show, Binary, Num, Enum, Real, Integral, Typeable)
newtype NodeId (height :: Nat) key val = NodeId { fromNodeId :: Word64 }
deriving (Eq, Ord, Binary, Num)
nodeIdToPageId :: NodeId height key val -> PageId
nodeIdToPageId = PageId . fromNodeId
pageIdToNodeId :: PageId -> NodeId height key val
pageIdToNodeId = NodeId . fromPageId
newtype TxId = TxId { fromTxId :: Word64 }
deriving (Eq, Ord, Binary, Num, Hashable, Value, Key, Typeable)
instance Show PageId where
showsPrec _ (PageId n) = showString "0x" . showHex n
instance Show PageCount where
showsPrec _ (PageCount n) = showString "0x" . showHex n
instance Show (NodeId height key val) where
showsPrec _ (NodeId n) = showString "0x" . showHex n
instance Show TxId where
showsPrec _ (TxId n) = showString "0x" . showHex n