% Simple array storage % Ken Johnson, 16-4-1990. You may copy and distribute this code % freely but if you sell copies at a profit then I want a share. % % This routine gives constant time storage and retrieval. Although % the constant time is fairly high, you may still find it interesting % and useful for very large arrays. % % Note: there is no check that arrays are not being redeclared nor % redimensioned, though this could be added readily. % % The test shows how to use the routines. The invocation of `array' % stores the characters of the array name as a difference list. % There is subscript bounds checking. Delete the lines indicated and % the predicates array/3, check_bounds/2 if you DON'T want it. test :- array(x), % create array x, no subscript checking array(y,1,5), % create array y, elements y[1]...y[5] inclusive put(x,1,foo), % store at elem 1 of x put(y,2,bar), get(x,1,X1), write(X1), nl, % get from elem 1 of x get(y,2,Y2), write(Y2), nl, get(y,101,_), % fails here as 101 is out of bounds put(y,-1,wub). % also fails -- delete line above to see it not work % ``Declare'' an array. This stores the characters of the name of the array % as a difference list, so it only needs to be computed once. % Mode: array(+) % Array: Any atom array(Array) :- name(Array,Array_chars), difference(Array_chars,Ac-X), record(Array,Ac-X,_). % This routine declares a simple bounds term. Subsequent attempts to % store in the array will fail with a message if the subscript is out % of bounds. % Mode array(+,+,+) % Array: as above; Low, High: positive integers array(Array,Low,High) :- Low =< High, % just in case array(Array), record(Array,bounds(Low,High),_). % To store or retrieve, work out the correct recorded term key, then % remove anything already stored there; then store the new item. % Mode put(+,+,+). % Array: any atom declared by array/1 or array/3 % N: positive integer subscript % Term: anything put(Array,N,Term) :- check_bounds(Array,N), % <-- delete this if not required get_key(Array,N,R_key), ( recorded(R_key,_,Ref) -> erase(Ref) ; true ), record(R_key,Term,_). % Mode get(+,+,?) % arguments as for `put' get(Array,N,Term) :- check_bounds(Array,N), % <-- delete this if not required get_key(Array,N,R_key), recorded(R_key,Term,_). % The ``key'' for element 5 in array `x' is `x5'. This uses the % difference list stored by ``array'' to generate the required atom % Mode get_key(+,+,?) % Array: any atom but must have been declared by ``array''; % N: positive integer % R_key: an atom get_key(Array,N,R_key) :- recorded(Array,Ac-Nc,_), name(N,Nc), name(R_key,Ac). % Convert ordinary list to a difference list % Mode difference(+,-) difference([],X-X). difference([H|T],[H|X]-Y) :- difference(T,X-Y). % Check subscript is in range. (This predicate is optional! If you % delete it, delete the two calls to it. array/3 will also become % redundant.) % Mode check_bounds(+,+) % Array: any atom declared as an array name with array/1 or array/3. % N: positive integer subscript check_bounds(Array,_) :- \+ recorded(Array,bounds(_,_),_). check_bounds(Array,N) :- recorded(Array,bounds(Low,High),_), N >= Low, N =< High. check_bounds(Array,N) :- recorded(Array,bounds(Low,High),_), ( N < Low ; N > High ), telling(Output), tell(user), nl, write('*** Subscript error: '), nl, write(Array), write('['), write(N), write('] does not exist. Bounds are: '), write(Low), write(', '), write(High), nl, tell(Output), fail.