module Database.Haskey.Alloc.Concurrent.Meta where
import Data.Binary (Binary)
import Data.Proxy (Proxy)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Data.BTree.Impure.Structures
import Data.BTree.Primitives
import Database.Haskey.Alloc.Concurrent.Environment
import Database.Haskey.Alloc.Concurrent.FreePages.Tree
import Database.Haskey.Alloc.Concurrent.Overflow
import Database.Haskey.Store
class Value root => Root root where
instance (Key k, Value v) => Root (Tree k v) where
data CurrentMetaPage = Meta1 | Meta2
data ConcurrentMeta root = ConcurrentMeta {
    concurrentMetaRevision :: TxId
  , concurrentMetaDataNumPages :: S 'TypeData PageId
  , concurrentMetaIndexNumPages :: S 'TypeIndex PageId
  , concurrentMetaRoot :: root
  , concurrentMetaDataFreeTree :: S 'TypeData FreeTree
  , concurrentMetaIndexFreeTree :: S 'TypeIndex FreeTree
  , concurrentMetaOverflowTree :: OverflowTree
  , concurrentMetaDataCachedFreePages :: S 'TypeData [FreePage]
  , concurrentMetaIndexCachedFreePages :: S 'TypeIndex [FreePage]
  } deriving (Generic, Typeable)
deriving instance (Show root) => Show (ConcurrentMeta root)
instance (Binary root) => Binary (ConcurrentMeta root) where
class StoreM FilePath m => ConcurrentMetaStoreM m where
    
    putConcurrentMeta :: Root root
                      => FilePath
                      -> ConcurrentMeta root
                      -> m ()
    
    
    readConcurrentMeta :: Root root
                       => FilePath
                       -> Proxy root
                       -> m (Maybe (ConcurrentMeta root))