1:- module(dynvector_persistence,
    2    [
    3        dynvector_clone/2,
    4        dynvector_erase/2,
    5        dynvector_persist/2,
    6        dynvector_restore/2,
    7        dynvector_serialize/2
    8    ]).

Persistence for dynvector objects, using Berkeley DB

This module provides persistence for dynvector objects, using the Berkeley DB utility package. For details on the SWI-Prolog interface to Berkeley DB, please refer to the documentation for bdb_rapper.pl .

author
- GT Nunes
version
- 1.3.2
license
- BSD-3-Clause License */
   22%-------------------------------------------------------------------------------------
   23
   24:- use_module(library(lists),
   25    [
   26        nth0/3
   27    ]).   28
   29:- use_module('bdb_wrapper',
   30    [
   31        bdb_erase/2,
   32        bdb_retrieve/3,
   33        bdb_store/3
   34    ]).   35
   36:- use_module('dynvector_core',
   37    [
   38        dynvector_create/1,
   39        dynvector_destroy/1,
   40        dynvector_label/3,
   41        dynvector_value/3,
   42        is_dynvector/1
   43    ]).   44
   45%-------------------------------------------------------------------------------------
 dynvector_clone(+IdSource, +IdTarget) is det
Clone a dynvector.
Arguments:
IdSource- Atom identifying the source dynvector
IdTarget- Atom identifying the target dynvector
   54dynvector_clone(IdSource, IdTarget) :-
   55
   56    % fail points (source dynvector must exist, target dynvector must not exist)
   57    is_dynvector(IdSource),
   58    \+ is_dynvector(IdTarget),
   59
   60    % serialize the source dynvector
   61    dynvector_serialize(IdSource, Data),
   62
   63    % create target dynvector with serialized data from IdSource
   64    dynvector_serialize(IdTarget, Data).
   65
   66%-------------------------------------------------------------------------------------
 dynvector_serialize(+Id, ?Serialized) is det
A serialization mechanism, for backup/restore purposes. The description below applies for a given dynvector containing Nv values and Nb labels.
Its serialization structure will be:
  <Nb>,<br/>
  [<key-label-1>,<value-label-1>],...,[<key-label-Nb>,<value-label-Nb>],<br/>
  [<index-1>,<value-1>],...,[<index-Nv>,<value-Nv>]

The serialized list will thus contain `Np + Nv + 1` elements:<br/>
  <num-labels>    - the total number of key-value label pairs<br/>
  <key-label-j>   - the key in the key-value label pair `j`<br/>
  <value-label-j> - the value in the key-value label pair<br/>
  <index-j>       - the index position of value `j` within the dynvector<br/>
  <value-j>       - the value `j` within the dynvector
Arguments:
Id- Atom identifying the dynvector
Serialized- Serialization list containing the dynvector data
   89dynvector_serialize(Id, Serialized) :-
   90
   91    % HAZARD: ground(Serialized) might be very expensive
   92    (var(Serialized) ->
   93        is_dynvector(Id),
   94        dynvector_to_serialized(Id, Serialized)
   95    ;
   96        (Serialized = [] ->
   97            dynvector_destroy(Id),
   98            dynvector_create(Id) 
   99        ;
  100            serialized_to_dynvector(Id, Serialized)
  101        )
  102    ).
  103
  104%-------------------------------------------------------------------------------------
 dynvector_to_serialized(+Id:atom, Serialized:data) is det
Serialize the contents (labels and values) of the dynvector.
Arguments:
Id- Atom identifying the dynvector
Serialized- Serialization list containing the dynvector data
  113dynvector_to_serialized(Id, Serialized) :-
  114
  115    % retrieve all labels (key and value pairs) in dynvector
  116    findall([Label,Value],
  117            dynvector_core:dynvect_labels(Id, Label, Value), Labels),
  118
  119    % retrieve all values (position-value pairs) in dynvector
  120    findall([Index,Value],
  121            dynvector_core:dynvect_values(Index, Id, Value), Values),
  122
  123    % join them in a single list
  124    append(Labels, Values, DynData),
  125
  126    % add dimensions ranges and number of labels
  127    length(Labels, NumLabels),
  128    append([NumLabels], DynData, Serialized).
  129
  130%-------------------------------------------------------------------------------------
 serialized_to_dynvector(+Id:atom, +Serialized:data) is det
Restore the contents (labels and values) of the dynvector
Arguments:
Id- Atom identifying the dynvector
Serialized- Serialization list containing the dynvector data
  139serialized_to_dynvector(Id, Serialized) :-
  140
  141    % create dynvector
  142    [NumLabels|_] = Serialized,
  143    dynvector_destroy(Id),                        % SANITY POINT
  144    dynvector_create(Id),
  145
  146    % restore the labels
  147    LabelsFinal is NumLabels + 2,
  148    serialized_to_labels_(Id, Serialized, 2, LabelsFinal),
  149
  150    % retrieve the indices/values list
  151    length(Serialized, ValuesFinal),
  152    serialized_to_values_(Id, Serialized, LabelsFinal, ValuesFinal).
 serialized_to_labels_(+Id:atom, +Labels:list, +PosCurr:int, +PosFinal:int) is det
Arguments:
Id- Atom identifying the dynvector
Labels- The labels (key-value pairs) to load to the dynvector
PosCurr- The current label position
PosLast- The last label position
  161% (done)
  162serialized_to_labels_(_Id, _Labels, PosFinal, PosFinal) :- !.
  163
  164% (iterate)
  165serialized_to_labels_(Id, Labels, PosCurr, PosFinal) :-
  166
  167    % register the label (dv_* labels are not accepted)
  168    nth0(PosCurr, Labels, [Key,Value]),
  169    (dynvector_label(Id, Key, Value) ; true),
  170    !,
  171
  172    % go for the next label
  173    PosNext is PosCurr + 1,
  174    serialized_to_labels_(Id, Labels, PosNext, PosFinal).
 serialized_to_values_(+Id:atom, +Values:data) is det
Arguments:
Id- Atom identifying the dynvector
Values- The values to load to the dynvector
  181% (done)
  182serialized_to_values_(_Id, _Values, IndexFinal, IndexFinal) :- !.
  183
  184% (iterate)
  185serialized_to_values_(Id, Values, IndexCurr, IndexFinal) :-
  186
  187    % load the value onto the dynvector
  188    nth0(IndexCurr, Values, [Index,Value]),
  189    dynvector_value(Id, Index, Value),
  190
  191    % go for the next value
  192    IndexNext is IndexCurr + 1,
  193    serialized_to_values_(Id, Values, IndexNext, IndexFinal).
  194
  195%-------------------------------------------------------------------------------------
 dynvector_persist(+Id:atom, +DataSet:atom) is det
Persist the dynvector data to a Berkeley DB external storage.
Arguments:
Id- Atom identifying the dynvector
DataSet- Atom identifying the data set
  204dynvector_persist(Id, DataSet) :-
  205
  206    % fail point
  207    is_dynvector(Id),
  208
  209    % fail point (erase the dynvector storage)
  210    bdb_erase(Id, DataSet),
  211
  212    % obtain the dynvector data
  213    dynvector_serialize(Id, Data),
  214
  215    !,
  216    % fail point (persist the dynvector data)
  217    bdb_store(Id, DataSet, Data).
  218
  219%-------------------------------------------------------------------------------------
 dynvector_restore(+Id, +DataSet) is det
Restore the dynvector data from a Berkeley DB external storage
Arguments:
Id- Atom identifying the dynvector
DataSet- Atom identifying the data set
  228dynvector_restore(Id, DataSet) :-
  229
  230    % fail point (retrieve the dynvector data from external storage)
  231    bdb_retrieve(Id, DataSet, Data),
  232
  233    % re-create the dynvector with its contents
  234    dynvector_serialize(Id, Data).
  235
  236%-------------------------------------------------------------------------------------
 dynvector_erase(+Id:atom, +DataSet:atom) is det
Erase the dynvector persisted data.
Arguments:
Id- Atom identifying the dynvector
DataSet- Atom identifying the data set
  245dynvector_erase(Id, DataSet) :-
  246
  247    % fail point (erase the dynvector storage)
  248    bdb_erase(Id, DataSet)