- 1.1.3
This module provides an implementation of multidimensional arrays by terms.
The array indices are integers starting at 1 and the dimension of an array is a list of integers.
array_list/2 (resp. array_lists/2) makes conversions between an array and a list (resp. of lists for multi-dimensional arrays), which can be used to initialize an array to a list of values.
?- array_lists(A, [[1, 2, 3], [4, 5, 6]]), array(A, Dim).
A = array(array(1, 2, 3), array(4, 5, 6)),
Dim = [2, 3].
Array cells are accessed by unification with predicate cell/3.
This module includes module comprehension.pl
for bounded quantification and is compatible with attributed variables,
clpfd and clpr libraries for creating arrays of constrained variables, and posting constraints on subscripted variables.
Array cells can also be modified by destructive assignment, backtrackable or not, with set_cell/3 and nb_set_cell/3.
?- array(A, [3]), cell(A, [2], v).
A = array(_, v, _).
?- array(A, [2, 3]), cell(A, [2,2], 3).
A = array(array(_, _, _), array(_, 3, _)).
?- array(A, [2, 3]), cell(A, [2], X).
A = array(array(_, _, _), array(_A, _B, _C)),
X = array(_A, _B, _C).
?- array_list(A, [2,3,4]), let([I=A[1],V=A[I]], writeln(a(I,V))).
a(2,3)
A = array(2, 3, 4).
?- array(A, [2, 3]), (set_cell(A, [1], 9) ; nb_set_cell(A, [2], 5); set_cell(A, [2,2],8)).
A = array(array(9, 9, 9), array(_, _, _)) ;
A = array(array(_, _, _), array(5, 5, 5)) ;
A = array(array(_, _, _), array(5, 8, 5)).
Array[Indices], or cell(Array, Indices)
functional notations defined here using multifile shorthand/3 predicate of library(comprehension)
are automatically expanded in "in" and "where" conditions of comprehension metapredicates and in constraints of library(clp)
.
?- array(A, [5]), for_all([I in 1..5], A[I] #= I).
A = array(1, 2, 3, 4, 5).