Preparing 5.6.56
[chr.git] / chr_integertable_store.pl
blob1a9b0e0715fb477338a9cca945c8d5cde227384e
1 /* $Id$
3 Part of CHR (Constraint Handling Rules)
5 based on chr_hashtable_store (by Tom Schrijvers)
6 Author: Jon Sneyers
7 E-mail: Jon.Sneyers@cs.kuleuven.be
8 WWW: http://www.swi-prolog.org
9 Copyright (C): 2005, K.U. Leuven
11 This program is free software; you can redistribute it and/or
12 modify it under the terms of the GNU General Public License
13 as published by the Free Software Foundation; either version 2
14 of the License, or (at your option) any later version.
16 This program is distributed in the hope that it will be useful,
17 but WITHOUT ANY WARRANTY; without even the implied warranty of
18 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
19 GNU General Public License for more details.
21 You should have received a copy of the GNU Lesser General Public
22 License along with this library; if not, write to the Free Software
23 Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
25 As a special exception, if you link this library with other files,
26 compiled with a Free Software compiler, to produce an executable, this
27 library does not by itself cause the resulting executable to be covered
28 by the GNU General Public License. This exception does not however
29 invalidate any other reasons why the executable file might be covered by
30 the GNU General Public License.
33 % is it safe to use nb_setarg here?
35 :- module(chr_integertable_store,
36 [ new_iht/1,
37 lookup_iht/3,
38 insert_iht/3,
39 delete_iht/3,
40 value_iht/2
41 ]).
42 :- use_module(library(lists)).
43 :- use_module(hprolog).
45 %initial_capacity(65536).
46 %initial_capacity(1024).
47 initial_capacity(8).
48 %initial_capacity(2).
49 %initial_capacity(1).
52 new_iht(HT) :-
53 initial_capacity(Capacity),
54 new_iht(Capacity,HT).
56 new_iht(Capacity,HT) :-
57 functor(T1,t,Capacity),
58 HT = ht(Capacity,Table),
59 Table = T1.
61 lookup_iht(ht(_,Table),Int,Values) :-
62 Index is Int + 1,
63 arg(Index,Table,Values),
64 Values \= [].
65 % nonvar(Values).
67 insert_iht(HT,Int,Value) :-
68 Index is Int + 1,
69 arg(2,HT,Table),
70 (arg(Index,Table,Bucket) ->
71 ( var(Bucket) ->
72 Bucket = [Value]
74 setarg(Index,Table,[Value|Bucket])
76 ; % index > capacity
77 Capacity is 1<<ceil(log(Index)/log(2)),
78 expand_iht(HT,Capacity),
79 insert_iht(HT,Int,Value)
82 delete_iht(ht(_,Table),Int,Value) :-
83 % arg(2,HT,Table),
84 Index is Int + 1,
85 arg(Index,Table,Bucket),
86 ( Bucket = [_Value] ->
87 setarg(Index,Table,[])
89 delete_first_fail(Bucket,Value,NBucket),
90 setarg(Index,Table,NBucket)
92 %delete_first_fail([], Y, []).
93 %delete_first_fail([_], _, []) :- !.
94 delete_first_fail([X | Xs], Y, Xs) :-
95 X == Y, !.
96 delete_first_fail([X | Xs], Y, [X | Zs]) :-
97 delete_first_fail(Xs, Y, Zs).
99 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
100 value_iht(HT,Value) :-
101 HT = ht(Capacity,Table),
102 value_iht(1,Capacity,Table,Value).
104 value_iht(I,N,Table,Value) :-
105 I =< N,
106 arg(I,Table,Bucket),
108 nonvar(Bucket),
109 member(Value,Bucket)
111 J is I + 1,
112 value_iht(J,N,Table,Value)
115 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
117 expand_iht(HT,NewCapacity) :-
118 HT = ht(Capacity,Table),
119 functor(NewTable,t,NewCapacity),
120 setarg(1,HT,NewCapacity),
121 setarg(2,HT,NewTable),
122 expand_copy(Table,1,Capacity,NewTable,NewCapacity).
124 expand_copy(Table,I,N,NewTable,NewCapacity) :-
125 ( I > N ->
126 true
128 arg(I,Table,Bucket),
129 ( var(Bucket) ->
130 true
132 arg(I,NewTable,Bucket)
134 J is I + 1,
135 expand_copy(Table,J,N,NewTable,NewCapacity)