34
35:- module(nb_set,
36 [ empty_nb_set/1, 37 add_nb_set/2, 38 add_nb_set/3, 39 gen_nb_set/2, 40 size_nb_set/2, 41 nb_set_to_list/2 42 ]). 43:- use_module(library(lists)). 44:- use_module(library(terms)). 45:- use_module(library(apply_macros), []).
62initial_size(32).
68empty_nb_set(nb_set(Buckets, 0)) :-
69 initial_size(Size),
70 '$filled_array'(Buckets, buckets, Size, []).
85add_nb_set(Key, Set) :-
86 add_nb_set(Key, Set, _).
87add_nb_set(Key, Set, New) :-
88 arg(1, Set, Buckets),
89 compound_name_arity(Buckets, _, BCount),
90 hash_key(Key, BCount, Hash),
91 arg(Hash, Buckets, Bucket),
92 ( member(X, Bucket),
93 Key =@= X
94 -> New = false
95 ; New = true,
96 duplicate_term(Key, Copy),
97 nb_linkarg(Hash, Buckets, [Copy|Bucket]),
98 arg(2, Set, Size0),
99 Size is Size0+1,
100 nb_setarg(2, Set, Size),
101 ( Size > BCount
102 -> rehash(Set)
103 ; true
104 )
105 ).
114:- if(catch((A = f(A), variant_hash(A,_)), error(type_error(_,_),_), fail)). 115hash_key(Term, BCount, Key) :-
116 variant_hash(Term, IntHash),
117 Key is (IntHash mod BCount)+1.
118:- else. 119hash_key(Term, BCount, Key) :-
120 acyclic_term(Key),
121 !,
122 variant_hash(Term, IntHash),
123 Key is (IntHash mod BCount)+1.
124hash_key(Term, BCount, Key) :-
125 term_factorized(Term, Skeleton, Substiution),
126 variant_hash(Skeleton+Substiution, IntHash),
127 Key is (IntHash mod BCount)+1.
128:- endif. 129
130rehash(Set) :-
131 arg(1, Set, Buckets0),
132 compound_name_arity(Buckets0, Name, Arity0),
133 Arity is Arity0*2,
134 '$filled_array'(Buckets, Name, Arity, []),
135 nb_setarg(1, Set, Buckets),
136 nb_setarg(2, Set, 0),
137 forall(( arg(_, Buckets0, Chain),
138 member(Key, Chain)
139 ),
140 add_nb_set(Key, Set, _)).
147nb_set_to_list(nb_set(Buckets, _Size), OrdSet) :-
148 compound_name_arguments(Buckets, _, Args),
149 append(Args, List),
150 sort(List, OrdSet).
156gen_nb_set(Set, Key) :-
157 nb_set_to_list(Set, OrdSet),
158 member(Key, OrdSet).
164size_nb_set(nb_set(_, Size), Size)
Non-backtrackable sets
This library provides a non-backtrackabe set of terms that are variants of each other. It is primarily intended to implement distinct/1 from
library(solution_sequences)
. The set is implemented as a hash table that is built using non-backtrackable primitives, notably nb_setarg/3.The original version of this library used binary trees which provides immediate ordering. As the trees were not balanced, performance could get really poor. The complexity of balancing trees using non-backtrackable primitives is too high.