Copyright | (c) 2015 Călin Ardelean |
---|---|
License | MIT |
Maintainer | Călin Ardelean <calinucs@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
The internal state of the database.
- module Database.Muesli.Backend.Types
- newtype Handle l = Handle {}
- data DBState l = DBState {
- logDbPath :: DbPath
- dataDbPath :: DbPath
- commitDelay :: Int
- masterState :: MVar (MasterState l)
- dataState :: MVar (DataState l)
- commitSgn :: MVar Bool
- gcState :: MVar GCState
- data MasterState l = MasterState {
- logState :: !l
- topTid :: !TransactionId
- idSupply :: !IdSupply
- keepTrans :: !Bool
- gaps :: !GapsIndex
- logPend :: !PendingIndex
- logComp :: !CompletedIndex
- mainIdx :: !MainIndex
- unqIdx :: !UniqueIndex
- sortIdx :: !SortIndex
- refIdx :: !FilterIndex
- data DataState l = DataState {
- dataHandle :: !(DataHandleOf l)
- dataCache :: !LRUCache
- data GCState
- type MainIndex = IntMap [LogRecord]
- type GapsIndex = Map DocSize [DocAddress]
- type SortIndex = IntMap (IntMap IntSet)
- type FilterIndex = IntMap (IntMap SortIndex)
- type UniqueIndex = IntMap (IntMap Int)
- type PendingIndex = Map TransactionId [(LogRecord, ByteString)]
- type CompletedIndex = Map TransactionId [LogRecord]
- withMasterLock :: MonadIO m => Handle l -> (MasterState l -> IO a) -> m a
- withMaster :: MonadIO m => Handle l -> (MasterState l -> IO (MasterState l, a)) -> m a
- withDataLock :: MonadIO m => Handle l -> (DataState l -> IO a) -> m a
- withData :: MonadIO m => Handle l -> (DataState l -> IO (DataState l, a)) -> m a
- withGC :: MonadIO m => Handle l -> (GCState -> IO (GCState, a)) -> m a
- withCommitSgn :: MonadIO m => Handle l -> (Bool -> IO (Bool, a)) -> m a
- mkNewTransactionId :: MonadIO m => Handle l -> m TransactionId
- mkNewDocumentKey :: MonadIO m => Handle l -> m DocumentKey
- findUnique :: PropertyKey -> UniqueKey -> [(LogRecord, a)] -> Maybe DocumentKey
Documentation
Database state
Handle used for database management operations.
The l
parameter stands for a LogState
backend.
The internal state of the database.
DBState | |
|
data MasterState l Source
Type of the master state, holding all indexes.
When talking about master lock in other parts, we mean taking the
masterState
MVar
.
MasterState | |
|
The state coresponding to the data file.
DataState | |
|
Type for the state of the GC thread used for messaging.
Allocation table
type MainIndex = IntMap [LogRecord] Source
Type of the allocation table of the database.
The key of the IntMap
is the DocumentKey
of the corresponding document.
type GapsIndex = Map DocSize [DocAddress] Source
A map from gap size to a list of addresses where gaps of that size start.
Inverted indexes
type SortIndex = IntMap (IntMap IntSet) Source
Type of the sort index, which an inverted index.
First key is PropertyKey
, second is SortableKey
, and the IntSet
contains all DocumentKey
s for the documents whose fields have the values
specified by the first two keys.
type FilterIndex = IntMap (IntMap SortIndex) Source
Type of the filter index, which is a 2-level nested inverted index.
First key is the PropertyKey
for the filter field, second is the
DocumentKey
of the filter field value, and then an entire SortIndex
containing the ordered subset for all sortable fields.
type UniqueIndex = IntMap (IntMap Int) Source
Type of the unique index, which is a simpler inverted index.
First key is PropertyKey
, second is the UniqueKey
, and then the unique
DocumentKey
corresponding to that UniqueKey
.
Transaction log
type PendingIndex = Map TransactionId [(LogRecord, ByteString)] Source
The type of the pending transaction log.
update
serializes the document before adding it to
transUpdateList
, and later
commitThread
moves it in the pending log.
type CompletedIndex = Map TransactionId [LogRecord] Source
The type of the completed transaction log.
Bracket functions
withMasterLock :: MonadIO m => Handle l -> (MasterState l -> IO a) -> m a Source
Standard bracket
function for the masterState
lock.
withMaster :: MonadIO m => Handle l -> (MasterState l -> IO (MasterState l, a)) -> m a Source
Standard bracket
function for the masterState
lock that also allows
updating the MasterState
.
Utilities
mkNewTransactionId :: MonadIO m => Handle l -> m TransactionId Source
Generates a new TransactionId
by incrementing the topTid
under
master lock.
mkNewDocumentKey :: MonadIO m => Handle l -> m DocumentKey Source
Generates a new DocumentKey
by calling alloc
under master lock.
findUnique :: PropertyKey -> UniqueKey -> [(LogRecord, a)] -> Maybe DocumentKey Source
Utility function for searching into a list of LogRecord
s and into their
recUniques
for a particular UniqueKey
.