Generic thread-safe in-memory transactional
store for dict terms.
- ds_open(+File) is det
- Opens the database file.
Throws
error(docstore_is_open)
when
the database is already open.
- ds_close is det
- Closes the database. Removes in-memory data.
Runs close hooks. Hooks are ran before
the file is closed and data is purged from memory.
Throws
error(database_is_not_open)
when
the database file is not open.
- ds_snapshot(+File) is det
- Writes the current database
snapshot into the file.
- ds_snapshot is det
- Writes the snapshot of
current database contents into
its file. Implemented by running
ds_snapshot/1 into a file (with a random
name) and renaming the file using
rename_file/2.
- ds_hook(+Col, +Action, :Goal) is det
- Adds new save/remove hook.
Action is one of:
before_save
, before_remove
.
before_save hooks are executed before insert
and update. before_remove hooks are executed
before the document removal. During update only
the updated fields are passed to the before_save hooks.
Hooks are run in the current transaction. Hooks that
fail or throw exception will end the transaction
and discard changes.
- ds_insert(Doc) is det
- Same as ds_insert/2 but the generated
ID is ignored.
- ds_insert(+Doc, -Id) is det
- Same as ds_insert/3 but collection
name is taken from dict tag.
- ds_insert(+Col, +Doc, -Id) is det
- Inserts new document into the given collection.
Gives back the generated ID. Document must be a dict.
All values in the dict must be ground.
Throws
error(doc_has_id)
when the document has the
$id key. Runs before_save hooks.
- ds_update(+Doc) is det
- Updates the given document. Only
changed properties are updated.
Throws error if Doc contains no
$id
.
Ignores updates to $id
. Runs
before_save
hooks. Throws error(no_such_doc(Id))
when no document with the given Id exists.
- ds_update(+Id, +Doc) is det
- Updates the given document. The document
id inside the document is ignored.
- ds_upsert(+Doc) is det
- Same as ds_upsert/2 but ignores
the generated id.
- ds_upsert(+Doc, -Id) is det
- Same as ds_upsert/3 but uses dict tag
as collection name when inserting.
- ds_upsert(+Col, +Doc, -Id) is det
- Inserts or updates the given document.
- ds_move(+Col, +Id, +NewCol) is det
- Moves the given document into
the new collection. Throws error
when the document does not exist.
- ds_col_get(+Col, +Id, -Doc) is semidet
- Retrieves entry with the given id.
Fails when the document with the given id
does not exist or is not in the given collection.
- ds_col_get(+Col, +Id, +Keys, -Doc) is semidet
- Retrieves entry with the given id.
Retrieves subset of properties. Fails
when the document with the given id does
not exist or is not in the given collection.
- ds_all(+Col, -List) is det
- Finds list of all documents in the given
collection.
- ds_all(+Col, +Keys, -List) is det
- Finds list of all documents in the given
collection. Retrieves subset of keys. Subset
will always contain '$id'.
- ds_all_ids(+Col, -List) is det
- Retrieves the list of all document
IDs in the collection.
- ds_find(+Col, +Cond, -List) is semidet
- Finds collection entries that
satisfy
condition(s)
. Cond is one of:
Key = Value
, Key \= Value
, Key > Value
,
Key < Value
, Key >= Value
, Key =< Value
,
member(Value, Key)
, (Cond1, Cond2)
, (Cond1 ; Cond2)
.
- ds_find(+Col, +Cond, +Keys, -List) is semidet
- Same as ds_find/3 but retrieves subset of keys.
- ds_collection(?Id, ?Col) is semidet
- Finds which collection the document
belongs to.
- ds_col_remove(+Col, +Id) is det
- Removes the given document.
Does nothing when the document
does not exist. Runs
before_remove
hooks.
- ds_col_remove_cond(+Col, +Cond) is det
- Removes all documents from
the collection that match the
condition. Runs
before_remove
hooks.
Cond expressions are same as in ds_find/3.
- ds_remove_col(Col) is det
- Removes all documents from
the given collection. Is equivalent
of running ds_remove/1 for each document
in the collection. Runs
before_remove
hooks.
- ds_tuples(+Col, +Keys, -Values) is nondet
- Provides backtrackable predicate-like view
of documents. It does not support built-in
indexing and therefore can be slow for purposes
where some values are restricted.
- ds_remove_key(+Id, +Key) is det
- Removes key from the given document.
Does nothing when the document or entry
does not exist.
- ds_col_add_key(+Col, +Key, +Default) is det
- Adds each document new key with the
default value. Runs
before_save
hooks.
- ds_col_remove_key(+Col, +Key) is det
- Removes given key from the document
collection. Throws
error(cannot_remove_id)
when key is $id
. save_before
hooks are
not executed.
- ds_col_rename(+Col, +ColNew) is det
- Rename collection. Relatively expensive
operation in terms of journal space. Needs
entry per document in the collection.
- ds_col_rename_key(+Col, +Key, +KeyNew) is det
- Renames a key in collection. Relatively expensive
operation in terms of journal space. Needs
2 entries per document in the collection. Does
not run hooks.
- ds_transactional(:Goal) is det
- Runs given goal that modifies the database
contents in a transactional mode. When the goal
throws exception or fails, no changes by it
are persisted.
- ds_id(+Doc, -Id) is det
- Extracts document id from the
given document. Equivalent to Doc.'$id'.
- ds_set_id(+In, +Id, -Out) is det
- Sets the document id. Throws error
when the document is not a dict or
id is not an atom.
- ds_uuid(-Id) is det
- Generates UUID version 4 identifier.
More info:
http://en.wikipedia.org/wiki/Universally_unique_identifier