1:- module(dynarray_core,
    2    [
    3        dynarray_cells/2,
    4        dynarray_cells/3,
    5        dynarray_create/2,
    6        dynarray_delete/2,
    7        dynarray_destroy/1,
    8        dynarray_dims/2,
    9        dynarray_elements/2,
   10        dynarray_fill/2,
   11        dynarray_find/3,
   12        dynarray_label/3,
   13        dynarray_list/2,
   14        dynarray_sort/1,
   15        dynarray_sort/2,
   16        dynarray_top/3,
   17        dynarray_value/3,
   18        dynarray_version/1,
   19        dynarray_position_delete/2,
   20        dynarray_position_find/3,
   21        dynarray_position_indices/3,
   22        dynarray_position_top/2,
   23        dynarray_position_value/3,
   24        is_dynarray/1
   25    ]).

Dynamic, multi-dimensional arrays

This module provides an implementation of dynamic multi-dimensional arrays. These are some of their noteworthy characteristics:

1. dynarrays are powerful, flexible, high-performance, hash-based
   multi-dimensional arrays;
2. dynarrays have O(1) read/insert/update/delete times, and this holds true
   up to sizes in the order of millions of cells;
3. dynarrays are not immutable objects, or more specifically, they are not
   recreated upon modification;
4. dynarrays have no limitation on the number of dimensions, nor any restriction
   on dimension sizes, apart from the running platform's resource limitations;
5. dynarrays have a maximum number of cells, defined at creation time and
   kept constant thereafter;
6. dynarrays demand no storage space reservation previous to the actual
   cell-by-cell space allocation requests;
7. dynarrays 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, dynarrays should be explicitly destroyed,
   upon ceasing to be of any further use;
9. elements may be freely inserted, updated, or deleted, as long as their
   indices are within the dynarray's dimension bounds.
author
- GT Nunes
version
- 1.3.2
license
- BSD-3-Clause License */
   58%-------------------------------------------------------------------------------------
   59
   60:- meta_predicate dynarray_sort(+, 3).   61
   62:- use_module(library(lists),
   63    [
   64        nth1/3,
   65        reverse/2
   66    ]).   67
   68:- use_module('quicksort',
   69    [
   70        quicksort/3
   71    ]).   72
   73:- dynamic  dynarr_dims/3,
   74            dynarr_factors/3,
   75            dynarr_labels/3,
   76            dynarr_offsets/3,
   77            dynarr_tops/3,
   78            dynarr_values/3.   79
   80:- volatile dynarr_dims/3,
   81            dynarr_factors/3,
   82            dynarr_labels/3,
   83            dynarr_offsets/3,
   84            dynarr_tops/3,
   85            dynarr_values/3.   86
   87%-------------------------------------------------------------------------------------
 dynarray_create(+Id:atom, +DimRanges:list) is semidet
Create a dynarray. Multi-dimensional dynarrays must be constructed with dimension sizes as integers > 0, and in this case their indices are 0-based positive integers, smaller then the corresponding dimension size (0 <= IndexI < DimSizeI).

Alternatively, a range of indices may be specified for any of its dimensions, in the form of an integer pair Ii:If. These pairs may contain negative values, and, within a single pair, the interval markers may be expressed in any order. Internally, offsets compensate for the fact that linear positions of cells start at 0 (zero).

These are examples of valid dynarray creation requests:

  dynarray_create(a, [9,5,8])      - indices ranges: [0 : 8,0 : 4,0 : 7]<br/>
  dynarray_create(a, [3,5,3 : -8]) - indices ranges: [0 : 2,-8 : 3]<br/>
  dynarray_create(a, [3,19 : 4])   - indices ranges: [0 : 2,4 : 19]<br/>
  dynarray_create(a, [-4 : -3,7])  - indices ranges: [-4 : -3,0 : 6]
Arguments:
Id- Atom identifying the dynarray
DimRanges- List of dimension ranges in ascending dimension order
  113dynarray_create(Id, DimRanges) :-
  114
  115    % fail point (make sure id is an atom)
  116    atom(Id),
  117    % fail point (make sure id is not taken)
  118    \+ is_dynarray(Id),
  119
  120    % compute the dynarray's structure
  121    dynarray_dimensions(Id, DimRanges),
  122    dynarray_factors(Id, CellCount),
  123
  124    % register the dynarray's sizes and creation ranges
  125    length(DimRanges, DimCount),
  126    assertz(dynarr_labels(Id, da_cells, CellCount)),
  127    assertz(dynarr_labels(Id, da_dims, DimCount)),
  128    assertz(dynarr_labels(Id, da_ranges, DimRanges)).
  129
  130%-------------------------------------------------------------------------------------
 dynarray_destroy(+Id:atom) is det
Destroy dynarray Id, and release all of its resources. No action if it does not exist.
Arguments:
Id- atom identifying the dynarray
  139dynarray_destroy(Id) :-
  140
  141  retractall(dynarr_dims(Id, _, _)),
  142  retractall(dynarr_factors(Id, _, _)),
  143  retractall(dynarr_labels(Id, _, _)),
  144  retractall(dynarr_offsets(Id, _, _)),
  145  retractall(dynarr_tops(Id, _, _)),
  146  retractall(dynarr_values(_, Id, _)).
  147
  148%-------------------------------------------------------------------------------------
 is_dynarray(+Id:atom) is semidet
Fail if Id does not identify a dynarray.
Arguments:
Id- Atom identifying the dynarray
  156is_dynarray(Id) :-
  157    dynarr_dims(Id, 0, _).
 dynarray_version(-Version:number) is det
Unify Version with the current version of the dynarray implementation.
Arguments:
Version- Dynarray implementation's current version
  165dynarray_version(Version) :-
  166    Version = 1.32.
  167
  168%-------------------------------------------------------------------------------------
 dynarray_dims(+Id:atom, -DimCount:int) is det
Unify DimCount with the number of dimensions in the dynarray.
Arguments:
Id- Atom identifying the dynarray
DimCount- The number of dimensions in the dynarray
  177dynarray_dims(Id, DimCount) :-
  178    dynarr_labels(Id, da_dims, DimCount).
  179
  180%-------------------------------------------------------------------------------------
 dynarray_top(+Id:atom, +Dim:int, -Top:int) is semidet
Unify Top with the highest inserted index on the dimension Dim. This holds true even if this highest index has subsequently been deleted. Dimensions are 1-based integers, thus if Dim is specified as 0 (zero), unify Top with the list of the highest indices for all dimensions, instead. Upon dynarray's creation, this value is set to -1 for all dimensions.
Arguments:
Id- Atom identifying the dynarray
Dim- 1-based dimension ordinal, or 0 for all top indices
Top- Value of the highest index
  194dynarray_top(Id, Dim, Top) :-
  195
  196    % fail points
  197    Dim >= 0,
  198    dynarr_tops(Id, Dim, Top).
 dynarray_position_top(+Id:atom, -Top:int) is det
Unify Top with the highest inserted 0-based linear position. This holds true even if the element at this highest linear position has subsequently been deleted. Unify Top with -1 If no element has been inserted.
Arguments:
Id- Atom identifying the dynarray
Top- Value of the highest linear position
  209dynarray_position_top(Id, Top) :-
  210
  211    % obtain the offset-adjusted list of the highest 0-based indices used
  212    dynarr_tops(Id, 0, Tops),
  213    dynarray_offset(Id, Tops, TopsOffset),
  214
  215    % obtain the corresponding linear position
  216    dynarray_position_indices(Id, Top, TopsOffset).
  217
  218%-------------------------------------------------------------------------------------
 dynarray_cells(+Id:atom, -CellCount:int) is det
Unify CellCount with the number of cells in the dynarray.
Arguments:
Id- Atom identifying the dynarray
CellCount- The number of cells in the dynarray
  227dynarray_cells(Id, CellCount) :-
  228    dynarr_labels(Id, da_cells, CellCount).
 dynarray_cells(+Id:atom, +Dim:int, -CellCount:int) is semidet
Unify CellCount with the number of cells in the dimension Dim. The cell values are stored in the dynamic predicate dynarr_dims(Id, DimI, DimSizeI). For the special instance Dim0, this list of lists is stored:
[[DimSizeI,I],...,[DimSizeK,K]] (in ascending order by DimSizeI).
Arguments:
Id- Atom identifying the dynarray
Dim- The 1-based dynarray dimension
CellCount- The number of cells in the given dimension
  242dynarray_cells(Id, Dim, CellCount) :-
  243    dynarr_dims(Id, Dim, CellCount).
  244
  245%-------------------------------------------------------------------------------------
 dynarray_elements(+Id:atom, -ElementsCount:int) is det
Unify ElementsCount with the number of elements in the dynarray. This might be a very costly operation, as the elements are counted by fully traversing the dynarray space.
Arguments:
Id- Atom identifying the dynarray
ElementsCount- The number of elements in the dynarray
  256dynarray_elements(Id, ElementsCount) :-
  257
  258    % obtain the highest 0-based linear position in use
  259    dynarray_position_top(Id, LastPosition),
  260
  261    % count the elements, by traversing the dynarray space in reverse position order
  262    dynarray_elements_(Id, LastPosition, 0, ElementsCount).
  263
  264% (done)
  265dynarray_elements_(_Id, -1, CountFinal, CountFinal) :- !.
  266
  267% iterate
  268dynarray_elements_(Id, Position, CountProgress, CountFinal) :-
  269
  270    % is there an element at this position ?
  271    (dynarray_position_value(Id, Position, _) ->
  272        % yes, so increment the count
  273        CountRevised is CountProgress + 1
  274    ;
  275        % no, so proceed
  276        CountRevised = CountProgress
  277    ),
  278
  279    % go for the next position
  280    PositionNext is Position - 1,
  281    dynarray_elements_(Id, PositionNext, CountRevised, CountFinal).
  282
  283%-------------------------------------------------------------------------------------
 dynarray_value(+Id:atom, +Indices:list, ?Value:data) is semidet
Unify Value with the value of the dynarray cell at Indices.

Dynarrays may be sparsed, i.e., they may have cells not holding values, but attempts to retrieve the value of an empty cell will fail. Dynarray values are stored in the dynamic predicate dynarr_vaLues(Position, Id, Value).

Arguments:
Id- Atom identifying the dynarray
Indices- Indices identifying the element
Value- The dynarray cell value
  298dynarray_value(Id, Indices, Value) :-
  299
  300    % obtain corresponding linear position
  301    labels_indices(Id, Indices, Indexes),
  302    dynarray_position_indices(Id, Position, Indexes),
  303
  304    % has Value been grounded ?
  305    (ground(Value) ->
  306       % yes, so register value and top indices
  307       dynarray_value_(Id, Indexes, Position, Value)
  308    ;
  309       % no, so retrieve value
  310       !,
  311       % fail point (cell might be empty)
  312       dynarr_values(Position, Id, Value)
  313   ).
 dynarray_position_value(+Id:atom, +Position:int, ?Value:data) is semidet
Unify Value with the value of the cell at Position.

The dynarray may be sparsed, i.e., it may have cell not holding values, but attempts to retrieve value of an empty cell will fail.

Arguments:
Id- Atom identifying the dynarray
Position- Linear position identifying the cell
Value- The dynarray cell value
  326dynarray_position_value(Id, Position, Value) :-
  327
  328    % has Value been grounded ?
  329    (var(Value) ->
  330       % no, so retrieve value
  331       !,
  332       % fail point (cell might been empty)
  333       dynarr_values(Position, Id, Value)
  334    ;
  335       % yes, so register value and top indices
  336       dynarray_position_indices(Id, Position, Indices),
  337       dynarray_value_(Id, Indices, Position, Value)
  338    ).
 dynarray_value_(+Id:atom, +Indices:list, +Position:int, +Value:data) is semidet
Arguments:
Id- Atom identifying the dynarray
Indices- Indices identifying the element
Position- Linear position identifying the element
Value- The dynarray element value
  347dynarray_value_(Id, Indices, Position, Value) :-
  348
  349    % register value at position
  350    (retract(dynarr_values(Position, Id, _)) ; true),
  351    !,
  352    assertz(dynarr_values(Position, Id, Value)),
  353
  354    % register top indices
  355    dynarray_tops_register(Id, Indices).
  356
  357%-------------------------------------------------------------------------------------
 dynarray_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 dynarr_labels(Id, Label, Value).

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

  da_cells  - number of cells in the dynarray
  da_dims   - number of dimensions in the dynarray
  da_ranges - dimension ranges data used at the dynarray's creation
Arguments:
Id- Atom identifying the dynarray
Label- Atom standing for the named attribute
Value- Value associated with the named attribute
  376dynarray_label(Id, Label, Value) :-
  377
  378    ((ground(Label) , ground(Value)) ->
  379        % fail point (must be an atom, and must not start with 'da_')
  380        \+ sub_atom(Label, 0, 3, _, da_),
  381        (retract(dynarr_labels(Id, Label, _)) ; true),
  382        !,
  383        assertz(dynarr_labels(Id, Label, Value))
  384    ;
  385        % fail point
  386        dynarr_labels(Id, Label, Value)
  387    ).
  388
  389%-------------------------------------------------------------------------------------
 dynarray_find(+Id:atom, +Indices:list, -Value:data) is semidet
dynarray_find(+Id:atom, -Indices:list, +Value:data) is semidet
Unify Indices or Value with an occurrence of Indices or Value in the dynarray, respectively. Fail if no such value or indices exist.
Arguments:
Id- Atom identifying the dynarray
Indices- The reference indices
Value- The reference value
  401dynarray_find(Id, Indices, Value) :-
  402
  403    % are Indices fully specified ?
  404    (ground(Indices) ->
  405        % yes, so obtain linear position and retrieve value
  406        labels_indices(Id, Indices, Indexes),
  407        dynarray_position_indices(Id, Position, Indexes),
  408        dynarr_values(Position, Id, Value)
  409    ;
  410        % no, so obtain the Indices of the cell holding Value
  411        dynarr_values(Position, Id, Value),
  412        dynarray_position_indices(Id, Position, Indices)
  413    ).
 dynarray_position_find(+Id:atom, +Position:int, -Value:data) is semidet
dynarray_position_find(+Id:atom, -Position:int, +Value:data) is semidet
Unify Position or Value with an occurrence of Position or Value in the dynarray, respectively. Fail if no such value or position exists.
Arguments:
Id- atom identifying the dynarray
Position- the reference linear position
Value- the reference value
  425dynarray_position_find(Id, Position, Value) :-
  426    dynarr_values(Position, Id, Value).
  427
  428%-------------------------------------------------------------------------------------
 dynarray_tops_register(+Id:atom, +Indices:list) is det
Register maximum indices associated with non-empty cells.

The dynamic predicate dynarr_tops(Id, DimI, DimTopI) holds the corresponding values for the 1-based dimensions. The special instance Dim0 holds the list [DimTop1,...,DimTopN] (top values for all dimensions).

Arguments:
Id- Atom identifying the dynarray
Indices- Indices identifying the element
  441dynarray_tops_register(Id, Indices) :-
  442    dynarray_tops_register_(Id, 1, Indices, []).
  443
  444% (done)
  445dynarray_tops_register_(Id, _Dim, [], AllTops) :-
  446
  447    % register top indices for all dimensions
  448    reverse(AllTops, DimsTops),
  449    retract(dynarr_tops(Id, 0, _)),
  450    assertz(dynarr_tops(Id, 0, DimsTops)),
  451    !.
  452    
  453
  454% (iterate)
  455dynarray_tops_register_(Id, Dim, [Index|Indices], AllTops) :-
  456
  457    % obtain current top index for dimension
  458    dynarr_tops(Id, Dim, Top),
  459
  460    % update current top index for dimension, if applicable
  461    ( Top >= Index
  462    ; ( retract(dynarr_tops(Id, Dim, _))
  463      , assertz(dynarr_tops(Id, Dim, Index)) ) ),
  464    !,
  465
  466    % go for the next index
  467    DimNext is Dim + 1,
  468    TopIndex is max(Top, Index),
  469    dynarray_tops_register_(Id, DimNext, Indices, [TopIndex|AllTops]).
  470
  471%-------------------------------------------------------------------------------------
 dynarray_delete(+Id:atom, +Indices:list) is semidet
Erase the dynarray cell at Indices, releasing the storage space taken. Fail if no such cell exists.
Arguments:
Id- Atom identifying the dynarray
Indices- Indices identifying the cell
  481dynarray_delete(Id, Indices) :-
  482
  483    % determine the element's linear position
  484    labels_indices(Id, Indices, Indexes),
  485    dynarray_position_indices(Id, Position, Indexes),
  486
  487    % erase the cell
  488    !,
  489    % fail point (cell might already be empty)
  490    retract(dynarr_values(Position, Id, _)).
 dynarray_position_delete(+Id:atom, +Position:int) is semidet
Erase the dynarray cell at the given Position, releasing the storage space taken. Fail if no such cell exists.
Arguments:
Id- Atom identifying the dynarray
Position- Linear position identifying the cell
  500dynarray_position_delete(Id, Position) :-
  501    % fail point (cell might not exist)
  502    retract(dynarr_values(Position, Id, _)).
  503
  504%-------------------------------------------------------------------------------------
 dynarray_list(+Id:atom, ?List:list) is det
Unify List with the contents of the dynarray, or the cells of the dynarray with the values in List. The dynarray may be empty. If List is grounded, the dynarray is created or erased prior to the load operation.
A 1-dimension dynarray sized to hold all the list elements may be created. Note that this is not a serialization mechanism, and as such it should not be used for backup/restore purposes.
Arguments:
Id- Atom identifying the dynarray
List- List of values to unify the dynarray cells with
  518dynarray_list(Id, List) :-
  519
  520    % HAZARD: ground(List) might be very expensive
  521    (var(List) ->
  522        % load all values in dynarray into List
  523        findall(Value, dynarr_values(_Position, Id, Value), List)
  524    ;
  525        % does the dynarrays exist ?
  526        (is_dynarray(Id) ->
  527            % yes, so clear it
  528            retractall(dynarr_values(_, Id, _))
  529        ;
  530            % no, so create it
  531            length(List, Length),
  532            dynarray_create(Id, [Length])
  533        ),
  534
  535        % load the values in list
  536        list_to_dynarray_(List, Id, 0)
  537    ).
 list_to_dynarray_(+List:list, +Id:atom, +Position:int) is det
  541%  @param Value    The value to unify the dynarray cell with
  542%  @param Id       Atom identifying the dynarray
  543%  @param Position Linear position identifying the dynarray cell
  544
  545% (done)
  546list_to_dynarray_([], Id, Position) :-
  547
  548    % register the top index for each dimension
  549    (Position = 0 ->
  550       dynarr_values(Id, da_dims, Dims),
  551       list_repeat(Dims, [-1], Indices)
  552    ;
  553       Pos is Position - 1,
  554       dynarray_position_indices(Id, Pos, Indices)
  555    ),
  556    dynarray_tops_register(Id, Indices),
  557    !.
  558
  559% (iterate)
  560list_to_dynarray_([Value|List], Id, Position) :-
  561
  562    assertz(dynarr_values(Position, Id, Value)),
  563    PosNext is Position + 1,
  564    list_to_dynarray_(List, Id, PosNext).
  565
  566% (done)
  567list_repeat(1, ListFinal, ListFinal) :- !.
  568
  569% (iterate)
  570list_repeat(Count, [Elem|ListProgress], ListFinal) :-
  571
  572    CountNext is Count - 1,
  573    list_repeat(CountNext, [Elem|[Elem|[ListProgress]]], ListFinal).
  574
  575%-------------------------------------------------------------------------------------
 dynarray_sort(+Id:atom) is det
Numerically sort the contents of the dynarray, in ascending order. It must be possible to numerically compare any two elements stored in the dynarray. The dynarray indices are retrieved in dimension order, from the first dimension (left-most) to the last (right-most).
In the case of a sparse dynarray, the empty cells are ignored. Nothing is done if the dynarray 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
  590dynarray_sort(Id) :-
  591    dynarray_sort(Id, number_comparator).
  592
  593number_comparator(ValueX, ValueY, Cmp) :-
  594
  595    (ValueX < ValueY ->
  596        Cmp = -1
  597    ; ValueX > ValueY ->
  598        Cmp = 1
  599    ; otherwise ->
  600        Cmp = 0
  601    ).
 dynarray_sort(+Id:atom, :Comparator:pred) is det
Sort the contents of the dynarray according to the given comparison predicate. The dynarray indices are retrieved in dimension order, from the first dimension (left-most) to the last (right-most).
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 dynarray, the empty cells are ignored. Nothing is done if the dynarray 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
Comparator- Predicate to perform comparisons between two values
  629dynarray_sort(Id, Comparator) :-
  630
  631    % retrieve all values (position-value pairs) in dynarray
  632    findall([Posx,Val], dynarr_values(Posx, Id, Val), PositionsValues),
  633
  634    % does the dynarray contain more than one element ?
  635    length(PositionsValues, Count),
  636    (Count > 1 ->
  637        % yes, so sort its values using the given comparator
  638        pairs_to_lists(PositionsValues, [], Positions, [], Values),
  639        quicksort(Values, Comparator, SortedValues),
  640
  641        % backtrack until Positions is exausted
  642        nth1(Pos, Positions, Position),
  643        nth1(Pos, SortedValues, Value),
  644
  645        % replace the value at the cell
  646        retract(dynarr_values(Position, Id, _)),
  647        assertz(dynarr_values(Position, Id, Value)),
  648
  649        % fail point
  650        Pos = Count
  651    ;
  652        % no, so just exit
  653        true
  654    ).
  655
  656% (done)
  657pairs_to_lists([], Final1st, Final1st, Final2nd, Final2nd).
  658
  659% (iterate)
  660pairs_to_lists([[Element1st,Element2nd]|Pairs],
  661              Progress1st, Final1st, Progress2nd, Final2nd) :-
  662    pairs_to_lists(Pairs, [Element1st|Progress1st], Final1st,
  663                   [Element2nd|Progress2nd], Final2nd).
  664
  665%-------------------------------------------------------------------------------------
 dynarray_fill(+Id:atom, +Value:data) is det
Unify all the cells of the dynarray with Value.
Arguments:
Id- Atom identifying the dynarray
Value- Value to unify the dynarray cells with
  674dynarray_fill(Id, Value) :-
  675
  676    retractall(dynarr_values(_, Id, _)),
  677    dynarr_labels(Id, da_cells, CellCount),
  678    dynarray_fill_(Id, Value, 0, CellCount).
 dynarray_fill_(+Id:atom, +Value, +Position:int) is det
Arguments:
Id- Atom identifying the dynarray
Value- Value to unify the dynarray cell with
Position- 0-based linear position identifying the dynarray cell
CellCount- Number of cells in dynarray
  687% (done)
  688dynarray_fill_(_Id, _Value, CellCount, CellCount) :- !.
  689
  690% (iterate)
  691dynarray_fill_(Id, Value, Position, CellCount) :-
  692
  693    assertz(dynarr_values(Position, Id, Value)),
  694    PosNext is Position + 1,
  695    dynarray_fill_(Id, Value, PosNext, CellCount).
  696
  697%-------------------------------------------------------------------------------------
 dynarray_dimensions(+Id:atom, +DimRanges:list) is det
Initialize the dynarray by ackowledging its dimensions. The dynamic predicate dynarr_offsets(Id, DimI, DimOffsetI) holds the offsets for the 1-based dynarray dimensions. The special instance Dim0 holds the list [DimOffset1,...,DimOffsetN] (offset values for all dimensions).
Arguments:
Id- Atom identifying the dynarray
DimRanges- List holding the dynarray dimension ranges
  709dynarray_dimensions(Id, DimRanges) :-
  710
  711    % register the dynarray dimension offsets, sizes, and top indices
  712    dynarray_dimensions_(Id, 1, DimRanges, [], [], []).
 dynarray_dimensions_(+Id:atom, +Dim:int, +DimRanges:list, +DimOffsets:list, +DimTops:list, -DimsSizes:list) is det
Arguments:
Id- Atom identifying the dynarray
Dim- The 1-based dynarray dimension
DimRanges- Range of indices of dimension Dim
DimTops- List of dimensions' top indices ([Top1,...,TopN])
DimOffsets- Dimensions' indices offsets ([Offset1,...,OffsetN])
DimsSizes- List of dimensions and its sizes ([[DimSz1,1],...,[DimSzN,N]])
  723% (done)
  724dynarray_dimensions_(Id, _Dim, [], DimOffsets, DimTops, DimsSizes) :-
  725    
  726    % register the initial values for the dimensions' top indices
  727    assertz(dynarr_tops(Id, 0, DimTops)),
  728
  729    % the dynarr_offsets 0 position will hold the dimension indices offsets
  730    reverse(DimOffsets, Offsets),
  731    assertz(dynarr_offsets(Id, 0, Offsets)),
  732
  733    % the dynarr_dims 0 position will hold the dimension sizes list of lists:
  734    %   [[DimSizeI,I],...,[DimSizeK,K]] - ordered by dim_size
  735    sort(DimsSizes, DimsSorted),
  736    assertz(dynarr_dims(Id, 0, DimsSorted)),
  737    !.
  738
  739% (iterate)
  740dynarray_dimensions_(Id, Dim, [DimRange|DimRanges],
  741                     DimOffsets, DimTops, DimsSizes) :-
  742
  743    (Ii:If = DimRange ->
  744        % fail points
  745        integer(Ii),
  746        integer(If)
  747    ;
  748       % fail points
  749       integer(DimRange),
  750       DimRange > 0,
  751
  752       Ii = 0,
  753       If is DimRange - 1
  754    ),
  755
  756    % register the dimension's size information
  757    Size is abs(If - Ii) + 1,
  758    assertz(dynarr_dims(Id, Dim, Size)),
  759
  760    % register the dimension's initial top index value
  761    assertz(dynarr_tops(Id, Dim, -1)),
  762
  763    % register the dimension's index offset information
  764    Offset is min(Ii, If),
  765    assertz(dynarr_offsets(Id, Dim, Offset)),
  766
  767    % go for the next dimension
  768    DimNext is Dim + 1,
  769    dynarray_dimensions_(Id, DimNext, DimRanges, [Offset|DimOffsets],
  770                         [-1|DimTops], [[Size,Dim]|DimsSizes]).
  771
  772%-------------------------------------------------------------------------------------
 dynarray_factors(+Id:atom, -CellCount) is det
Obtain the number of cells in the dynarray, and its compound factors. Compound factors are used for mapping between indices and linear positions. The dynamic predicate dynarr_factors(Id, DimI, DimFactorI) holds the factors for the 1-based dimensions. The special instance Dim0 holds the list [DimFactor1,...,DimFactorN] (the factor values for all dimensions).

These facts hold for a 4-dimension dynarray:

(a)
DimSizeW <= DimSizeX <= DimSizeY <= DimSizeZ

(b)
FactorW = DimSizeX * DimSizeY * DimSizeZ
FactorX = DimSizeY * DimSizeZ
FactorY = DimSizeZ
FactorZ = 1

(c)
Indices (W,X,Y,Z) -> Linear position:
Pos = FactorW * W + FactorX * X + FactorY * Y + FactorZ * Z

(d)
Linear position -> Indices (W,X,Y,Z):
W    = div(Pos, FactorW)
RemW = mod(Pos, FactorW)
X    = div(RemW, FactorX)
RemX = mod(RemW, FactorX)
Y    = div(RemX, FactorY)
RemY = mod(RemX, FactorY)
Z    = div(RemY, FactorZ) -> FactorZ = 1, Z = RemY
Arguments:
Id- Atom identifying the dynarray
CellCount- Number of cells in dynarray
  811dynarray_factors(Id, CellCount) :-
  812
  813    dynarr_dims(Id, 0, DimsSizes),
  814    length(DimsSizes, DimCount),
  815    dynarray_factors_(Id, DimCount, DimCount, 1,
  816                      DimsSizes, 1, CellCount, [], DimFactors),
  817
  818    % the dynarr_factors 0 position holds the dimension factors:
  819    % [DimFactor1,...,DimFactorN]
  820    assertz(dynarr_factors(Id, 0, DimFactors)).
 dynarray_factors_(+Id:atom, +DimOrdinal:int, +DimCount:int, +CompoundFactor:int, +DimsSizes:list, +CountProgress:list, -CountFinal:list, +FactorsProgress:list, -FactorsFinal:list) is det
Arguments:
Id- Atom identifying the dynarray
DimOrdinal- Size-based position for dynarray dimension
DimCount- Number of dynarray dimensions
CompoundFactor- Current compound factor
DimsSizes- List of dimensions and its sizes param CountProgress Working number of dynarray cells
CountFinal- Final number of dynarray cells
FactorsProgress- The working dimension factors
FactorsFinal- The final dimension factors
  834% (done)
  835dynarray_factors_(_Id, 0, _DimCount, _CompoundFactor, _DimsSizes,
  836                  CountFinal, CountFinal, FactorsProgress, FactorsFinal) :-
  837    sort(FactorsProgress, FactorsFinal), !.
  838
  839% (iterate)
  840dynarray_factors_(Id, DimOrdinal, DimCount, CompoundFactor, DimsSizes,
  841                  CountProgress, CountFinal, FactorsProgress, FactorsFinal) :-
  842
  843    nth1(DimOrdinal, DimsSizes, [DimSize,Dim]),
  844    (DimOrdinal = DimCount ->
  845       % factor for dimension with the largest size is 1
  846       DimFactor = 1
  847    ;
  848       % factor for current dimension is size of next larger dimension
  849       DimAdjusted is DimOrdinal + 1,
  850       nth1(DimAdjusted, DimsSizes, [DimFactor,_])
  851    ),
  852
  853    CountRevised is DimSize * CountProgress,
  854    Factor is DimFactor * CompoundFactor,
  855
  856    % register the dimension's index factor
  857    assertz(dynarr_factors(Id, Dim, Factor)),
  858
  859    % go for the next dimension
  860    OrdinalNext is DimOrdinal - 1,
  861    dynarray_factors_(Id, OrdinalNext, DimCount, Factor,
  862                      DimsSizes, CountRevised, CountFinal,
  863                      [Factor|FactorsProgress], FactorsFinal).
  864
  865%-------------------------------------------------------------------------------------
 dynarray_position_indices(+Id:atom, +Position:int, -Indices:list) is semidet
dynarray_position_indices(+Id:atom, -Position:int, +Indices:list) is semidet
Unify Position or Indices with the corresponding Position or Indices, respectively.
Arguments:
Id- Atom identifying the dynarray
Position- The final 0-based linear position of the element
Indices- The element's indices (offset-corrected, if applicable)
  877dynarray_position_indices(Id, Position, Indices) :-
  878
  879    (ground(Position) ->
  880        % fail point
  881        Position >= 0,
  882        dynarr_dims(Id, 0, DimsSizes),
  883        position_indices_1(Id, Position, DimsSizes, [], IndicesOffset),
  884        dynarray_offset(Id, Indices, IndicesOffset)
  885    ;
  886        labels_indices(Id, Indices, Indexes),
  887        dynarray_offset(Id, Indexes, IndicesOffset),
  888        dynarr_labels(Id, da_dims, DimCount),
  889        indices_position_(Id, IndicesOffset, DimCount, 0, Position)
  890    ).
 indices_position_(+Id:atom, +Indices:list, +Dim:int, +PosProgress:int, -PosFinal:int) is semidet
Obtain the element's linear position from its indices.</br> Pos = Factor1 * I1 + Factor2 * I2 + ... + FactorN * In (FactorN = 1)
Arguments:
Id- Atom identifying the dynarray
Indices- The element's indices
Dim- The 1-based dynarray dimension
PosProgress- The working linear position of the cell
PosFinal- The final linear position of the cell
  903% (done)
  904indices_position_(_Id, _Indices, 0, PosFinal, PosFinal) :- !.
  905
  906% (iterate)
  907indices_position_(Id, Indices, Dim, PosProgress, PosFinal) :-
  908
  909    % fail points
  910    nth1(Dim, Indices, Index),
  911    Index >= 0,
  912    dynarr_dims(Id, Dim, DimSize),
  913    Index < DimSize,
  914
  915    dynarr_factors(Id, Dim, DimFactor),
  916    PosRevised is PosProgress + DimFactor * Index,
  917    DimNext is Dim - 1,
  918    indices_position_(Id, Indices, DimNext, PosRevised, PosFinal).
 position_indices_1(+Id:atom, +Factor:int, +Dim:int, +IndicesProgress:list, -IndicesFinal:list) is semidet
Obtain the element's indices from its linear position.
Size1 <= Size2 <= ... <= SizeN

I1     = div(Pos, Factor1)
Rem1   = mod(Pos, Factor1)
I2     = div(Rem1, Factor2)
Rem2   = mod(Rem1, Factor2)
:                :
:                :
In-1   = div(RemN-2, FactorN-1)
RemN-1 = mod(RemN-2, FactorN-1)
In     = div(RemN-1, FactorN) -> In = RemN-1
Arguments:
Id- Atom identifying the dynarray
Position- The element's 0-based linear position
DimsSizes- The dimensions and their corresponding sizes
IndicesProgress- The working indices of the element
IndicesFinal- The final indices of the element
  943% (done)
  944position_indices_1(_Id, _Pos, [], IndicesProgress, IndicesFinal) :-
  945
  946    % IndicesProgress is [[DimI,IndexI],...[DimK,IndexK]], unsorted
  947    % IndicesSorted is [[Dim1,Index1],...[DimN,IndexN]], ascending order by Dim
  948    sort(IndicesProgress, IndicesSorted),
  949 
  950    % IndicesFinal has the indices in proper order: [Index1,...,IndexN]
  951    position_indices_2(IndicesSorted, [], IndicesFinal),
  952    !.
  953
  954% (iterate)
  955position_indices_1(Id, Position, [[_,Dim]|DimsSizes],
  956                   IndicesProgress, IndicesFinal) :-
  957
  958    dynarr_factors(Id, Dim, DimFactor),
  959    Index is div(Position, DimFactor),
  960    Remainder is mod(Position, DimFactor),
  961    position_indices_1(Id, Remainder, DimsSizes,
  962                       [[Dim,Index]|IndicesProgress], IndicesFinal).
  963
  964% morph list of lists with dimensions and indices in the format
  965%   [[Dim1,Index1],...,[DimN,IndexN]]
  966% into a simple list of indices in the format
  967%   [Index1,...,IndexN]
  968
  969% (done)
  970position_indices_2([], IndicesProgress, IndicesFinal) :-
  971    reverse(IndicesProgress, IndicesFinal), !.
  972
  973% (iterate)
  974position_indices_2([[_,Index]|DimsIndices], IndicesProgress, IndicesFinal) :-
  975    position_indices_2(DimsIndices, [Index|IndicesProgress], IndicesFinal).
  976
  977%-------------------------------------------------------------------------------------
 dynarray_offset(+Id:atom, +Indices:list, -OffsetIndices:list) is det
dynarray_offset(+Id:atom, -Indices:list, +OffsetIndices:list) is det
Unify Indices and OffsetIndices with the corresponding real indices and offset indices, respectively.
Arguments:
Id- Atom identifying the dynarray
Indices- The dynarray cell's indices
OffsetIndices- The dynarray cell's offset indices
  989dynarray_offset(Id, Indices, OffsetIndices) :-
  990
  991    (ground(Indices) ->
  992        indices_offsets_(Id, 1, Indices, [], OffsetIndices)
  993    ;
  994        offsets_indices_(Id, 1, OffsetIndices, [], Indices)
  995    ).
 indices_offsets_(+Id:atom, +Dim:int, +Indices:list, +OffsetsProgress:list, -OffsetsFinal:list) is det
Convert real indices into offset indices.
Arguments:
Id- Atom identifying the dynarray
Dim- The current dynarray dimension
Indices- The dynarray cell's real indices
OffsetsProgress- The working dynarray cell's offset indices
OffsetsFinal- The final dynarray cell's offset indices
 1007% (done)
 1008indices_offsets_(_Id, _Dim, [], OffsetsProgress, OffsetsFinal) :-
 1009    reverse(OffsetsProgress, OffsetsFinal), !.
 1010
 1011% (iterate)
 1012indices_offsets_(Id, Dim, [Index|Indices], OffsetsProgress, OffsetsFinal) :-
 1013
 1014    % adjust index with the offset for the given dim
 1015    dynarr_offsets(Id, Dim, Offset),
 1016    OffsetIndex is Index - Offset,
 1017
 1018    % go for next dim
 1019    DimNext is Dim + 1,
 1020    indices_offsets_(Id, DimNext, Indices,
 1021                     [OffsetIndex|OffsetsProgress], OffsetsFinal).
 offsets_indices_(+Id:atom, +Dim:int, +OffsetIndices:list, +IndicesProgress:list, -IndicesFinal:list) is det
Convert offset indices into real indices.
Arguments:
Id- Atom identifying the dynarray
Dim- The current dynarray dimension
OffsetIndices- The dynarray cell's offset indices
IndicesProgress- The working dynarray cell's real indices
IndicesFinal- The final dynarray cell's real indices
 1033% (done)
 1034offsets_indices_(_Id, _Dim, [], IndicesProgress, IndicesFinal) :-
 1035    reverse(IndicesProgress, IndicesFinal), !.
 1036
 1037% (iterate)
 1038offsets_indices_(Id, Dim, [OffsetIndex|OffsetIndices],
 1039                 IndicesProgress, IndicesFinal) :-
 1040
 1041    % adjust index with the offset for the given dim
 1042    dynarr_offsets(Id, Dim, Offset),
 1043    Index is OffsetIndex + Offset,
 1044
 1045    % go for the next dim
 1046    DimNext is Dim + 1,
 1047    offsets_indices_(Id, DimNext, OffsetIndices,
 1048                     [Index|IndicesProgress], IndicesFinal).
 1049
 1050%-------------------------------------------------------------------------------------
 labels_indices(+Id:atom, +Labels:list, -Indices:list) is semidet
Unify Indices with a list of integers obtained from Labels.
Arguments:
Id- Atom identifying the dynarray
Labels- List of indices possibly containing atoms
Indices- List with corresponding integer values
 1060labels_indices(Id, Labels, Indices) :-
 1061    labels_indices_(Id, Labels, [], Indices).
 1062
 1063% (done)
 1064labels_indices_(_Id, [], IndicesProgress, IndicesFinal) :-
 1065    reverse(IndicesProgress, IndicesFinal), !.
 1066
 1067% (iterate)
 1068labels_indices_(Id, [Label|Labels], IndicesProgress, IndicesFinal) :-
 1069
 1070    (atom(Label) ->
 1071        dynarr_labels(Id, Label, Index)
 1072    ;
 1073        Index = Label
 1074    ),
 1075
 1076    % go for the next label
 1077    labels_indices_(Id, Labels, [Index|IndicesProgress], IndicesFinal)