Copyright | (c) 2023-2025 Cardano Development Foundation |
---|---|
License | Apache-2.0 |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | GHC2021 |
Database.LSMTree.Simple
Description
Synopsis
- data Session
- withOpenSession :: forall a. FilePath -> (Session -> IO a) -> IO a
- openSession :: FilePath -> IO Session
- closeSession :: Session -> IO ()
- data Table k v
- withTable :: forall k v a. Session -> (Table k v -> IO a) -> IO a
- withTableWith :: forall k v a. TableConfig -> Session -> (Table k v -> IO a) -> IO a
- newTable :: forall k v. Session -> IO (Table k v)
- newTableWith :: forall k v. TableConfig -> Session -> IO (Table k v)
- closeTable :: forall k v. Table k v -> IO ()
- member :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> k -> IO Bool
- members :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> Vector k -> IO (Vector Bool)
- lookup :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> k -> IO (Maybe v)
- lookups :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> Vector k -> IO (Vector (Maybe v))
- rangeLookup :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> Range k -> IO (Vector (k, v))
- insert :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> k -> v -> IO ()
- inserts :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> Vector (k, v) -> IO ()
- delete :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> k -> IO ()
- deletes :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> Vector k -> IO ()
- update :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> k -> Maybe v -> IO ()
- updates :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> Vector (k, Maybe v) -> IO ()
- withDuplicate :: forall k v a. Table k v -> (Table k v -> IO a) -> IO a
- duplicate :: forall k v. Table k v -> IO (Table k v)
- withUnion :: forall k v a. Table k v -> Table k v -> (Table k v -> IO a) -> IO a
- withUnions :: forall k v a. NonEmpty (Table k v) -> (Table k v -> IO a) -> IO a
- union :: forall k v. Table k v -> Table k v -> IO (Table k v)
- unions :: forall k v. NonEmpty (Table k v) -> IO (Table k v)
- withIncrementalUnion :: forall k v a. Table k v -> Table k v -> (Table k v -> IO a) -> IO a
- withIncrementalUnions :: forall k v a. NonEmpty (Table k v) -> (Table k v -> IO a) -> IO a
- incrementalUnion :: forall k v. Table k v -> Table k v -> IO (Table k v)
- incrementalUnions :: forall k v. NonEmpty (Table k v) -> IO (Table k v)
- remainingUnionDebt :: forall k v. Table k v -> IO UnionDebt
- supplyUnionCredits :: forall k v. Table k v -> UnionCredits -> IO UnionCredits
- data Cursor k v
- withCursor :: forall k v a. Table k v -> (Cursor k v -> IO a) -> IO a
- withCursorAtOffset :: forall k v a. SerialiseKey k => Table k v -> k -> (Cursor k v -> IO a) -> IO a
- newCursor :: forall k v. Table k v -> IO (Cursor k v)
- newCursorAtOffset :: forall k v. SerialiseKey k => Table k v -> k -> IO (Cursor k v)
- closeCursor :: forall k v. Cursor k v -> IO ()
- next :: forall k v. (SerialiseKey k, SerialiseValue v) => Cursor k v -> IO (Maybe (k, v))
- take :: forall k v. (SerialiseKey k, SerialiseValue v) => Int -> Cursor k v -> IO (Vector (k, v))
- takeWhile :: forall k v. (SerialiseKey k, SerialiseValue v) => Int -> (k -> Bool) -> Cursor k v -> IO (Vector (k, v))
- saveSnapshot :: forall k v. SnapshotName -> SnapshotLabel -> Table k v -> IO ()
- withTableFromSnapshot :: forall k v a. Session -> SnapshotName -> SnapshotLabel -> (Table k v -> IO a) -> IO a
- withTableFromSnapshotWith :: forall k v a. TableConfigOverride -> Session -> SnapshotName -> SnapshotLabel -> (Table k v -> IO a) -> IO a
- openTableFromSnapshot :: forall k v. Session -> SnapshotName -> SnapshotLabel -> IO (Table k v)
- openTableFromSnapshotWith :: forall k v. TableConfigOverride -> Session -> SnapshotName -> SnapshotLabel -> IO (Table k v)
- doesSnapshotExist :: Session -> SnapshotName -> IO Bool
- deleteSnapshot :: Session -> SnapshotName -> IO ()
- listSnapshots :: Session -> IO [SnapshotName]
- data SnapshotName
- isValidSnapshotName :: String -> Bool
- toSnapshotName :: String -> SnapshotName
- newtype SnapshotLabel = SnapshotLabel Text
- data TableConfig
- data MergePolicy = LazyLevelling
- data SizeRatio = Four
- data WriteBufferAlloc = AllocNumEntries !Int
- data BloomFilterAlloc
- data FencePointerIndexType
- data DiskCachePolicy
- data MergeSchedule
- newtype MergeBatchSize = MergeBatchSize Int
- data TableConfigOverride = TableConfigOverride {}
- noTableConfigOverride :: TableConfigOverride
- data Range k
- = FromToExcluding k k
- | FromToIncluding k k
- newtype UnionCredits = UnionCredits Int
- newtype UnionDebt = UnionDebt Int
- newtype RawBytes = RawBytes (Vector Word8)
- class SerialiseKey k where
- serialiseKey :: k -> RawBytes
- deserialiseKey :: RawBytes -> k
- class SerialiseKey k => SerialiseKeyOrderPreserving k
- class SerialiseValue v where
- serialiseValue :: v -> RawBytes
- deserialiseValue :: RawBytes -> v
- serialiseKeyIdentity :: (Eq k, SerialiseKey k) => k -> Bool
- serialiseKeyIdentityUpToSlicing :: (Eq k, SerialiseKey k) => RawBytes -> k -> RawBytes -> Bool
- serialiseKeyPreservesOrdering :: (Ord k, SerialiseKey k) => k -> k -> Bool
- serialiseValueIdentity :: (Eq v, SerialiseValue v) => v -> Bool
- serialiseValueIdentityUpToSlicing :: (Eq v, SerialiseValue v) => RawBytes -> v -> RawBytes -> Bool
- packSlice :: RawBytes -> RawBytes -> RawBytes -> RawBytes
- data SessionDirDoesNotExistError = ErrSessionDirDoesNotExist !FilePath
- data SessionDirLockedError = ErrSessionDirLocked !FilePath
- data SessionDirCorruptedError = ErrSessionDirCorrupted !Text !FilePath
- data SessionClosedError = ErrSessionClosed
- data TableClosedError = ErrTableClosed
- data TableCorruptedError = ErrLookupByteCountDiscrepancy !ByteCount !ByteCount
- data TableTooLargeError = ErrTableTooLarge
- data TableUnionNotCompatibleError
- data SnapshotExistsError = ErrSnapshotExists !SnapshotName
- data SnapshotDoesNotExistError = ErrSnapshotDoesNotExist !SnapshotName
- data SnapshotCorruptedError = ErrSnapshotCorrupted !SnapshotName !FileCorruptedError
- data SnapshotNotCompatibleError = ErrSnapshotWrongLabel !SnapshotName !SnapshotLabel !SnapshotLabel
- data CursorClosedError = ErrCursorClosed
- data InvalidSnapshotNameError = ErrInvalidSnapshotName !String
Example
>>>
:{
runExample $ \session table -> do insert table 0 "Hello" insert table 1 "World" lookup table 0 :} Just (Value "Hello")
Usage Notes
Resource Management
This package uses explicit resource management. The Session
, Table
, and Cursor
handles hold open resources, such as file handles, which must be explicitly released.
Every operation that allocates a resource is paired with another operation to releases
that resource. For each pair of allocate and release operations there is a bracketed
function that combines the two.
To prevent resource and memory leaks due to asynchronous exceptions, it is recommended to use the bracketed functions whenever possible, and otherwise:
- Run functions that allocate and release a resource with asynchronous exceptions masked.
- Ensure that every use allocate operation is followed by the corresponding release
operation even in the presence of asynchronous exceptions, e.g., using
bracket
.
Concurrency
Table handles may be used concurrently from multiple Haskell threads, and doing read operations concurrently may result in improved throughput, as it can take advantage of CPU and I/O parallelism. However, concurrent use of write operations may introduces races. Specifically:
- It is a race to read and write the same table concurrently.
- It is a race to write and write the same table concurrently.
- It is not a race to read and read the same table concurrently.
- It is not a race to read or write separate tables concurrently.
For the purposes of the above rules:
- The read operations are
lookup
,rangeLookup
,duplicate
,union
,saveSnapshot
,newCursor
, and their variants. - The write operations are
insert
,delete
,update
,closeTable
, and their variants.
It is possible to read from a stable view of a table while concurrently writing to
the table by using duplicate
and performing the read operations on the duplicate.
However, this requires that the duplicate
operation happens before the subsequent
writes, as it is a race to duplicate concurrently with any writes.
As this package does not provide any construct for synchronisation or atomic
operations, this ordering of operations must be accomplished by the user through
other means.
A Cursor
creates a stable view of a table and can safely be read while
modifying the original table. However, reading the next
key/value pair from
a cursor locks the view, so concurrent reads on the same cursor block.
This is because next
updates the cursor's current position.
Session handles may be used concurrently from multiple Haskell threads,
but concurrent use of read and write operations may introduce races.
Specifically, it is a race to use listSnapshots
and deleteSnapshots
with the same session handle concurrently.
ACID properties
This text copies liberally from https://en.wikipedia.org/wiki/ACID and related wiki pages.
Atomicity, consistency, isolation, and durability (ACID) are important properties of database transactions. They guarantee data validity despite errors, power failures, and other mishaps. A transaction is a sequence of database operations that satisfy the ACID properties.
lsm-tree
does not support transactions in the typical sense that many relational databases do,
where transactions can be built from smaller components/actions,
e.g., reads and writes of individual cells.
Instead, the public API only exposes functions that individually form a transaction;
there are no smaller building blocks.
An example of such a transaction is updates
.
An lsm-tree
transaction still perform multiple database actions internally,
but transactions themselves are not composable into larger transactions,
so it should be expected that table contents can change between transactions in a concurrent setting.
A consistent view of a table can be created,
so that independent transactions have access to their own version of the database state (see concurrency).
All lsm-tree
transactions are designed for atomicity, consistency, and isolation (ACI),
assuming that users of the library perform proper resource management.
Durability is only guaranteed when saving a snapshot,
which is the only method of stopping and restarting tables.
We currently cannot guarantee consistency in the presence of synchronous and asynchronous exceptions, eventhough major strides were made to make it so. The safest course of action when an internal exception is encountered is to stop and restart: close the session along with all its tables and cursors, reopen the session, and load a previous saved table snapshot.
Sharing
Tables created via duplicate
or union
will initially share as much of their
in-memory and on-disk data as possible with the tables they were created from.
Over time as these related tables are modified, the contents of the tables will
diverge, which means that the tables will share less and less.
Sharing of in-memory data is not preserved by snapshots, but sharing of on-disk
data is partially preserved.
Existing files for runs are shared, but files for ongoing merges are not.
Opening a table from a snapshot (using openTableFromSnapshot
or
withTableFromSnapshot
) is expensive, but creating a snapshot (using
saveSnapshot
) is relatively cheap.
Sessions
A session stores context that is shared by multiple tables.
Each session is associated with one session directory where the files containing table data are stored. Each session locks its session directory. There can only be one active session for each session directory at a time. If a database is must be accessed from multiple parts of a program, one session should be opened and shared between those parts of the program. Session directories cannot be shared between OS processes.
Run an action with access to a session opened from a session directory.
If the session directory is empty, a new session is created. Otherwise, the session directory is restored as an existing session.
If there are no open tables or cursors when the session terminates, then the disk I/O complexity of this operation is \(O(1)\).
Otherwise, closeTable
is called for each open table and closeCursor
is called for each open cursor.
Consequently, the worst-case disk I/O complexity of this operation depends on the merge policy of the open tables in the session.
The following assumes all tables in the session have the same merge policy:
LazyLevelling
- \(O(o \: T \log_T \frac{n}{B})\).
The variable \(o\) refers to the number of open tables and cursors in the session.
This function is exception-safe for both synchronous and asynchronous exceptions.
It is recommended to use this function instead of openSession
and closeSession
.
Throws the following exceptions:
SessionDirDoesNotExistError
- If the session directory does not exist.
SessionDirLockedError
- If the session directory is locked by another process.
SessionDirCorruptedError
- If the session directory is malformed.
Open a session from a session directory.
If the session directory is empty, a new session is created. Otherwise, the session directory is restored as an existing session.
The worst-case disk I/O complexity of this operation is \(O(1)\).
Warning: Sessions hold open resources and must be closed using closeSession
.
Throws the following exceptions:
SessionDirDoesNotExistError
- If the session directory does not exist.
SessionDirLockedError
- If the session directory is locked by another process.
SessionDirCorruptedError
- If the session directory is malformed.
closeSession :: Session -> IO () Source #
Close a session.
If there are no open tables or cursors in the session, then the disk I/O complexity of this operation is \(O(1)\).
Otherwise, closeTable
is called for each open table and closeCursor
is called for each open cursor.
Consequently, the worst-case disk I/O complexity of this operation depends on the merge policy of the tables in the session.
The following assumes all tables in the session have the same merge policy:
LazyLevelling
- \(O(o \: T \log_T \frac{n}{B})\).
The variable \(o\) refers to the number of open tables and cursors in the session.
Closing is idempotent, i.e., closing a closed session does nothing. All other operations on a closed session will throw an exception.
Tables
A table is a handle to an individual LSM-tree key/value store with both in-memory and on-disk parts.
Warning: Tables are ephemeral. Once you close a table, its data is lost forever. To persist tables, use snapshots.
withTable :: forall k v a. Session -> (Table k v -> IO a) -> IO a Source #
Run an action with access to an empty table.
The worst-case disk I/O complexity of this operation depends on the merge policy of the table:
LazyLevelling
- \(O(T \log_T \frac{n}{B})\).
This function is exception-safe for both synchronous and asynchronous exceptions.
It is recommended to use this function instead of newTable
and closeTable
.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
withTableWith :: forall k v a. TableConfig -> Session -> (Table k v -> IO a) -> IO a Source #
Variant of withTable
that accepts table configuration.
newTable :: forall k v. Session -> IO (Table k v) Source #
Create an empty table.
The worst-case disk I/O complexity of this operation is \(O(1)\).
Warning: Tables hold open resources and must be closed using closeTable
.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
newTableWith :: forall k v. TableConfig -> Session -> IO (Table k v) Source #
Variant of newTable
that accepts table configuration.
closeTable :: forall k v. Table k v -> IO () Source #
Close a table.
The worst-case disk I/O complexity of this operation depends on the merge policy of the table:
LazyLevelling
- \(O(T \log_T \frac{n}{B})\).
Closing is idempotent, i.e., closing a closed table does nothing. All other operations on a closed table will throw an exception.
Warning: Tables are ephemeral. Once you close a table, its data is lost forever. To persist tables, use snapshots.
Table Lookups
member :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> k -> IO Bool Source #
Check if the key is a member of the table.
The worst-case disk I/O complexity of this operation depends on the merge policy of the table:
LazyLevelling
- \(O(T \log_T \frac{n}{B})\).
Membership tests can be performed concurrently from multiple Haskell threads.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
TableCorruptedError
- If the table data is corrupted.
members :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> Vector k -> IO (Vector Bool) Source #
Variant of member
for batch membership tests.
The batch of keys corresponds in-order to the batch of results.
The worst-case disk I/O complexity of this operation depends on the merge policy of the table:
LazyLevelling
- \(O(b \: T \log_T \frac{n}{B})\).
The variable \(b\) refers to the length of the input vector.
The following property holds in the absence of races:
members table keys = traverse (member table) keys
lookup :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> k -> IO (Maybe v) Source #
Look up the value associated with a key.
The worst-case disk I/O complexity of this operation depends on the merge policy of the table:
LazyLevelling
- \(O(T \log_T \frac{n}{B})\).
Lookups can be performed concurrently from multiple Haskell threads.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
TableCorruptedError
- If the table data is corrupted.
lookups :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> Vector k -> IO (Vector (Maybe v)) Source #
Variant of lookup
for batch lookups.
The batch of keys corresponds in-order to the batch of results.
The worst-case disk I/O complexity of this operation depends on the merge policy of the table:
LazyLevelling
- \(O(b \: T \log_T \frac{n}{B})\).
The variable \(b\) refers to the length of the input vector.
The following property holds in the absence of races:
lookups table keys = traverse (lookup table) keys
rangeLookup :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> Range k -> IO (Vector (k, v)) Source #
Look up a batch of values associated with keys in the given range.
The worst-case disk I/O complexity of this operation is \(O(T \log_T \frac{n}{B} + \frac{b}{P})\), where the variable \(b\) refers to the length of the output vector.
Range lookups can be performed concurrently from multiple Haskell threads.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
TableCorruptedError
- If the table data is corrupted.
Table Updates
insert :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> k -> v -> IO () Source #
Insert a new key and value in the table. If the key is already present in the table, the associated value is replaced with the given value.
The worst-case disk I/O complexity of this operation depends on the merge policy and the merge schedule of the table:
LazyLevelling
/Incremental
- \(O(\frac{1}{P} \: \log_T \frac{n}{B})\).
LazyLevelling
/OneShot
- \(O(\frac{n}{P})\).
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
inserts :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> Vector (k, v) -> IO () Source #
Variant of insert
for batch insertions.
The worst-case disk I/O complexity of this operation depends on the merge policy and the merge schedule of the table:
LazyLevelling
/Incremental
- \(O(b \: \frac{1}{P} \: \log_T \frac{n}{B})\).
LazyLevelling
/OneShot
- \(O(\frac{b}{P} \log_T \frac{b}{B} + \frac{n}{P})\).
The variable \(b\) refers to the length of the input vector.
The following property holds in the absence of races:
inserts table entries = traverse_ (uncurry $ insert table) entries
delete :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> k -> IO () Source #
Delete a key and its value from the table. If the key is not present in the table, the table is left unchanged.
The worst-case disk I/O complexity of this operation depends on the merge policy and the merge schedule of the table:
LazyLevelling
/Incremental
- \(O(\frac{1}{P} \: \log_T \frac{n}{B})\).
LazyLevelling
/OneShot
- \(O(\frac{n}{P})\).
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
deletes :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> Vector k -> IO () Source #
Variant of delete
for batch deletions.
The worst-case disk I/O complexity of this operation depends on the merge policy and the merge schedule of the table:
LazyLevelling
/Incremental
- \(O(b \: \frac{1}{P} \: \log_T \frac{n}{B})\).
LazyLevelling
/OneShot
- \(O(\frac{b}{P} \log_T \frac{b}{B} + \frac{n}{P})\).
The variable \(b\) refers to the length of the input vector.
The following property holds in the absence of races:
deletes table keys = traverse_ (delete table) keys
update :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> k -> Maybe v -> IO () Source #
Update the value at a specific key:
- If the given value is
Just
, this operation acts asinsert
. - If the given value is
Nothing
, this operation acts asdelete
.
The worst-case disk I/O complexity of this operation depends on the merge policy and the merge schedule of the table:
LazyLevelling
/Incremental
- \(O(\frac{1}{P} \: \log_T \frac{n}{B})\).
LazyLevelling
/OneShot
- \(O(\frac{n}{P})\).
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
updates :: forall k v. (SerialiseKey k, SerialiseValue v) => Table k v -> Vector (k, Maybe v) -> IO () Source #
Variant of update
for batch updates.
The worst-case disk I/O complexity of this operation depends on the merge policy and the merge schedule of the table:
LazyLevelling
/Incremental
- \(O(b \: \frac{1}{P} \: \log_T \frac{n}{B})\).
LazyLevelling
/OneShot
- \(O(\frac{b}{P} \log_T \frac{b}{B} + \frac{n}{P})\).
The variable \(b\) refers to the length of the input vector.
The following property holds in the absence of races:
updates table entries = traverse_ (uncurry $ update table) entries
Table Duplication
withDuplicate :: forall k v a. Table k v -> (Table k v -> IO a) -> IO a Source #
Run an action with access to the duplicate of a table.
The duplicate is an independent copy of the given table. The duplicate is unaffected by subsequent updates to the given table and vice versa.
The worst-case disk I/O complexity of this operation depends on the merge policy of the table:
LazyLevelling
- \(O(T \log_T \frac{n}{B})\).
This function is exception-safe for both synchronous and asynchronous exceptions.
It is recommended to use this function instead of duplicate
and closeTable
.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
duplicate :: forall k v. Table k v -> IO (Table k v) Source #
Duplicate a table.
The duplicate is an independent copy of the given table. The duplicate is unaffected by subsequent updates to the given table and vice versa.
The worst-case disk I/O complexity of this operation is \(O(0)\).
Warning: The duplicate must be independently closed using closeTable
.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
Table Unions
withUnion :: forall k v a. Table k v -> Table k v -> (Table k v -> IO a) -> IO a Source #
Run an action with access to a table that contains the union of the entries of the given tables.
The worst-case disk I/O complexity of this operation is \(O(\frac{n}{P})\).
This function is exception-safe for both synchronous and asynchronous exceptions.
It is recommended to use this function instead of union
and closeTable
.
Warning: Both input tables must be from the same Session
.
Warning: This is a relatively expensive operation that may take some time to complete.
See withIncrementalUnion
for an incremental alternative.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
TableUnionNotCompatibleError
- If both tables are not from the same
Session
.
withUnions :: forall k v a. NonEmpty (Table k v) -> (Table k v -> IO a) -> IO a Source #
Variant of withUnions
that takes any number of tables.
union :: forall k v. Table k v -> Table k v -> IO (Table k v) Source #
Create a table that contains the left-biased union of the entries of the given tables.
The worst-case disk I/O complexity of this operation is \(O(\frac{n}{P})\).
Warning: The new table must be independently closed using closeTable
.
Warning: Both input tables must be from the same Session
.
Warning: This is a relatively expensive operation that may take some time to complete.
See incrementalUnion
for an incremental alternative.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
TableUnionNotCompatibleError
- If both tables are not from the same
Session
.
unions :: forall k v. NonEmpty (Table k v) -> IO (Table k v) Source #
Variant of union
that takes any number of tables.
withIncrementalUnion :: forall k v a. Table k v -> Table k v -> (Table k v -> IO a) -> IO a Source #
Run an action with access to a table that incrementally computes the union of the given tables.
The worst-case disk I/O complexity of this operation depends on the merge policy of the table:
LazyLevelling
- \(O(T \log_T \frac{n}{B})\).
This function is exception-safe for both synchronous and asynchronous exceptions.
It is recommended to use this function instead of incrementalUnion
and closeTable
.
The created table has a union debt which represents the amount of computation that remains. See remainingUnionDebt
.
The union debt can be paid off by supplying union credit which performs an amount of computation proportional to the amount of union credit. See supplyUnionCredits
.
While a table has unresolved union debt, operations may become more expensive by a factor that scales with the number of unresolved unions.
Warning: Both input tables must be from the same Session
.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
TableUnionNotCompatibleError
- If both tables are not from the same
Session
.
withIncrementalUnions :: forall k v a. NonEmpty (Table k v) -> (Table k v -> IO a) -> IO a Source #
Variant of withIncrementalUnion
that takes any number of tables.
The worst-case disk I/O complexity of this operation depends on the merge policy of the table:
LazyLevelling
- \(O(T \log_T \frac{n}{B} + b)\).
The variable \(b\) refers to the number of input tables.
incrementalUnion :: forall k v. Table k v -> Table k v -> IO (Table k v) Source #
Create a table that incrementally computes the union of the given tables.
The worst-case disk I/O complexity of this operation is \(O(1)\).
The created table has a union debt which represents the amount of computation that remains. See remainingUnionDebt
.
The union debt can be paid off by supplying union credit which performs an amount of computation proportional to the amount of union credit. See supplyUnionCredits
.
While a table has unresolved union debt, operations may become more expensive by a factor that scales with the number of unresolved unions.
Warning: The new table must be independently closed using closeTable
.
Warning: Both input tables must be from the same Session
.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
TableUnionNotCompatibleError
- If both tables are not from the same
Session
.
incrementalUnions :: forall k v. NonEmpty (Table k v) -> IO (Table k v) Source #
Variant of incrementalUnion
for any number of tables.
The worst-case disk I/O complexity of this operation is \(O(b)\), where the variable \(b\) refers to the number of input tables.
remainingUnionDebt :: forall k v. Table k v -> IO UnionDebt Source #
Get the amount of remaining union debt. This includes the union debt of any table that was part of the union's input.
The worst-case disk I/O complexity of this operation is \(O(0)\).
supplyUnionCredits :: forall k v. Table k v -> UnionCredits -> IO UnionCredits Source #
Supply the given amount of union credits.
This reduces the union debt by at least the number of supplied union credits.
It is therefore advisable to query remainingUnionDebt
every once in a while to see what the current debt is.
This function returns any surplus of union credits as leftover credits when a union has finished. In particular, if the returned number of credits is positive, then the union is finished.
The worst-case disk I/O complexity of this operation is \(O(\frac{b}{P})\), where the variable \(b\) refers to the amount of credits supplied.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
Cursors
A cursor is a stable read-only iterator for a table.
A cursor iterates over the entries in a table following the order of the serialised keys. After the cursor is created, updates to the referenced table do not affect the cursor.
The name of this type references database cursors, not, e.g., text editor cursors.
withCursor :: forall k v a. Table k v -> (Cursor k v -> IO a) -> IO a Source #
Run an action with access to a cursor.
The worst-case disk I/O complexity of this operation depends on the merge policy of the table:
LazyLevelling
- \(O(T \log_T \frac{n}{B})\).
This function is exception-safe for both synchronous and asynchronous exceptions.
It is recommended to use this function instead of newCursor
and closeCursor
.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
withCursorAtOffset :: forall k v a. SerialiseKey k => Table k v -> k -> (Cursor k v -> IO a) -> IO a Source #
Variant of withCursor
that starts at a given key.
newCursor :: forall k v. Table k v -> IO (Cursor k v) Source #
Create a cursor for the given table.
The worst-case disk I/O complexity of this operation depends on the merge policy of the table:
LazyLevelling
- \(O(T \log_T \frac{n}{B})\).
Warning: Cursors hold open resources and must be closed using closeCursor
.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
newCursorAtOffset :: forall k v. SerialiseKey k => Table k v -> k -> IO (Cursor k v) Source #
Variant of newCursor
that starts at a given key.
closeCursor :: forall k v. Cursor k v -> IO () Source #
Close a cursor.
The worst-case disk I/O complexity of this operation depends on the merge policy of the table:
LazyLevelling
- \(O(T \log_T \frac{n}{B})\).
Closing is idempotent, i.e., closing a closed cursor does nothing. All other operations on a closed cursor will throw an exception.
next :: forall k v. (SerialiseKey k, SerialiseValue v) => Cursor k v -> IO (Maybe (k, v)) Source #
Read the next table entry from the cursor.
The worst-case disk I/O complexity of this operation is \(O(\frac{1}{P})\).
Throws the following exceptions:
SessionClosedError
- If the session is closed.
CursorClosedError
- If the cursor is closed.
take :: forall k v. (SerialiseKey k, SerialiseValue v) => Int -> Cursor k v -> IO (Vector (k, v)) Source #
Read the next batch of table entries from the cursor.
The worst-case disk I/O complexity of this operation is \(O(\frac{b}{P})\), where the variable \(b\) refers to the length of the output vector, which is at most equal to the given number. In practice, the length of the output vector is only less than the given number once the cursor reaches the end of the table.
The following property holds:
take n cursor = catMaybes <$> replicateM n (next cursor)
Throws the following exceptions:
SessionClosedError
- If the session is closed.
CursorClosedError
- If the cursor is closed.
takeWhile :: forall k v. (SerialiseKey k, SerialiseValue v) => Int -> (k -> Bool) -> Cursor k v -> IO (Vector (k, v)) Source #
Variant of take
that accepts an additional predicate to determine whether or not to continue reading.
The worst-case disk I/O complexity of this operation is \(O(\frac{b}{P})\), where the variable \(b\) refers to the length of the output vector, which is at most equal to the given number. In practice, the length of the output vector is only less than the given number when the predicate returns false or the cursor reaches the end of the table.
The following properties hold:
takeWhile n (const True) cursor = take n cursor
takeWhile n (const False) cursor = pure empty
Throws the following exceptions:
SessionClosedError
- If the session is closed.
CursorClosedError
- If the cursor is closed.
Snapshots
saveSnapshot :: forall k v. SnapshotName -> SnapshotLabel -> Table k v -> IO () Source #
Save the current state of the table to disk as a snapshot under the given
snapshot name. This is the only mechanism that persists a table. Each snapshot
must have a unique name, which may be used to restore the table from that snapshot
using openTableFromSnapshot
.
Saving a snapshot does not close the table.
Saving a snapshot is relatively cheap when compared to opening a snapshot. However, it is not so cheap that one should use it after every operation.
The worst-case disk I/O complexity of this operation depends on the merge policy of the table:
LazyLevelling
- \(O(T \log_T \frac{n}{B})\).
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
SnapshotExistsError
- If a snapshot with the same name already exists.
withTableFromSnapshot :: forall k v a. Session -> SnapshotName -> SnapshotLabel -> (Table k v -> IO a) -> IO a Source #
Run an action with access to a table from a snapshot.
The worst-case disk I/O complexity of this operation is \(O(\frac{n}{P})\).
This function is exception-safe for both synchronous and asynchronous exceptions.
It is recommended to use this function instead of openTableFromSnapshot
and closeTable
.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
SnapshotDoesNotExistError
- If no snapshot with the given name exists.
SnapshotCorruptedError
- If the snapshot data is corrupted.
SnapshotNotCompatibleError
- If the snapshot has a different label or is a different table type.
withTableFromSnapshotWith :: forall k v a. TableConfigOverride -> Session -> SnapshotName -> SnapshotLabel -> (Table k v -> IO a) -> IO a Source #
Variant of withTableFromSnapshot
that accepts table configuration overrides.
openTableFromSnapshot :: forall k v. Session -> SnapshotName -> SnapshotLabel -> IO (Table k v) Source #
Open a table from a named snapshot.
The worst-case disk I/O complexity of this operation is \(O(\frac{n}{P})\).
Warning: The new table must be independently closed using closeTable
.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
TableClosedError
- If the table is closed.
SnapshotDoesNotExistError
- If no snapshot with the given name exists.
SnapshotCorruptedError
- If the snapshot data is corrupted.
SnapshotNotCompatibleError
- If the snapshot has a different label or is a different table type.
openTableFromSnapshotWith :: forall k v. TableConfigOverride -> Session -> SnapshotName -> SnapshotLabel -> IO (Table k v) Source #
Variant of openTableFromSnapshot
that accepts table configuration overrides.
doesSnapshotExist :: Session -> SnapshotName -> IO Bool Source #
Check if the named snapshot exists.
The worst-case disk I/O complexity of this operation is \(O(1)\).
Throws the following exceptions:
SessionClosedError
- If the session is closed.
deleteSnapshot :: Session -> SnapshotName -> IO () Source #
Delete the named snapshot.
The worst-case disk I/O complexity of this operation depends on the merge policy of the table:
LazyLevelling
- \(O(T \log_T \frac{n}{B})\).
Throws the following exceptions:
SessionClosedError
- If the session is closed.
SnapshotDoesNotExistError
- If no snapshot with the given name exists.
listSnapshots :: Session -> IO [SnapshotName] Source #
List the names of all snapshots.
The worst-case disk I/O complexity of this operation is \(O(s)\), where the variable \(s\) refers to the number of snapshots in the session.
Throws the following exceptions:
SessionClosedError
- If the session is closed.
data SnapshotName #
Instances
IsString SnapshotName | |
Defined in Database.LSMTree.Internal.Paths Methods fromString :: String -> SnapshotName # | |
Show SnapshotName | |
Defined in Database.LSMTree.Internal.Paths Methods showsPrec :: Int -> SnapshotName -> ShowS # show :: SnapshotName -> String # showList :: [SnapshotName] -> ShowS # | |
Eq SnapshotName | |
Defined in Database.LSMTree.Internal.Paths | |
Ord SnapshotName | |
Defined in Database.LSMTree.Internal.Paths Methods compare :: SnapshotName -> SnapshotName -> Ordering # (<) :: SnapshotName -> SnapshotName -> Bool # (<=) :: SnapshotName -> SnapshotName -> Bool # (>) :: SnapshotName -> SnapshotName -> Bool # (>=) :: SnapshotName -> SnapshotName -> Bool # max :: SnapshotName -> SnapshotName -> SnapshotName # min :: SnapshotName -> SnapshotName -> SnapshotName # |
isValidSnapshotName :: String -> Bool #
toSnapshotName :: String -> SnapshotName #
newtype SnapshotLabel #
Constructors
SnapshotLabel Text |
Instances
IsString SnapshotLabel | |
Defined in Database.LSMTree.Internal.Snapshot Methods fromString :: String -> SnapshotLabel # | |
Show SnapshotLabel | |
Defined in Database.LSMTree.Internal.Snapshot Methods showsPrec :: Int -> SnapshotLabel -> ShowS # show :: SnapshotLabel -> String # showList :: [SnapshotLabel] -> ShowS # | |
NFData SnapshotLabel | |
Defined in Database.LSMTree.Internal.Snapshot Methods rnf :: SnapshotLabel -> () # | |
Eq SnapshotLabel | |
Defined in Database.LSMTree.Internal.Snapshot Methods (==) :: SnapshotLabel -> SnapshotLabel -> Bool # (/=) :: SnapshotLabel -> SnapshotLabel -> Bool # |
Table Configuration
data TableConfig #
Instances
Show TableConfig | |
Defined in Database.LSMTree.Internal.Config Methods showsPrec :: Int -> TableConfig -> ShowS # show :: TableConfig -> String # showList :: [TableConfig] -> ShowS # | |
NFData TableConfig | |
Defined in Database.LSMTree.Internal.Config Methods rnf :: TableConfig -> () # | |
Eq TableConfig | |
Defined in Database.LSMTree.Internal.Config | |
Override DiskCachePolicy TableConfig | |
Defined in Database.LSMTree.Internal.Config.Override Methods override :: DiskCachePolicy -> TableConfig -> TableConfig | |
Override MergeBatchSize TableConfig | |
Defined in Database.LSMTree.Internal.Config.Override Methods override :: MergeBatchSize -> TableConfig -> TableConfig |
data MergePolicy #
Constructors
LazyLevelling |
Instances
Show MergePolicy | |
Defined in Database.LSMTree.Internal.Config Methods showsPrec :: Int -> MergePolicy -> ShowS # show :: MergePolicy -> String # showList :: [MergePolicy] -> ShowS # | |
NFData MergePolicy | |
Defined in Database.LSMTree.Internal.Config Methods rnf :: MergePolicy -> () # | |
Eq MergePolicy | |
Defined in Database.LSMTree.Internal.Config |
Constructors
Four |
data WriteBufferAlloc #
Constructors
AllocNumEntries !Int |
Instances
Show WriteBufferAlloc | |
Defined in Database.LSMTree.Internal.Config Methods showsPrec :: Int -> WriteBufferAlloc -> ShowS # show :: WriteBufferAlloc -> String # showList :: [WriteBufferAlloc] -> ShowS # | |
NFData WriteBufferAlloc | |
Defined in Database.LSMTree.Internal.Config Methods rnf :: WriteBufferAlloc -> () # | |
Eq WriteBufferAlloc | |
Defined in Database.LSMTree.Internal.Config Methods (==) :: WriteBufferAlloc -> WriteBufferAlloc -> Bool # (/=) :: WriteBufferAlloc -> WriteBufferAlloc -> Bool # |
data BloomFilterAlloc #
Constructors
AllocFixed !Double | |
AllocRequestFPR !Double |
Instances
Show BloomFilterAlloc | |
Defined in Database.LSMTree.Internal.Config Methods showsPrec :: Int -> BloomFilterAlloc -> ShowS # show :: BloomFilterAlloc -> String # showList :: [BloomFilterAlloc] -> ShowS # | |
NFData BloomFilterAlloc | |
Defined in Database.LSMTree.Internal.Config Methods rnf :: BloomFilterAlloc -> () # | |
Eq BloomFilterAlloc | |
Defined in Database.LSMTree.Internal.Config Methods (==) :: BloomFilterAlloc -> BloomFilterAlloc -> Bool # (/=) :: BloomFilterAlloc -> BloomFilterAlloc -> Bool # |
data FencePointerIndexType #
Constructors
OrdinaryIndex | |
CompactIndex |
Instances
Show FencePointerIndexType | |
Defined in Database.LSMTree.Internal.Config Methods showsPrec :: Int -> FencePointerIndexType -> ShowS # show :: FencePointerIndexType -> String # showList :: [FencePointerIndexType] -> ShowS # | |
NFData FencePointerIndexType | |
Defined in Database.LSMTree.Internal.Config Methods rnf :: FencePointerIndexType -> () # | |
Eq FencePointerIndexType | |
Defined in Database.LSMTree.Internal.Config Methods (==) :: FencePointerIndexType -> FencePointerIndexType -> Bool # (/=) :: FencePointerIndexType -> FencePointerIndexType -> Bool # |
data DiskCachePolicy #
Constructors
DiskCacheAll | |
DiskCacheLevelOneTo !Int | |
DiskCacheNone |
Instances
Show DiskCachePolicy | |
Defined in Database.LSMTree.Internal.Config Methods showsPrec :: Int -> DiskCachePolicy -> ShowS # show :: DiskCachePolicy -> String # showList :: [DiskCachePolicy] -> ShowS # | |
NFData DiskCachePolicy | |
Defined in Database.LSMTree.Internal.Config Methods rnf :: DiskCachePolicy -> () # | |
Eq DiskCachePolicy | |
Defined in Database.LSMTree.Internal.Config Methods (==) :: DiskCachePolicy -> DiskCachePolicy -> Bool # (/=) :: DiskCachePolicy -> DiskCachePolicy -> Bool # | |
Override DiskCachePolicy TableConfig | |
Defined in Database.LSMTree.Internal.Config.Override Methods override :: DiskCachePolicy -> TableConfig -> TableConfig | |
Override DiskCachePolicy SnapshotMetaData | |
Defined in Database.LSMTree.Internal.Config.Override Methods override :: DiskCachePolicy -> SnapshotMetaData -> SnapshotMetaData | |
Override DiskCachePolicy (SnapLevels SnapshotRun) | |
Defined in Database.LSMTree.Internal.Config.Override Methods override :: DiskCachePolicy -> SnapLevels SnapshotRun -> SnapLevels SnapshotRun |
data MergeSchedule #
Constructors
OneShot | |
Incremental |
Instances
Show MergeSchedule | |
Defined in Database.LSMTree.Internal.Config Methods showsPrec :: Int -> MergeSchedule -> ShowS # show :: MergeSchedule -> String # showList :: [MergeSchedule] -> ShowS # | |
NFData MergeSchedule | |
Defined in Database.LSMTree.Internal.Config Methods rnf :: MergeSchedule -> () # | |
Eq MergeSchedule | |
Defined in Database.LSMTree.Internal.Config Methods (==) :: MergeSchedule -> MergeSchedule -> Bool # (/=) :: MergeSchedule -> MergeSchedule -> Bool # |
newtype MergeBatchSize #
Constructors
MergeBatchSize Int |
Instances
Table Configuration Overrides
data TableConfigOverride #
Constructors
TableConfigOverride | |
Instances
Show TableConfigOverride | |
Defined in Database.LSMTree.Internal.Config.Override Methods showsPrec :: Int -> TableConfigOverride -> ShowS # show :: TableConfigOverride -> String # showList :: [TableConfigOverride] -> ShowS # | |
Eq TableConfigOverride | |
Defined in Database.LSMTree.Internal.Config.Override Methods (==) :: TableConfigOverride -> TableConfigOverride -> Bool # (/=) :: TableConfigOverride -> TableConfigOverride -> Bool # | |
Override TableConfigOverride SnapshotMetaData | |
Defined in Database.LSMTree.Internal.Config.Override Methods override :: TableConfigOverride -> SnapshotMetaData -> SnapshotMetaData |
Ranges
Constructors
FromToExcluding k k | |
FromToIncluding k k |
Union Credit and Debt
newtype UnionCredits #
Constructors
UnionCredits Int |
Instances
Instances
Num UnionDebt | |
Defined in Database.LSMTree.Internal.Unsafe | |
Show UnionDebt | |
Eq UnionDebt | |
Ord UnionDebt | |
Defined in Database.LSMTree.Internal.Unsafe |
Key/Value Serialisation
Instances
IsString RawBytes | |
Defined in Database.LSMTree.Internal.RawBytes Methods fromString :: String -> RawBytes # | |
Monoid RawBytes | |
Semigroup RawBytes | |
IsList RawBytes | |
Show RawBytes | |
Hashable RawBytes | |
Defined in Database.LSMTree.Internal.RawBytes Methods hashSalt64 :: Salt -> RawBytes -> Hash # | |
NFData RawBytes | |
Defined in Database.LSMTree.Internal.RawBytes | |
Eq RawBytes | |
Ord RawBytes | |
Defined in Database.LSMTree.Internal.RawBytes | |
type Item RawBytes | |
Defined in Database.LSMTree.Internal.RawBytes |
class SerialiseKey k where #
Instances
class SerialiseKey k => SerialiseKeyOrderPreserving k #
Instances
class SerialiseValue v where #
Instances
Key/Value Serialisation Property Tests
serialiseKeyIdentity :: (Eq k, SerialiseKey k) => k -> Bool #
serialiseKeyIdentityUpToSlicing :: (Eq k, SerialiseKey k) => RawBytes -> k -> RawBytes -> Bool #
serialiseKeyPreservesOrdering :: (Ord k, SerialiseKey k) => k -> k -> Bool #
serialiseValueIdentity :: (Eq v, SerialiseValue v) => v -> Bool #
serialiseValueIdentityUpToSlicing :: (Eq v, SerialiseValue v) => RawBytes -> v -> RawBytes -> Bool #
Errors
data SessionDirDoesNotExistError Source #
The session directory does not exist.
Constructors
ErrSessionDirDoesNotExist !FilePath |
Instances
Exception SessionDirDoesNotExistError Source # | |
Defined in Database.LSMTree.Simple | |
Show SessionDirDoesNotExistError Source # | |
Defined in Database.LSMTree.Simple Methods showsPrec :: Int -> SessionDirDoesNotExistError -> ShowS # show :: SessionDirDoesNotExistError -> String # showList :: [SessionDirDoesNotExistError] -> ShowS # | |
Eq SessionDirDoesNotExistError Source # | |
Defined in Database.LSMTree.Simple Methods (==) :: SessionDirDoesNotExistError -> SessionDirDoesNotExistError -> Bool # (/=) :: SessionDirDoesNotExistError -> SessionDirDoesNotExistError -> Bool # |
data SessionDirLockedError Source #
The session directory is locked by another active session.
Constructors
ErrSessionDirLocked !FilePath |
Instances
Exception SessionDirLockedError Source # | |
Defined in Database.LSMTree.Simple | |
Show SessionDirLockedError Source # | |
Defined in Database.LSMTree.Simple Methods showsPrec :: Int -> SessionDirLockedError -> ShowS # show :: SessionDirLockedError -> String # showList :: [SessionDirLockedError] -> ShowS # | |
Eq SessionDirLockedError Source # | |
Defined in Database.LSMTree.Simple Methods (==) :: SessionDirLockedError -> SessionDirLockedError -> Bool # (/=) :: SessionDirLockedError -> SessionDirLockedError -> Bool # |
data SessionDirCorruptedError Source #
The session directory is corrupted, e.g., it misses required files or contains unexpected files.
Constructors
ErrSessionDirCorrupted !Text !FilePath |
Instances
Exception SessionDirCorruptedError Source # | |
Defined in Database.LSMTree.Simple | |
Show SessionDirCorruptedError Source # | |
Defined in Database.LSMTree.Simple Methods showsPrec :: Int -> SessionDirCorruptedError -> ShowS # show :: SessionDirCorruptedError -> String # showList :: [SessionDirCorruptedError] -> ShowS # | |
Eq SessionDirCorruptedError Source # | |
Defined in Database.LSMTree.Simple Methods (==) :: SessionDirCorruptedError -> SessionDirCorruptedError -> Bool # (/=) :: SessionDirCorruptedError -> SessionDirCorruptedError -> Bool # |
data SessionClosedError #
Constructors
ErrSessionClosed |
Instances
Exception SessionClosedError | |
Defined in Database.LSMTree.Internal.Unsafe Methods toException :: SessionClosedError -> SomeException # fromException :: SomeException -> Maybe SessionClosedError # | |
Show SessionClosedError | |
Defined in Database.LSMTree.Internal.Unsafe Methods showsPrec :: Int -> SessionClosedError -> ShowS # show :: SessionClosedError -> String # showList :: [SessionClosedError] -> ShowS # | |
Eq SessionClosedError | |
Defined in Database.LSMTree.Internal.Unsafe Methods (==) :: SessionClosedError -> SessionClosedError -> Bool # (/=) :: SessionClosedError -> SessionClosedError -> Bool # |
data TableClosedError #
Constructors
ErrTableClosed |
Instances
Exception TableClosedError | |
Defined in Database.LSMTree.Internal.Unsafe Methods toException :: TableClosedError -> SomeException # | |
Show TableClosedError | |
Defined in Database.LSMTree.Internal.Unsafe Methods showsPrec :: Int -> TableClosedError -> ShowS # show :: TableClosedError -> String # showList :: [TableClosedError] -> ShowS # | |
Eq TableClosedError | |
Defined in Database.LSMTree.Internal.Unsafe Methods (==) :: TableClosedError -> TableClosedError -> Bool # (/=) :: TableClosedError -> TableClosedError -> Bool # |
data TableCorruptedError #
Constructors
ErrLookupByteCountDiscrepancy !ByteCount !ByteCount |
Instances
Exception TableCorruptedError | |
Defined in Database.LSMTree.Internal.Lookup Methods toException :: TableCorruptedError -> SomeException # fromException :: SomeException -> Maybe TableCorruptedError # | |
Show TableCorruptedError | |
Defined in Database.LSMTree.Internal.Lookup Methods showsPrec :: Int -> TableCorruptedError -> ShowS # show :: TableCorruptedError -> String # showList :: [TableCorruptedError] -> ShowS # | |
Eq TableCorruptedError | |
Defined in Database.LSMTree.Internal.Lookup Methods (==) :: TableCorruptedError -> TableCorruptedError -> Bool # (/=) :: TableCorruptedError -> TableCorruptedError -> Bool # |
data TableTooLargeError #
Constructors
ErrTableTooLarge |
Instances
Exception TableTooLargeError | |
Defined in Database.LSMTree.Internal.MergingRun Methods toException :: TableTooLargeError -> SomeException # fromException :: SomeException -> Maybe TableTooLargeError # | |
Show TableTooLargeError | |
Defined in Database.LSMTree.Internal.MergingRun Methods showsPrec :: Int -> TableTooLargeError -> ShowS # show :: TableTooLargeError -> String # showList :: [TableTooLargeError] -> ShowS # | |
Eq TableTooLargeError | |
Defined in Database.LSMTree.Internal.MergingRun Methods (==) :: TableTooLargeError -> TableTooLargeError -> Bool # (/=) :: TableTooLargeError -> TableTooLargeError -> Bool # |
data TableUnionNotCompatibleError Source #
A table union was constructed with two tables that are not compatible.
Instances
Exception TableUnionNotCompatibleError Source # | |
Defined in Database.LSMTree.Simple | |
Show TableUnionNotCompatibleError Source # | |
Defined in Database.LSMTree.Simple Methods showsPrec :: Int -> TableUnionNotCompatibleError -> ShowS # show :: TableUnionNotCompatibleError -> String # showList :: [TableUnionNotCompatibleError] -> ShowS # | |
Eq TableUnionNotCompatibleError Source # | |
Defined in Database.LSMTree.Simple Methods (==) :: TableUnionNotCompatibleError -> TableUnionNotCompatibleError -> Bool # (/=) :: TableUnionNotCompatibleError -> TableUnionNotCompatibleError -> Bool # |
data SnapshotExistsError #
Constructors
ErrSnapshotExists !SnapshotName |
Instances
Exception SnapshotExistsError | |
Defined in Database.LSMTree.Internal.Unsafe Methods toException :: SnapshotExistsError -> SomeException # fromException :: SomeException -> Maybe SnapshotExistsError # | |
Show SnapshotExistsError | |
Defined in Database.LSMTree.Internal.Unsafe Methods showsPrec :: Int -> SnapshotExistsError -> ShowS # show :: SnapshotExistsError -> String # showList :: [SnapshotExistsError] -> ShowS # | |
Eq SnapshotExistsError | |
Defined in Database.LSMTree.Internal.Unsafe Methods (==) :: SnapshotExistsError -> SnapshotExistsError -> Bool # (/=) :: SnapshotExistsError -> SnapshotExistsError -> Bool # |
data SnapshotDoesNotExistError #
Constructors
ErrSnapshotDoesNotExist !SnapshotName |
Instances
Exception SnapshotDoesNotExistError | |
Defined in Database.LSMTree.Internal.Unsafe | |
Show SnapshotDoesNotExistError | |
Defined in Database.LSMTree.Internal.Unsafe Methods showsPrec :: Int -> SnapshotDoesNotExistError -> ShowS # show :: SnapshotDoesNotExistError -> String # showList :: [SnapshotDoesNotExistError] -> ShowS # | |
Eq SnapshotDoesNotExistError | |
Defined in Database.LSMTree.Internal.Unsafe Methods (==) :: SnapshotDoesNotExistError -> SnapshotDoesNotExistError -> Bool # (/=) :: SnapshotDoesNotExistError -> SnapshotDoesNotExistError -> Bool # |
data SnapshotCorruptedError #
Constructors
ErrSnapshotCorrupted !SnapshotName !FileCorruptedError |
Instances
Exception SnapshotCorruptedError | |
Defined in Database.LSMTree.Internal.Unsafe | |
Show SnapshotCorruptedError | |
Defined in Database.LSMTree.Internal.Unsafe Methods showsPrec :: Int -> SnapshotCorruptedError -> ShowS # show :: SnapshotCorruptedError -> String # showList :: [SnapshotCorruptedError] -> ShowS # | |
Eq SnapshotCorruptedError | |
Defined in Database.LSMTree.Internal.Unsafe Methods (==) :: SnapshotCorruptedError -> SnapshotCorruptedError -> Bool # (/=) :: SnapshotCorruptedError -> SnapshotCorruptedError -> Bool # |
data SnapshotNotCompatibleError #
Constructors
ErrSnapshotWrongLabel !SnapshotName !SnapshotLabel !SnapshotLabel |
Instances
Exception SnapshotNotCompatibleError | |
Show SnapshotNotCompatibleError | |
Defined in Database.LSMTree.Internal.Unsafe Methods showsPrec :: Int -> SnapshotNotCompatibleError -> ShowS # show :: SnapshotNotCompatibleError -> String # showList :: [SnapshotNotCompatibleError] -> ShowS # | |
Eq SnapshotNotCompatibleError | |
Defined in Database.LSMTree.Internal.Unsafe Methods (==) :: SnapshotNotCompatibleError -> SnapshotNotCompatibleError -> Bool # (/=) :: SnapshotNotCompatibleError -> SnapshotNotCompatibleError -> Bool # |
data CursorClosedError #
Constructors
ErrCursorClosed |
Instances
Exception CursorClosedError | |
Defined in Database.LSMTree.Internal.Unsafe Methods toException :: CursorClosedError -> SomeException # | |
Show CursorClosedError | |
Defined in Database.LSMTree.Internal.Unsafe Methods showsPrec :: Int -> CursorClosedError -> ShowS # show :: CursorClosedError -> String # showList :: [CursorClosedError] -> ShowS # | |
Eq CursorClosedError | |
Defined in Database.LSMTree.Internal.Unsafe Methods (==) :: CursorClosedError -> CursorClosedError -> Bool # (/=) :: CursorClosedError -> CursorClosedError -> Bool # |
data InvalidSnapshotNameError #
Constructors
ErrInvalidSnapshotName !String |
Instances
Exception InvalidSnapshotNameError | |
Defined in Database.LSMTree.Internal.Paths | |
Show InvalidSnapshotNameError | |
Defined in Database.LSMTree.Internal.Paths Methods showsPrec :: Int -> InvalidSnapshotNameError -> ShowS # show :: InvalidSnapshotNameError -> String # showList :: [InvalidSnapshotNameError] -> ShowS # | |
Eq InvalidSnapshotNameError | |
Defined in Database.LSMTree.Internal.Paths Methods (==) :: InvalidSnapshotNameError -> InvalidSnapshotNameError -> Bool # (/=) :: InvalidSnapshotNameError -> InvalidSnapshotNameError -> Bool # |