Did you know ... Search Documentation:
Pack rocksdb -- prolog/rocksdb.pl
PublicShow source

RocksDB is an embeddable persistent key-value store for fast storage. The store can be used only from one process at the same time. It may be used from multiple Prolog threads though. This library provides a SWI-Prolog binding for RocksDB. RocksDB just associates byte arrays. This interface defines several mappings between Prolog datastructures and byte arrays that may be configured to store both keys and values. See rocks_open/3 for details.

See also
- http://rocksdb.org/
 rocks_open(+Directory, -RocksDB, +Options) is det
Open a RocksDB database in Directory and unify RocksDB with a handle to the opened database. Most of the DBOptions in rocksdb/include/rocksdb/options.h are supported, in addition to the following options:
  • alias(+Name) Give the database a name instead of using an anonymous handle. A named database is not subject to GC and must be closed explicitly.
  • open(+How) If How is once and an alias is given, a second open simply returns a handle to the already open database.
  • key(+Type)
  • value(+Type) Define the type for the key and value. This must be consistent over multiple invocations. Defined types are:
    atom
    Accepts an atom or string. Unifies the result with an atom. Data is stored as a UTF-8 string in RocksDB.
    string
    Accepts an atom or string. Unifies the result with a string. Data is stored as a UTF-8 string in RocksDB.
    binary
    Accepts an atom or string with codes in the range 0..255. Unifies the result with a string. Data is stored as a sequence of bytes in RocksDB.
    int32
    Maps to a Prolog integer in the range -2,147,483,648...2,147,483,647. Stored as a 4 bytes in native byte order.
    int64
    Maps to a Prolog integer in the range -9223372036854775808..9223372036854775807 Stored as a 8 bytes in native byte order.
    float
    Value is mapped to a 32-bit floating point number.
    double
    Value is mapped to a 64-bit floating point number (double).
    term
    Stores any Prolog term. Stored using PL_record_external(). The PL_record_external() function serializes the internal structure of a term, including cycles, sharing and attributes. This means that if the key is a term, it only matches if the the same cycles and sharing is used. For example, X = f(a), Key = k(X,X) is a different key from Key = k(f(a),f(a)) and X = [a|X] is a different key from X = [a,a|X]. Applications for which such keys should match must first normalize the key. Normalization can be based on term_factorized/3 from library(terms). In addition, value accepts one of list(type) or set(type), currently only for the numeric types. This causes rocks_put/3 and rocks_get/3 to exchange the value as a list and installs a built-in merge function.
  • merge(:Goal) Define RocksDB value merging. See rocks_merge/3.
  • mode(+Mode) One of read_write (default) or read_only. The latter uses OpenForReadOnly() to open the database.
  • optimize_for_small_db(true) - Use this if your DB is very small (like under 1GB) and you don't want tog spend lots of memory for memtables.
  • increase_parallelism(true) - see DBOptions::IncreaseParallelism()
See also
- https://github.com/facebook/rocksdb/wiki/RocksDB-Tuning-Guide
- http://rocksdb.org/blog/2018/08/01/rocksdb-tuning-advisor.html
- https://github.com/EighteenZi/rocksdb_wiki/blob/master/RocksDB-Tuning-Guide.md
 rocks_close(+RocksDB) is det
Destroy the RocksDB handle. Note that anonymous handles are subject to (atom) garbage collection.
 rocks_put(+RocksDB, +Key, +Value) is det
 rocks_put(+RocksDB, +Key, +Value, Options) is det
Add Key-Value to the RocksDB database. If Key already has a value, the existing value is silently replaced by Value. If the value type is list(Type) or set(Type), Value must be a list. For set(Type) the list is converted into an ordered set.
 rocks_merge(+RocksDB, +Key, +Value) is det
 rocks_merge(+RocksDB, +Key, +Value, +Options) is det
Merge Value with the already existing value for Key. Requires the option merge(:Merger) or the value type to be one of list(Type) or set(Type) to be used when opening the database. Using rocks_merge/3 rather than rocks_get/2, update and rocks_put/3 makes the operation atomic and reduces disk accesses.

Options are the same as for rocks_put/4.

Merger is called as below, where two clauses are required: one with How set to partial and one with How set to full. If full, MergeValue is a list of values that need to be merged, if partial, MergeValue is a single value.

call(:Merger, +How, +Key, +Value0, +MergeValue, -Value)

If Key is not in RocksDB, Value0 is unified with a value that depends on the value type. If the value type is an atom, it is unified with the empty atom; if it is string or binary it is unified with an empty string; if it is int32 or int64 it is unified with the integer 0; and finally if the type is term it is unified with the empty list.

For example, if the value is a set of Prolog values we open the database with value(term) to allow for Prolog lists as value and we define merge_set/5 as below.

merge(partial, _Key, Left, Right, Result) :-
    ord_union(Left, Right, Result).
merge(full, _Key, Initial, Additions, Result) :-
    append([Initial|Additions], List),
    sort(List, Result).

If the merge callback fails or raises an exception the merge operation fails and the error is logged through the RocksDB logging facilities. Note that the merge callback can be called in a different thread or even in a temporary created thread if RocksDB decides to merge remaining values in the background.

Errors
- permission_error(merge, rocksdb RocksDB) if the database was not opened with the merge(Merger) option.
See also
- https://github.com/facebook/rocksdb/wiki/Merge-Operator for understanding the concept of value merging in RocksDB.
 rocks_delete(+RocksDB, +Key) is semidet
 rocks_delete(+RocksDB, +Key, +Options) is semidet
Delete Key from RocksDB. Fails if Key is not in the database.

Options are the same as for rocks_put/4.

 rocks_get(+RocksDB, +Key, -Value) is semidet
 rocks_get(+RocksDB, +Key, -Value, +Options) is semidet
True when Value is the current value associated with Key in RocksDB. If the value type is list(Type) or set(Type) this returns a Prolog list.
 rocks_enum(+RocksDB, -Key, -Value) is nondet
 rocks_enum(+RocksDB, -Key, -Value, +Options) is nondet
True when Value is the current value associated with Key in RocksDB. This enumerates all keys in the database. If the value type is list(Type) or set(Type) Value is a list.

Options are the same as for rocks_get/4.

 rocks_enum_from(+RocksDB, -Key, -Value, +Prefix) is nondet
 rocks_enum_from(+RocksDB, -Key, -Value, +Prefix, +Options) is nondet
As rocks_enum/3, but starts enumerating from Prefix. The key type must be one of atom, string or binary. To only iterate all keys with Prefix, use rocks_enum_prefix/4 or the construct below.

Options are the same as for rocks_get/4.

    rocks_enum_from(DB, Key, Value, Prefix),
    (   sub_atom(Key, 0, _, _, Prefix)
    ->  handle(Key, Value)
    ;   !, fail
    )
 rocks_enum_prefix(+RocksDB, -Suffix, -Value, +Prefix) is nondet
 rocks_enum_prefix(+RocksDB, -Suffix, -Value, +Prefix, +Options) is nondet
True for all keys that start with Prefix. Instead of returning the full key this predicate returns the suffix of the matching key. This predicate succeeds deterministically no next key exists or the next key does not match Prefix.

Options are the same as for rocks_get/4.

 rocks_batch(+RocksDB, +Actions:list) is det
 rocks_batch(+RocksDB, +Actions:list, +Options) is det
Perform a batch of operations on RocksDB as an atomic operation.

Options are the same as for rocks_put/4.

Actions is a list of:

delete(+Key)
As rocks_delete/2.
put(+Key, +Value)
As rocks_put/3.

The following example is translated from the RocksDB documentation:

  rocks_get(RocksDB, key1, Value),
  rocks_batch(RocksDB,
              [ delete(key1),
                put(key2, Value)
              ])
 rocks_property(+RocksDB, ?Property) is nondet

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

 rocks_put(Arg1, Arg2, Arg3, Arg4)
 rocks_merge(Arg1, Arg2, Arg3, Arg4)
 rocks_delete(Arg1, Arg2, Arg3)
 rocks_batch(Arg1, Arg2, Arg3)
 rocks_get(Arg1, Arg2, Arg3, Arg4)
 rocks_enum(Arg1, Arg2, Arg3, Arg4)
 rocks_enum_from(Arg1, Arg2, Arg3, Arg4, Arg5)
 rocks_enum_prefix(Arg1, Arg2, Arg3, Arg4, Arg5)