1:- module(dynvector_core,
    2    [
    3        dynvector_append/3,
    4        dynvector_create/1,
    5        dynvector_delete/2,
    6        dynvector_destroy/1,
    7        dynvector_fill/2,
    8        dynvector_find/3,
    9        dynvector_insert/3,
   10        dynvector_label/3,
   11        dynvector_list/2,
   12        dynvector_sort/1,
   13        dynvector_sort/2,
   14        dynvector_top/2,
   15        dynvector_value/3,
   16        dynvector_version/1,
   17        is_dynvector/1,
   18
   19        dynvector_iterator_append/2,
   20        dynvector_iterator_create/1,
   21        dynvector_iterator_create/2,
   22        dynvector_iterator_create/3,
   23        dynvector_iterator_current/2,
   24        dynvector_iterator_delete/1,
   25        dynvector_iterator_destroy/1,
   26        dynvector_iterator_first/2,
   27        dynvector_iterator_index/2,
   28        dynvector_iterator_insert/2,
   29        dynvector_iterator_last/2,
   30        dynvector_iterator_next/2,
   31        dynvector_iterator_prev/2
   32    ]).

Dynamic vectors

This module provides an implementation of dynvectors. These are their noteworthy characteristics:

1. dynvectors are powerful, flexible, extendable, high-performance,
   hash-based vectors;
2. dynvectors have O(1) read/insert/update/delete times, and this holds
   true up to sizes in the order of millions of cells;<
3. dynvectors are not immutable objects, or more specifically, they are not
   recreated upon modification;
4. dynvectors have no limitation on the number of cells, apart from the
   running platform's resource limitations;
5. dynvectors do not have a maximum number of cells specified at creation time -
   elements may be freely inserted, updated, or deleted, as the dynvector
   dynamically adjusts its upper bound as needed;
6. dynvectors demand no storage space reservation previous to the actual
   cell-by-cell space allocation requests;
7. dynvectors are resource-minded; their cells are not required to have values
   assigned to, in any particular sequence or fashion;
8. in order to avoid resource wastage, dynvectors should be explicitly
   destroyed, upon ceasing to be of any further use.
author
- GT Nunes
version
- 1.3.2
license
- BSD-3-Clause License */
   64%-------------------------------------------------------------------------------------
   65
   66:- meta_predicate dynvector_sort(+, 3).   67
   68:- use_module(library(apply),
   69    [
   70        maplist/2
   71    ]).   72
   73:- use_module(library(lists),
   74    [
   75        nth1/3
   76    ]).   77
   78:- use_module('quicksort',
   79    [
   80        quicksort/3
   81    ]).   82
   83:- dynamic  dynvect_labels/3,
   84            dynvect_values/3.   85
   86:- volatile dynvect_labels/3,
   87            dynvect_values/3.   88
   89%-------------------------------------------------------------------------------------
 dynvector_create(+Id:atom) is semidet
Create a dynvector.
Arguments:
Id- Atom identifying the dynvector
   97dynvector_create(Id) :-
   98
   99    % fail point (make sure id is an atom)
  100    atom(Id),
  101
  102    % fail point (make sure id is not taken)
  103    \+ is_dynvector(Id),
  104
  105    % register the dynvector's size, max index, and iterator bounds
  106    assertz(dynvect_labels(Id, dv_top, -1)),
  107    assertz(dynvect_labels(Id, dv_first, -1)),
  108    assertz(dynvect_labels(Id, dv_last, -1)),
  109    assertz(dynvect_labels(Id, dv_curr, -1)).
  110
  111%-------------------------------------------------------------------------------------
 dynvector_destroy(+Id:atom)
Destroy dynvector Id, and release all of its resources. No action if it does not exist.
Arguments:
Id- Atom identifying the dynvector
  120dynvector_destroy(Id) :-
  121
  122  retractall(dynvect_labels(Id, _, _)),
  123  retractall(dynvect_values(_, Id, _)).
  124
  125%-------------------------------------------------------------------------------------
 is_dynvector(+Id:atom) is semidet
Fail if Id does not identify a dynvector.
Arguments:
Id- Atom identifying the dynvector
  133is_dynvector(Id) :-
  134    dynvect_labels(Id, dv_top, _).
 dynvector_version(-Version:number) is det
Unify Version with the current version of the dynvector implementation.
Arguments:
Version- Dynvector implementation's current version
  142dynvector_version(Version) :-
  143    Version = 1.32.
  144
  145%-------------------------------------------------------------------------------------
 dynvector_top(+Id:atom, -Top:int) is semidet
Unify Top with the highest inserted index value in the dynvector, even if it has subsequently been deleted. Upon dynvector's creation, this value is set to -1.
Arguments:
Id- Atom identifying the dynvector
Top- Value of the highest index
  155dynvector_top(Id, Top) :-
  156    dynvect_labels(Id, dv_top, Top).
  157
  158%-------------------------------------------------------------------------------------
 dynvector_value(+Id:atom, +Index:int, ?Value:data) is semidet
Unify Value with the value of the dynvector cell at Index. Dynvectors may be sparsed, i.e., they may have cells not holding values, but attempts to retrieve the value of an empty cell will fail. Dynvector values are stored in the dynamic predicate dynvect_vaLues(Position, Id, Value).
Arguments:
Id- Atom identifying the dynvector
Index- The reference index, or a label standing for it
Value- The dynvector cell value
  172dynvector_value(Id, Index, Value) :-
  173
  174    % determine the element's index from label, if necessary
  175    ( (integer(Index) , Inx = Index)
  176    ; dynvect_labels(Id, Index, Inx) ),
  177    !,
  178
  179    % has Value been grounded ?
  180    (ground(Value) ->
  181       % yes, so register value and top index
  182       dynvector_value_(Id, Inx, Value)
  183    ;
  184       % no, so retrieve value
  185       !,
  186       % fail point (cell might be empty)
  187       dynvect_values(Inx, Id, Value)
  188    ).
  189
  190dynvector_value_(Id, Index, Value) :-
  191
  192    % register value
  193    (retract(dynvect_values(Index, Id, _)) ; true),
  194    !,
  195    assertz(dynvect_values(Index, Id, Value)),
  196
  197    % register top index, if appropriate
  198    dynvect_labels(Id, dv_top, Top),
  199    ( Index =< Top
  200    ; ( retract(dynvect_labels(Id, dv_top, _))
  201      , assertz(dynvect_labels(Id, dv_top, Index)) ) ),
  202    !.
  203
  204%-------------------------------------------------------------------------------------
 dynvector_label(+Id:atom, +Label:atom, ?Value:Data) is semidet
Unify Value with the value associated with Label. This allows atoms to stand for indices. Label values are stored in the dynamic predicate dynvect_labels(Id, Label, Value).

The following are the read-only private labels in use:

dv_top   - maximum index value in the dynvector
dv_first - begin index for iterator
dv_last  - end index for iterator
dv_curr  - current index for iterator
Arguments:
Id- atom identifying the dynvector
Label- atom standing for the named attribute
Value- associated with the named attribute
  224dynvector_label(Id, Label, Value) :-
  225
  226    (ground(Value) ->
  227        % fail point (must be an atom, and must not start with dv_)
  228        \+ sub_atom(Label, 0, 3, _, dv_),
  229        (retract(dynvect_labels(Id, Label, _)) ; true),
  230        !,
  231        assertz(dynvect_labels(Id, Label, Value))
  232    ;
  233        dynvect_labels(Id, Label, Value)
  234    ).
  235
  236%-------------------------------------------------------------------------------------
 dynvector_find(+Id:atom, ?Index:int, ?Value:data) is semidet
Unify Index or Value with an occurrence of Index or Value in the dynvector, respectively. Fail if no such value or index exist.
Arguments:
Id- Atom identifying the dynvector
Index- The reference index
Value- The reference value
  247dynvector_find(Id, Index, Value) :-
  248    dynvect_values(Index, Id, Value).
  249
  250%-------------------------------------------------------------------------------------
 dynvector_append(+Id:atom, +Value:data, -Index:int) is det
Append the given Value to the dynvector, and unify Index with the appension position. Value may be scalar, a list, or another dynvector.
Arguments:
Id- Atom identifying the dynvector
Value- Value or list of of values to append
Index- Index identifying the element holding Value or its first element
  261dynvector_append(Id, Value, Index) :-
  262
  263    % compute the index for the Value
  264    dynvect_labels(Id, dv_top, Top),
  265    Index is Top + 1,
  266
  267    % is Value a list of Values ?
  268    (is_list(Value) ->
  269        % yes, so append the list of values to the dynvector
  270        Values = Value
  271
  272    % is Value a dynvector ?
  273    ; is_dynvector(Value) ->
  274        % yes, so append the source dynvector values into the target dynvector
  275        findall(Value, dynvect_values(_Index, Id, Value), Values)
  276
  277    % Value is a single entity
  278    ; otherwise ->
  279        % so, append it to the dynvector
  280        Values = [Value]
  281    ),
  282
  283    % append Values to the dynvector
  284    dynvector_append_(Values, Id, Index),
  285
  286    % register the new Top
  287    length(Values, Count),
  288    TopNew is Top + Count,
  289    retract(dynvect_labels(Id, dv_top, _)),
  290    assertz(dynvect_labels(Id, dv_top, TopNew)).
  291
  292dynvector_append_([], _Id, _Index) :- !.
  293
  294dynvector_append_([Value|Values], Id, Index) :-
  295
  296    assertz(dynvect_values(Index, Id, Value)),
  297    IndexNext is Index + 1,
  298    dynvector_append_(Values, IndexNext, Id).
  299
  300%-------------------------------------------------------------------------------------
 dynvector_insert(+Id:atom, +Index:int, +Value:data)
Insert Value into the dynvector at Index. Value may be scalar, a list, or another dynvector.
Arguments:
Id- Atom identifying the dynvector
Index- The insertion point
Value- Value or list of of values to insert
  311dynvector_insert(Id, Index, Value) :-
  312
  313    % is Value a list of Values ?
  314    (is_list(Value) ->
  315        % yes, so make it explicit
  316        Values = Value
  317
  318    % is Value a dynvector ?
  319    ; is_dynvector(Value) ->
  320        % yes, so obtain its list of values
  321        findall(Value, dynvect_values(_Index, Id, Value), Values)
  322
  323    % Value is a single entity
  324    ; otherwise ->
  325        % so, obtain a list with a Value as its single element
  326        Values = [Value]
  327    ),
  328
  329    % insert the values
  330    dynvect_labels(Id, dv_top, Top),
  331    dynvector_insert_(Values, Id, Top, Index, Top),
  332
  333    % register the new top
  334    length(Values, Count),
  335    TopNew is Top + Count,
  336    retract(dynvect_labels(Id, dv_top, _)),
  337    assertz(dynvect_labels(Id, dv_top, TopNew)).
  338
  339% (done)
  340dynvector_insert_([], _Id, _Top, _From, _To) :- !.
  341
  342% (iterate)
  343dynvector_insert_([Value|Values], Id, Top, From, To) :-
  344
  345    ToNext is To + 1,
  346
  347    % is there a value at From ?
  348    ((From =< Top , dynvect_values(From, Id, Value)) ->
  349        % yes, so move it to ToNext
  350        retract(dynvect_values(From, Id, _Value)),
  351        assertz(dynvect_values(ToNext, Id, Value))
  352    ;
  353        % no, so proceed
  354        true
  355    ),
  356
  357    % register Value at From
  358    assertz(dynvect_values(From, Id, Value)),
  359
  360    % go for the next value
  361    FromNext is From + 1,
  362    dynvector_insert_(Values, Id, Top, FromNext, ToNext).
  363
  364%-------------------------------------------------------------------------------------
 dynvector_delete(+Id:atom, +Index) is semidet
Erase the dynvector cell at Index, releasing the storage space taken. Fail if no such cell exists.
Arguments:
Id- Atom identifying the dynvector
Index- The reference index, or a label standing for it
  374dynvector_delete(Id, Index) :-
  375
  376    % determine the element's Index from Label, if necessary
  377    ( (integer(Index) , Inx = Index)
  378    ; dynvect_labels(Id, Index, Inx) ),
  379
  380    % erase the cell
  381    !,
  382    % fail point (cell might already be empty)
  383    retract(dynvect_values(Inx, Id, _)).
  384
  385%-------------------------------------------------------------------------------------
 dynvector_list(+Id:atom, ?List:list) is det
Unify the cells of the dynvector with the values in List. A dynvector to hold all the list elements may be created. Note that this is not a serialization a mechanism, and as such it should not be used for backup/restore purposes.
Arguments:
Id- Atom identifying the dynvector
List- List of values to unify the dynvector cells with
  397dynvector_list(Id, List) :-
  398
  399    % HAZARD: ground(List) might be very expensive
  400    (var(List) ->
  401        % load all values in dynvector into List
  402        findall(Value, dynvect_values(_Index, Id, Value), List)
  403    ;
  404        % clear dynvector or create it anew
  405        (is_dynvector(Id) ->
  406            retractall(dynvect_values(_, Id, _))
  407        ;
  408            dynvector_create(Id)
  409        ),
  410
  411        % List might be a list or a dynvector
  412        % (in the latter case, List is an atom holding the dynvector id)
  413        (is_list(List) ->
  414            Values = List
  415        ;
  416            findall(Value, dynvect_values(_, List, Value), Values)
  417        ),
  418
  419        % load all values in Values into dynvector
  420        list_to_dynvector_(Values, Id, 0)
  421    ).
  422
  423% list_to_dynvector_(+List:list, +Id:atom, +Index:int) is det.
  424%
  425%  @param List  The value to unify the dynvector cell with
  426%  @param Id    Atom identifying the dynvector
  427%  @param Index Index identifying the dynvector cell
  428
  429% (done)
  430list_to_dynvector_([], Id, Index) :-
  431
  432    % register the top index for the dynvector
  433    Top is Index - 1,
  434    retract(dynvect_labels(Id, dv_top, _)),
  435    assertz(dynvect_labels(Id, dv_top, Top)),
  436    !.
  437
  438% (iterate)
  439list_to_dynvector_([Value|List], Id, Index) :-
  440
  441    assertz(dynvect_values(Index, Id, Value)),
  442    IndexNext is Index + 1,
  443    list_to_dynvector_(List, Id, IndexNext).
  444
  445%-------------------------------------------------------------------------------------
 dynvector_fill(+Id:atom, +Value:data) is det
Unify all of the cells of the dynvector with Value.
Arguments:
Id- Atom identifying the dynvector
Value- Value to unify the dynvector cells with
  454dynvector_fill(Id, Value) :-
  455
  456    retractall(dynvect_values(_, Id, _)),
  457    dynvect_labels(Id, dv_top, Count),
  458    dynvector_fill_(Id, Value, 0, Count).
 dynvector_fill_(+Id:atom, +Value:data, +Index:int, +Count:int) is det
Arguments:
Id- Atom identifying the dynvector
Value- Value to unify the dynvector cell with
Index- 0-based index identifying the dynvector cell
Count- Nnumber of cells in dynvector
  467% (done)
  468dynvector_fill_(_Id, _Value, Count, Count) :- !.
  469
  470% (iterate)
  471dynvector_fill_(Id, Value, Index, Count) :-
  472
  473    % load Value into the cell at Index
  474    assertz(dynvect_values(Index, Id, Value)),
  475
  476    % go for thew next index
  477    IndexNext is Index + 1,
  478    dynvector_fill_(Id, Value, IndexNext, Count).
  479
  480%-------------------------------------------------------------------------------------
 dynvector_sort(+Id:atom) is det
Numerically sort the contents of the dynvector, in ascending order. It must be possible to numerically compare any two elements stored in the dynvector. In the case of a sparse dynvector, the empty cells are ignored. Nothing is done if the dynvector contains less than two elements. Depending on the volume and nature of the data stored, this may be a very expensive operation, in terms of memory and/or time consumed.<br/>
Arguments:
Id- Atom identifying the dynarray
  493dynvector_sort(Id) :-
  494    dynvector_sort(Id, number_comparator).
  495
  496number_comparator(ValueX, ValueY, Result) :-
  497
  498    (ValueX < ValueY ->
  499        Result = -1
  500    ; ValueX > ValueY ->
  501        Result = 1
  502    ; otherwise ->
  503        Result = 0
  504    ).
 dynvector_sort(+Id:atom, :Comparator:pred) is det
Sort the contents of the dynvector according to the given comparison predicate. The comparison predicate must accept two parameters, ValueX and ValueY, and have the following behavior:
<Comparator>(+ValueX, +ValueY, -Result:number) is det
where Result is unified with
  a) 0 (zero)          - ValueX is equal to ValueY
  b) a negative number - ValueX is less than ValueY
  c) a positive number - ValueX is greater than ValueY

The criteria that will determine the results of the comparisons are entirely up to Comparator, and as such it must be able to handle all the values it receives.
In the case of a sparse dynvector, the empty cells are ignored. Nothing is done if the dynvector contains less than two elements. Depending on the volume and nature of the data stored, this may be a very expensive operation, in terms of memory and/or time consumed.<br/>

Arguments:
Id- Atom identifying the dynvector
Comparator- Predicate to perform comparisons between two values
  530dynvector_sort(Id, Comparator) :-
  531
  532    % retrieve all values (index-value pairs) in dynvector
  533    findall([Inx,Val], dynvect_values(Inx, Id, Val), IndicesValues),
  534
  535    % does the dynvector contain more than one element ?
  536    length(IndicesValues, Count),
  537    (Count > 1 ->
  538        % yes, so sort its values using the given comparator
  539        pairs_to_lists(IndicesValues, [], Indices, [], Values),
  540        quicksort(Values, Comparator, SortedValues),
  541
  542%>>> backtrack until Indices is exausted
  543        nth1(Pos, Indices, Index),
  544        nth1(Pos, SortedValues, Value),
  545
  546        % replace the value at the cell
  547        retract(dynvect_values(Index, Id, _)),
  548        assertz(dynvect_values(Index, Id, Value)),
  549
  550        % fail point
  551        Pos = Count
  552%<<<
  553    ;
  554        % no, so just exit
  555        true
  556    ).
  557
  558% (done)
  559pairs_to_lists([], Final1st, Final1st, Final2nd, Final2nd) :- !.
  560
  561% (iterate)
  562pairs_to_lists([[Element1st,Element2nd]|Pairs],
  563              Progress1st, Final1st, Progress2nd, Final2nd) :-
  564    pairs_to_lists(Pairs, [Element1st|Progress1st], Final1st,
  565                   [Element2nd|Progress2nd], Final2nd).
  566
  567%-------------------------------------------------------------------------------------
 dynvector_iterator_create(+Id:atom) is semidet
Create iterator with range from 0 to Top.
Arguments:
Id- Atom identifying the dynvector
  575dynvector_iterator_create(Id) :-
  576
  577    dynvect_labels(Id, dv_top, Top),
  578    dynvector_iterator_create(Id, 0, Top).
 dynvector_iterator_create(+Id:atom, +From:int) is semidet
Create iterator with range from From to Top.
Arguments:
Id- Atom identifying the dynvector
From- The iterator's first index
  587dynvector_iterator_create(Id, From) :-
  588
  589    dynvect_labels(Id, dv_top, Top),
  590    dynvector_iterator_create(Id, From, Top).
 dynvector_iterator_create(+Id:atom, +From:int, +To:int) is semidet
Create iterator with range from From to To. Initial and final range positions must be consistent with the dynvector state. Fail if the dynvector already has an active iterator.
Arguments:
Id- Atom identifying the dynvector
From- The iterator's first index
To- The iterator's last index
  602dynvector_iterator_create(Id, From, To) :-
  603
  604    % fail points (From and To must be consistent)
  605    To >= From,
  606    From >= 0,
  607
  608    dynvect_labels(Id, dv_top, Top),
  609    %fail point (iterator's upper bound must be within dynvector's bounds)
  610    To >= Top,
  611
  612    % fail point (dynvector cannot already have an active iterator)
  613    dynvect_labels(Id, dv_first, -1),
  614
  615    % register the iterator
  616    retract(dynvect_labels(Id, dv_first, _)),
  617    assertz(dynvect_labels(Id, dv_first, From)),
  618    retract(dynvect_labels(Id, dv_last, _)),
  619    assertz(dynvect_labels(Id, dv_last, To)),
  620    retract(dynvect_labels(Id, dv_curr, _)),
  621    assertz(dynvect_labels(Id, dv_curr, From)).
  622
  623%-------------------------------------------------------------------------------------
 dynvector_iterator_destroy(+Id:atom) is semidet
Destroy the dynvector's iterator. Fail if dynvector Id does not exist. No action if dynvector does not have an active iterator.
Arguments:
Id- Atom identifying the dynvector
  632dynvector_iterator_destroy(Id) :-
  633
  634    retract(dynvect_labels(Id, dv_first, _)),
  635    assertz(dynvect_labels(Id, dv_first, -1)),
  636    retract(dynvect_labels(Id, dv_last, _)),
  637    assertz(dynvect_labels(Id, dv_last, -1)),
  638    retract(dynvect_labels(Id, dv_curr, _)),
  639    assertz(dynvect_labels(Id, dv_curr, -1)).
  640
  641%-------------------------------------------------------------------------------------
 dynvector_iterator_next(+Id:atom, ?Value:data) is semidet
Move the itrator to the next position, and unify Value with the value therein. Fail if dynvector does not have an active iterator, or if a next position is not possible.
Arguments:
Id- Atom identifying the dynvector
Value- Value to unify the iterator's next position with
  652dynvector_iterator_next(Id, Value) :-
  653
  654    % retrieve iterator's current position
  655    dynvect_labels(Id, dv_curr, Current),
  656    % fail point (iterator must be active)
  657    Current > -1,
  658
  659    % retrieve iterator's last position
  660    dynvect_labels(Id, dv_last, Last),
  661    !,
  662    % fail point
  663    dynvector_iterator_next_(Id, Current, Last, Value).
  664
  665dynvector_iterator_next_(_Id, Last, Last, _Value) :- !, fail.
  666
  667dynvector_iterator_next_(Id, Current, Last, Value) :-
  668
  669    Next is Current + 1,
  670    % attempt to unify Value with the value at Next, OR
  671    ( dynvector_iterator_nav_(Id, Next, Value)
  672    % go for the next position
  673    ; dynvector_iterator_next_(Id, Next, Last, Value) ),
  674    !.
  675
  676%-------------------------------------------------------------------------------------
 dynvector_iterator_prev(+Id:atom, ?Value:data) is semidet
Move the iterator to the previous position, and unify Value with the value therein. Fail if dynvector does not have an active iterator, or if a previous position is not possible.
Arguments:
Id- Atom identifying the dynvector
Value- Value to unify the iterator's previous position with
  687dynvector_iterator_prev(Id, Value) :-
  688
  689    % retrieve iterator's current position
  690    dynvect_labels(Id, dv_curr, Current),
  691    % fail point (iterator must be active)
  692    Current > -1,
  693
  694    % retrieve iterator's first position
  695    dynvect_labels(Id, dv_first, First),
  696    !,
  697    % fail point
  698    dynvector_iterator_prev_(Id, Current, First, Value).
  699
  700dynvector_iterator_prev_(_Id, First, First, _Value) :- !, fail.
  701
  702dynvector_iterator_prev_(Id, Current, First, Value) :-
  703
  704    Prev is Current - 1,
  705    % attempt to unify Value with the value at Prev, OR
  706    ( dynvector_iterator_nav_(Id, Prev, Value)
  707    % go for the previous position
  708    ; dynvector_iterator_prev_(Id, Prev, First, Value) ),
  709    !.
  710
  711%-------------------------------------------------------------------------------------
 dynvector_iterator_first(+Id:atom, ?Value:data) is semidet
Move the iterator to the first position, and unify Value with the value therein. Fail if dynvector does not have an active iterator.
Arguments:
Id- Atom identifying the dynvector
Value- Value to unify the iterator's first position with
  721dynvector_iterator_first(Id, Value) :-
  722
  723    % obtain iterator's first index
  724    dynvect_labels(Id, dv_first, First),
  725    % fail point (iterator must be active)
  726    First > -1,
  727
  728    % unify Value with the value at First
  729    !,
  730    % fail point
  731    dynvector_iterator_nav_(Id, First, Value).
  732
  733%-------------------------------------------------------------------------------------
 dynvector_iterator_last(+Id:atom, ?Value:data) is semidet
Move the iterator to the last position, and unify Value with the value therein. Fail if dynvector does not have an active iterator.
Arguments:
Id- Atom identifying the dynvector
Value- Value to unify the iterator's last position with
  743dynvector_iterator_last(Id, Value) :-
  744
  745    % obtain iterator's last index
  746    dynvect_labels(Id, dv_last, Last),
  747    % fail point (iterator must be active)
  748    Last > -1,
  749
  750    % unify Value with the value at Last
  751    !,
  752    % fail point
  753    dynvector_iterator_nav_(Id, Last, Value).
  754
  755% dynvector_iterator_nav_(+Id:atom, ?Value:data) is det.
  756%
  757% Unify Value with the value at Index.
  758%
  759% @param Id    Atom identifying the dynvector
  760% @param Value Value to unify the iterator's given position with
  761
  762dynvector_iterator_nav_(Id, Index, Value) :-
  763
  764    % has Value been grounded ?
  765    (ground(Value) ->
  766       % yes, so register value
  767       (retract(dynvect_values(Index, Id, Value)) ; true),
  768       !,
  769       assertz(dynvect_values(Index, Id, Value))
  770    ;
  771       % no, so retrieve value
  772       !,
  773       % fail point (cell might be empty)
  774       dynvect_values(Index, Id, Value)
  775    ),
  776
  777    % adjust iterator's current index
  778    retract(dynvect_labels(Id, dv_curr, _)),
  779    assertz(dynvect_labels(Id, dv_curr, Index)).
  780
  781%-------------------------------------------------------------------------------------
 dynvector_iterator_current(+Id:atom, ?Value) is semidet
Unify Value with the value at iterator's current position. Fail if dynvector does not have an active iterator.
Arguments:
Id- Atom identifying the dynvector
Value- Value to unify the iterator's current position with
  791dynvector_iterator_current(Id, Value) :-
  792
  793    % obtain iterator's current index
  794    dynvect_labels(Id, dv_curr, Current),
  795    % fail point (iterator must be active)
  796    Current > -1,
  797
  798    % unify Value with the value at Current
  799    !,
  800    % fail point
  801    dynvector_iterator_nav_(Id, Current, Value).
  802
  803%-------------------------------------------------------------------------------------
 dynvector_iterator_delete(+Id:atom) is semidet
Erase value at iterator's current position. Fail if dynvector does not have an active iterator.
Arguments:
Id- Atom identifying the dynvector
  812dynvector_iterator_delete(Id) :-
  813
  814    % obtain iterator's current index
  815    dynvect_labels(Id, dv_curr, Current),
  816    % fail point (iterator must be active)
  817    Current > -1,
  818
  819    % remove value
  820    (retract(dynvect_values(Current, Id, _)) ; true),
  821    !.
  822
  823%-------------------------------------------------------------------------------------
 dynvector_iterator_index(+Id:atom, -Index:int) is semidet
Unify Index with iterator's current index.
Arguments:
Id- Atom identifying the dynvector
Index- The iterator's current index
  832dynvector_iterator_index(Id, Index) :-
  833
  834    % fail point (Index must be a var)
  835    var(Index),
  836
  837    % obtain iterator's current index
  838    dynvect_labels(Id, dv_curr, Index).
  839
  840%-------------------------------------------------------------------------------------
 dynvector_iterator_insert(+Id:atom, ?Value:data) is semidet
Insert Value at iterator's current position, and adjust the iterator's range accordingly. Fail if dynvector does not have an active iterator.
Arguments:
Id- Atom identifying the dynvector
Value- Value to be inserted
  850dynvector_iterator_insert(Id, Value) :-
  851
  852    % obtain iterator's current position
  853    dynvect_labels(Id, dv_curr, Index),
  854    % fail point (iterator must be active)
  855    Index > -1,
  856
  857    % save dynvector's current Top
  858    dynvect_labels(Id, dv_top, Top),
  859
  860    % insert Value (Value might be a singleton, a list, or another dynvector)
  861    dynvector_insert(Id, Index, Value),
  862
  863    % adjust iterator's last index
  864    dynvect_labels(Id, dv_last, Last),
  865    dynvect_labels(Id, dv_top, TopNew),
  866    LastNew is Last + TopNew - Top,
  867    retract(dynvect_labels(Id, dv_last, _)),
  868    assertz(dynvect_labels(Id, dv_last, LastNew)).
  869
  870%-------------------------------------------------------------------------------------
 dynvector_iterator_append(+Id:atom, ?Value)
Insert Value after iterator's last position, and adjust the iterator's range accordingly. Fail if dynvector does not have an active iterator.
Arguments:
Id- Atom identifying the dynvector
Value- Value to be appended
  880dynvector_iterator_append(Id, Value) :-
  881
  882    % obtain iterator's current position
  883    dynvect_labels(Id, dv_last, Last),
  884    % fail point (iterator mus be active)
  885    Last > -1,
  886
  887    % save dynvector's current Top
  888    dynvect_labels(Id, dv_top, Top),
  889
  890    % insert Value (Value might be a singleton, a list, or another dynvector)
  891    Index is Last + 1,
  892    dynvector_insert(Id, Index, Value),
  893
  894    % adjust iterator's last index
  895    dynvect_labels(Id, dv_last, Last),
  896    dynvect_labels(Id, dv_top, TopNew),
  897    LastNew is Last + TopNew - Top,
  898    retract(dynvect_labels(Id, dv_last, _)),
  899    assertz(dynvect_labels(Id, dv_last, LastNew))