Did you know ... Search Documentation:
Pack modeling -- prolog/arrays.pl
PublicShow source
author
- Francois Fages
version
- 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] functional notation defined here using multifile shorthand/3 predicate of library(comprehension) can be used 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).
 array(+Term)
tests whether a given term is an array without checking multidimensional consistency.
 array(?Array, ?DimensionList)
Array is an array of dimension DimensionList. Either creates an array of given dimensions greater or equal to 1, or returns the dimensions of a given array, or enumerates single dimension arrays.
 cell(+Array, +Indices, ?Cell)
Cell is the Array cell at given Indices (list of indices for a multidimensional array). Throws an error if the indices are out of range. Shorthand expressions in Indices are evaluated.
 cell(+ArrayIndices, ?Cell)
Just a shorthand for cell(Array, Indices, Cell) for ArrayIndices of the shorthand/3 form Array[Indices]
 array_list(?Array, ?List)
List is the flat list of the array cells with lexicographically ordered indices. Either creates the List or a one dimensional Array indexed by integers starting from 1. For a one dimensional array, there is no difference with array_lists/2.
 array_lists(+Array, ?List)
List is the list (of lists in the case of a multidimensional array) of the array cells with lexicographically ordered indices. Either creates the lists or the array indexed by integers in intervals starting from 1. For a one dimensional array, there is no difference with array_list/2.
 set_cell(+Array, +Indices, ?Term)
backtrackable assignment of Term to either simple array cell or all subarray cells at given indices. Shorthand expressions in Indices are evaluated.
 set_cell(+ArrayIndices, ?Cell)
Just a shorthand for set_cell(Array, Indices, Cell) for ArrayIndices of the shorthand/3 form Array[Indices]
 nb_set_cell(+Array, +Indices, ?Term)
backtrackable assignment of Term to either simple array cell or all subarray cells at given indices. Shorthand expressions in Indices are evaluated.
 nb_set_cell(+ArrayIndices, ?Cell)
Just a shorthand for nb_set_cell(Array, Indices, Cell) for ArrayIndices of the shorthand/3 form Array[Indices]

Undocumented predicates

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

 for_all(Arg1, Arg2)
 list_of(Arg1, Arg2, Arg3)
 aggregate_for(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6)
 exists(Arg1, Arg2)
 let(Arg1, Arg2)
 apply_list(Arg1, Arg2)
 call_list(Arg1, Arg2)
 call_list(Arg1, Arg2, Arg3)
 call_list(Arg1, Arg2, Arg3, Arg4)
 call_list(Arg1, Arg2, Arg3, Arg4, Arg5)
 call_list(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6)