1% BEGIN LICENSE BLOCK
2% Version: CMPL 1.1
3%
4% The contents of this file are subject to the Cisco-style Mozilla Public
5% License Version 1.1 (the "License"); you may not use this file except
6% in compliance with the License.  You may obtain a copy of the License
7% at www.eclipse-clp.org/license.
8%
9% Software distributed under the License is distributed on an "AS IS"
10% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied.  See
11% the License for the specific language governing rights and limitations
12% under the License.
13%
14% The Original Code is  The ECLiPSe Constraint Logic Programming System.
15% The Initial Developer of the Original Code is  Cisco Systems, Inc.
16% Portions created by the Initial Developer are
17% Copyright (C) 1995-2006 Cisco Systems, Inc.  All Rights Reserved.
18%
19% Contributor(s): Carmen Gervet and Pascal Brisset, ECRC.
20%
21% END LICENSE BLOCK
22
23%----------------------------------------------------------------------
24:- module(set).
25%----------------------------------------------------------------------
26
27:- reexport(s_lists).
28
29:- export
30	op(700, xfx, `<>),
31	op(700, xfx, `=),
32	op(700, xfx, in),
33	op(700, xfx, notin),
34	op(700, xfx, `::),
35	op(700, xfx, `<),
36	op(500, yfx, \),
37
38	op(700, xfy, dis_s),     /* disjoint       */
39	op(700, xfy, in_s),      /* membership     */
40	op(700, xfy, nin_s),     /* non membership */
41	op(650, xfx, def_s),     /* set def        */
42	op(700, xfy, sub_s),     /* subset         */
43	op(650, xfx, glb),
44	op(650, xfx, lub).
45
46:- export
47	(`<>) /2,
48	(`=) /2 ,
49	(in) /2,
50	(notin) /2,
51	(`::) /2,
52	(`<) /2,
53	(#) /2,
54	sum_weight/2,
55	def_s /2,
56	car_s /2,
57	weight_s/2,
58	dis_s /2,
59	in_s /2,
60	nin_s /2,
61	sub_s /2,
62	included/2,
63	 set_range/3,
64	glb/2,
65	lub/2,
66	union_s/3,
67	all_union/2,
68	inter_s/3,
69	all_disjoint/1,
70	diff_s/3,
71	tr_set/2,
72	svar_attribute/2,
73	el_weight/2,
74	max_weight/2,
75	refine/1,
76	par_refine/1,
77	modify_bound/3.
78
79
80:- export struct( set(
81	del_glb,	% delayed goals woken if the glb changes
82	del_lub,	% delayed goals woken if the lub changes
83	del_any,	% the delayed goals woken if the variable is bound
84			%	or the cardinal instantiated
85	card,		% cardinal of the set
86	setdom,		% the set domain itself
87	weight		% sum of the set elements according to a given argument
88    )).
89
90:- meta_attribute(set, [unify: unify_set/2,
91	test_unify: test_unify_set/2,
92	suspensions: suspensions_set/3,
93	delayed_goals_number: delayed_goals_number_set/2,
94	print: tr_setvar/2]).
95
96:- export portray(property(functor) of set, tr_set/2, [protect_arg]).
97
98tr_set(set with setdom:[Glb, Lub], T) :-
99	-?->
100	tr_s_lists(Glb, Glb1),
101	tr_s_lists(Lub, Lub1),
102	T = (Glb1.. Lub1).
103
104% ECLiPSe versions older than 3.5.2 pass only the attribute!!!
105tr_setvar(_{In}, Out) ?-
106	tr_set(In, Out).
107tr_setvar(In, Out) :-
108	tr_set(In, Out).
109
110
111%----------------------------------------------------------------------
112:- pragma(nodebug).
113
114:- import suspensions_to_goals/3 from sepia_kernel.
115
116S `:: Min .. Max :-
117	var(S),!,
118	S def_s Min .. Max.
119[] `:: _Min .. _Max :- !.
120[S |List] `:: Min .. Max :-
121	S def_s Min .. Max,
122	List `:: Min .. Max.
123
124
125% seteval/2 modified a bit to avoid coicepoint creation [joachim]
126
127%seteval(S, S) :-
128%	set_range(S, _, _),!.		% subsumed by next clause
129seteval(S, S1) :-
130	var(S),!,
131	S = S1.
132seteval(S \/ S1, Re) :- !,
133	seteval(S, R),
134	seteval(S1, R1),
135	union_s(R, R1,Re).
136seteval(S /\ S1, Re) :- !,
137	seteval(S, R),
138	seteval(S1, R1),
139	inter_s(R, R1, Re).
140seteval(S \ S1, Re) :- !,
141	seteval(S, R),
142	seteval(S1, R1),
143	diff_s(R, R1, Re).
144seteval(S, S) :-
145	set(S).
146
147
148S `<> S1 :-
149	seteval(S, R),
150	seteval(S1, R1),
151	dis_s(R, R1).
152
153S `= S1 :-
154	seteval(S, R),
155	seteval(S1, R).
156
157E in S :-
158	seteval(S, R),
159	in_s(E, R).
160
161E notin S :-
162	seteval(S, R),
163	nin_s(E, R).
164
165S `< S1 :-
166	seteval(S, R),
167	seteval(S1, R1),
168	sub_s(R, R1).
169
170#(S, C) :-
171	seteval(S, R),
172	car_s(R, C).
173
174sum_weight(S, W) :-
175	weight_s(S, W).
176
177
178set_weight(Attr, Value) ?-
179	setarg(weight of set, Attr, Value).
180
181set_card_dom(Attr, C, S) :-
182	setarg(card of set, Attr, C),
183	setarg(setdom of set, Attr, S).
184
185set_setdom(Attr, S) :-
186	setarg(setdom of set, Attr, S).
187
188svar_attribute(_{Attr}, Attr1) ?- Attr1 = Attr.
189
190glb(_{set with setdom:[G,_L]}, Glb) ?- Glb = G.
191
192lub(_{set with setdom:[_G,L]}, Lub) ?- Lub = L.
193
194set_range(_{set with setdom:[G,L]}, Glb, Lub) ?- !, Glb = G, Lub = L.
195
196set_or_set_range(_{set with setdom:[G,L]}, Glb, Lub) ?- !, Glb = G, Lub = L.
197set_or_set_range(Set, Set1, Set1) :- set(Set), !, Set=Set1.
198
199/*----------------------------------------------------- unification procedure*/
200
201unify_set(_, AttrSet) :-
202	var(AttrSet).
203unify_set(SY, AttrSX) :-
204	compound(AttrSX),
205	unify_term_set(SY,AttrSX).
206
207:- mode unify_term_set(?, +).
208
209unify_term_set(S, Attr) :-
210	compound(S),
211	set(S),!,
212	Attr= set with setdom:[Min,Max],
213	s_included(Min,S),
214	s_included(S,Max),
215	schedule_inst(Attr,S).
216unify_term_set(S,AttrSX) :-
217	meta(S),
218	svar_attribute(S,AttrSY),
219	unify_set_set(S,AttrSX,AttrSY).
220
221unify_set_set(_,AttrSX,AttrSY) :-
222	var(AttrSY),
223	AttrSY = AttrSX. /* change. share the attribute */
224unify_set_set(SY,AttrSX,AttrSY) :-
225	nonvar(AttrSY),
226	AttrSY= set with [card:CardY,setdom:[MinY,MaxY], weight: WeiY],
227	AttrSX= set with [card:CardX,setdom:[MinX,MaxX], weight: WeiX],
228	CardX=CardY,
229	(meta(WeiX);meta(WeiY)
230         -> WeiX = WeiY
231         ;
232	  WeiX = 0, WeiY = 0),
233	%(var(WeiY), var(WeiX),  ->
234	%    WeiX = 0, WeiY = 0;
235	%WeiX = WeiY),
236	s_included(MinX,MaxY),
237	s_included(MinY,MaxX),
238	s_union(MinX,MinY,NewMin),
239	s_intersection(MaxX,MaxY,NewMax),
240	(s_equality(NewMax,NewMin) ->
241	    schedule_inst(AttrSX, NewMin),	% wake X's lists
242	    SY=NewMin				% bind Y and wake its lists
243	;
244	   s_card(NewMin,Cmin),
245	   s_card(NewMax,Cmax),
246	   Card :: Cmin..Cmax,
247	   schedule_update(AttrSY,NewMin,NewMax),
248	   schedule_update(AttrSX,NewMin,NewMax),
249	   set_card_dom(AttrSY, Card, [NewMin,NewMax]),
250	   s_weight(NewMin, Weimin),
251	   s_weight(NewMax, Weimax),
252	   set_weight_dom(Weimin, Weimax, Wdom),
253	   Wei = Wdom,
254	   set_weight(AttrSY, Wei),
255	   merge_suspension_lists(del_glb of set, AttrSX, del_glb of set, AttrSY),
256	   merge_suspension_lists(del_lub of set, AttrSX, del_lub of set, AttrSY),
257	   merge_suspension_lists(del_any of set, AttrSX, del_any of set, AttrSY)
258       ).
259
260% schedule suspensions as a result of instantiating to Val
261schedule_inst(Attr, Val) :-
262	Attr = set with [del_lub:Lu, del_glb:Gl, setdom:[Glb,Lub]],
263	schedule_suspensions(del_any of set, Attr),
264	(s_equality(Val,Glb) ->
265	    attach_suspensions(postponed,Gl) /* as late as possible */
266	;
267	    schedule_woken(Gl)
268	),
269	(s_equality(Val,Lub) ->
270	    attach_suspensions(postponed,Lu)
271	;
272	    schedule_woken(Lu)
273	).
274
275% schedule suspensions as a result of updating the domain to NewMin..NewMax
276schedule_update(Attr, NewMin, NewMax) :-
277	Attr = set with [setdom:[Glb,Lub]],
278	( s_equality(NewMin,Glb) ->
279	    ( s_equality(NewMax,Lub) ->
280	    	true
281	    ;
282		schedule_suspensions(del_any of set, Attr),
283		schedule_suspensions(del_lub of set, Attr)
284	    )
285	;
286	    schedule_suspensions(del_any of set, Attr),
287	    schedule_suspensions(del_glb of set, Attr),
288	    ( s_equality(NewMax,Lub) ->
289		true
290	    ;
291		schedule_suspensions(del_lub of set, Attr)
292	    )
293	).
294
295
296/*-------------------------------------------------------- test_unify -*/
297
298test_unify_set(_, AttrSet) :-
299	var(AttrSet).
300test_unify_set(SY, AttrSX) :-
301	compound(AttrSX),
302	test_unify_term_set(SY, AttrSX).
303
304:- mode test_unify_term_set(?, +).
305test_unify_term_set(S, Attr) :-
306	nonvar(S),
307	set(S),
308	Attr= set with setdom:[Min,Max],
309	s_included(Min, S),
310	s_included(S, Max).
311test_unify_term_set(SY{AttrSY}, AttrSX) :-
312	-?->
313	test_unify_set_set(SY, AttrSX, AttrSY).
314
315test_unify_set_set(_, _, AttrSY) :-
316	var(AttrSY).
317test_unify_set_set(_SY, AttrSX, AttrSY) :-
318	nonvar(AttrSY),
319	AttrSY = set with [card:CardY,setdom:[MinY,MaxY]],
320	AttrSX = set with [card:CardX,setdom:[MinX,MaxX]],
321	dvar_domain(CardY, DomCardY),
322	dvar_domain(CardX, DomCardX),
323	dom_intersection(DomCardY, DomCardX, _, _),	% may fail
324	s_included(MinX, MaxY),				% may fail
325	s_included(MinY, MaxX).				% may fail
326
327
328/*--------------------------------------------------------           -*/
329
330suspensions_set(_{Attr}, Susps, Susps0) ?-
331	( var(Attr) ->
332	    Susps=Susps0
333	;
334	    Attr = set with [del_glb:DL, del_lub:DU, del_any:DA],
335	    Susps = [DL,DU,DA|Susps0]
336	).
337
338
339delayed_goals_number_set(_{set with [del_any:Bound,del_glb:Glb]}, N) ?- !,	%%%%
340	count_active_suspensions(Bound, 0, N1),
341	count_active_suspensions(Glb, N1, N).
342delayed_goals_number_set(_, 0).
343
344    count_active_suspensions([Susp|Susps], N0, N) ?- !,
345	( is_suspension(Susp) -> N1 is N0 + 1 ; N1 = N0 ),
346	count_active_suspensions(Susps, N1, N).
347    count_active_suspensions(_, N, N).
348
349
350/*--------------------------------------------------Actions on domain updates-*/
351
352modify_bound(glb, Set, Newmin) :-
353	set(Set),!, Set = Newmin.
354modify_bound(glb, Set, Newmin) :-
355	glb(Set, Min), s_included(Min, Newmin),
356	(Min = Newmin -> true;
357	set_changed_glb(Set, Newmin)).
358modify_bound(lub, Set, Newmax) :-
359	set(Set),!, Set = Newmax.
360modify_bound(lub, Set, Newmax) :-
361	lub(Set, Max), s_included(Newmax, Max),
362	(Max = Newmax -> true;
363	set_changed_lub(Set, Newmax)).
364
365modified_bounds(_,Set,Oldmin,Newmin) :-
366	set(Set), !,
367	s_equality(Newmin,Oldmin),
368	s_equality(Set,Oldmin).
369modified_bounds(min,_Set,Oldmin,Newmin) :-
370	s_equality(Newmin,Oldmin),!.
371modified_bounds(min,Set,_Oldmin,Newmin) :-
372	set_changed_glb(Set, Newmin).
373
374modified_bounds(max,_Set,Oldmax,Newmax) :-
375	s_equality(Oldmax,Newmax),!.
376modified_bounds(max,Set,_Oldmax,Newmax) :-
377	set_changed_lub(Set, Newmax).
378
379set_changed_lub(Var{Attr}, Value) ?-
380	Attr= set with [setdom:[Glb,_Lub]],
381	(s_equality(Value,Glb)
382              ->
383	      Var=Value
384	      ;
385	      set_setdom(Attr, [Glb,Value]),
386	      schedule_suspensions(del_lub of set, Attr),
387	      schedule_suspensions(del_any of set, Attr),
388	      notify_constrained(Var)
389	  ).
390
391set_changed_glb(Var{Attr}, Value) ?-
392	Attr= set with [setdom:[_Glb,Lub]],
393	(s_equality(Lub,Value)
394              ->
395	       Var=Value
396	      ;
397	      set_setdom(Attr, [Value,Lub]),
398	      schedule_suspensions(del_glb of set, Attr),
399	      schedule_suspensions(del_any of set, Attr),
400	      notify_constrained(Var)
401	      ).
402
403/*------------------------------------------------------------set variable --*/
404/* definition of a set variable within a domain <Glb,Lub> */
405
406init_set_fields(Set,Glb,Lub) :-
407	(s_equality(Lub,Glb)
408         ->
409	 s_card(Lub,Card)
410         ;
411	 s_card(Lub,L1),
412	 s_card(Glb,L2),
413	 Card ::L2..L1
414        ),
415	add_attribute(Set, set with [card:Card, setdom:[Glb,Lub],
416	    	del_glb:[], del_lub:[], del_any:[]]).
417
418Set def_s Glb..Glb :-
419	Set = Glb,!.
420Set def_s SetDom :-
421	make_setdom(Set,SetDom).
422make_setdom(Set,Glb..Lub) :-
423	s_included(Glb,Lub),
424	init_set_fields(Set,Glb,Lub).
425
426included(S, S1) :-
427	s_included(S,S1).
428
429/*-------------------------------------------------------cardinality operator-*/
430
431car_s(Set,Card) :-
432	set(Set),!,
433	s_card(Set,Card).
434car_s(Set,Card) :-
435	integer(Card),
436	svar_attribute(Set,SAttr),
437	SAttr= set with [setdom:[Glb,_Lub], card : Card1],
438	s_card(Glb,Card),
439	Card1 = Card,
440	!,
441	Set=Glb.
442car_s(Set,Card) :-
443	integer(Card),
444	svar_attribute(Set,SAttr),
445	SAttr= set with [setdom:[_Glb,Lub], card: Card1],
446	s_card(Lub,Card),
447	Card1= Card,
448	!,
449	Set=Lub.
450car_s(Set,Card) :-
451	integer(Card),
452	Card =1,
453	svar_attribute(Set,SAttr),
454	SAttr= set with [setdom:[_Glb,Lub], card: Card1,weight: W],
455	integer(W),!,
456	get_elements(Lub, L,W),
457	list2set(L,SNewmax),
458	Card1 = Card,
459	(s_card(SNewmax,1) ->
460	    Set = SNewmax;
461	    modified_bounds(max,Set,Lub,SNewmax),
462	    suspend(car_s(Set,Card), 2, Set->del_any)
463	).
464car_s(Set,Card) :-
465	svar_attribute(Set,SAttr),
466	SAttr= set with [setdom:[Glb,Lub], card: Card1],
467	s_card(Lub,Length2),
468	s_card(Glb,Length1),
469	Card :: Length1..Length2,
470	Card1 = Card,
471	attr_card_instantiate(Card,Set,SAttr,Length1,Length2).
472
473attr_card_instantiate(Card,Set,SAttr,_Length1,Length2) :-
474	SAttr =set with [setdom:[_Glb,Lub]],
475	is_domain(Card),
476	dvar_range(Card,Min,_Max),
477	Min=Length2,!,
478	Set=Lub.
479attr_card_instantiate(Card,Set,SAttr,Length1,_Length2) :-
480	SAttr =set with [setdom:[Glb,_Lub]],
481	is_domain(Card),
482	dvar_range(Card,_Min,Max),
483	Max=Length1,!,
484	Set=Glb.
485attr_card_instantiate(Card,Set,_SAttr,_Length1,_Length2) :-
486	is_domain(Card), !,
487	suspend(car_s(Set,Card), 2, [Set->del_any, Card->any]).
488attr_card_instantiate(Card,Set,SAttr,Length1,Length2) :-
489	SAttr =set with [setdom:[Glb,Lub]],
490	integer(Card),
491	(set(Set),s_card(Set,Card)
492         ->true;
493	(Card=Length2
494              ->
495	      Set=Lub ;
496	      (Card=Length1
497	       ->
498	         Set=Glb;
499		 suspend(car_s(Set,Card), 2, Set->del_any)
500	     )
501	 )).
502
503
504/*-----------------------------------------------------------weight operator --*/
505max_weight(S, E):-
506	set(S),!,
507	set2list(S, List),
508	find_longest(List, E, e(_, 0)).
509max_weight(S, E) :-
510	set_range(S, Min, Max),
511	s_delta(Max, Min, Diff),
512	set2list(Diff, List),
513	find_longest(List, E, e(_, 0)).
514
515find_longest([], X, X).
516find_longest([e(N, L) | List], X, e(Name, Length)) :-
517	( L < Length
518         ->
519	  find_longest(List, X, e(Name, Length))
520         ;
521	  find_longest(List, X, e(N, L))
522        ).
523
524el_weight(E,W) :-
525	arg(2, E, W).
526
527% get all elements with the given weight
528get_elements(Lub, L, W) :-
529	set2list(Lub, LLub),
530	getelements(LLub, L, W),
531	L \= [].
532
533getelements([],[],_W).
534getelements([E | LLub], [E |L], W) :-
535	arg(2, E, W),!,
536	getelements(LLub, L, W).
537getelements([_F | LLub], L, W) :-
538	getelements(LLub, L, W).
539
540set_weight_dom(Weimin, Weimax, Wdom) :-
541	(Weimin= 0, Weimax = 0 ->
542	    Wdom =0;
543	    Wdom :: Weimin .. Weimax).
544
545set_weight_discrdom(NewMin, NewMax, Weimin, Wdom) :-
546	s_delta(NewMax, NewMin, Sdiff),
547	set2list(Sdiff, Ldiff),
548	setweightdom(Weimin, Ldiff, Wdom1),
549	Wdom :: [Weimin | Wdom1],
550	Wdom ## 0.
551
552setweightdom(_Weimin, [], []).
553setweightdom(Weimin, [E | Ldiff], Wdom) :-
554	setweightdom(Weimin, Ldiff, Wdom1),
555	arg(2, E, We),
556	Wee is We + Weimin,
557	Wdom = [ Wee | Wdom1].
558
559weight_s(S, W) :-
560	set(S), !,
561	s_weight(S, W).
562%changes 2 weight_s predicates removed
563weight_s(S, W) :-
564	svar_attribute(S, SAttr),
565	SAttr= set with [setdom: [Glb, Lub], card: C, weight : W],
566	s_weight(Glb, W1),
567	s_weight(Lub, W2),
568	(C==1
569         ->
570	 s_weight_discr(Lub, W22),
571	 Wtemp :: W22
572	%set_weight_discrdom(Glb, Lub, W1,Wtemp)
573         ;
574	 set_weight_dom(W1,W2, Wtemp)
575        ),
576	W = Wtemp,
577	attr_weight_instanciate(W, S, SAttr, W1, W2),
578	( nonvar(S) ->
579	           true;
580		   s_delta(Lub, Glb, S_diff),
581		   set_dom_change(S, S_diff, W1, W)
582	).
583
584% carmen changes : procedure made generic
585exist_nil_weights_indiff(Lub, Glb) :-
586	s_delta(Lub, Glb, Sdiff),
587	set2list(Sdiff,LSdiff),
588	exist_nil_weights(LSdiff).
589
590exist_nil_weights([]) :-!.
591exist_nil_weights([ E | Lub]) :-
592	(arg(2,E,0) -> true;
593	    exist_nil_weights(Lub)
594	).
595
596set_dom_change(S, Lub, W1, W) :-
597	set2list(Lub, Llub),
598	(is_domain(W)
599         -> dvar_range(W, _, Wlocal); Wlocal = W),
600	 setdomremove(S, Llub, W1, Wlocal).
601
602setdomchange1(_S, [], _W1, _W).
603setdomchange1(S, [E | Llub], W1, W) :-
604	arg(2, E, We),
605	((We + W1 > W;We + W1 < W)
606          ->
607	  E nin_s S;
608	  true),
609	  setdomchange1(S, Llub, W1, W).
610
611setdomremove(_S, [], _W1, _W).
612setdomremove(S, [E | Llub], W1, W) :-
613	arg(2, E, We),
614	(We + W1 > W
615          ->
616	  E nin_s S;
617	  true),
618	  setdomremove(S, Llub, W1, W).
619
620%changes: two additional conditions added to test for elements with weight 0 in the last clause
621attr_weight_instanciate(W, S, SAttr, _W1, W2) :-
622	SAttr = set with [setdom : [_Glb, Lub]],
623	is_domain(W),
624	dvar_range(W, Min, _Max),
625	Min = W2, !,
626	S = Lub.
627attr_weight_instanciate(W, S, SAttr, W1, _W2) :-
628	SAttr = set with [setdom : [Glb, _Lub]],
629	is_domain(W),
630	dvar_range(W, _Min, Max),
631	Max = W1, !,
632	S = Glb.
633attr_weight_instanciate(W, S, SAttr, _W1, _W2) :-
634	is_domain(W),
635	SAttr = set with [card : C],
636	!,
637	suspend(weight_s(S, W), 2, [S->del_any, W->any, C -> inst]).
638attr_weight_instanciate(W, S, SAttr, W1, W2) :-
639	SAttr = set with [setdom : [Glb, Lub]],
640	integer(W),
641	(W = W2
642             ->
643             (not(exist_nil_weights_indiff(Lub, Glb)) ->
644	     S = Lub;
645             add_all_not_nil(Lub, Glb, Subset),
646	     Subset sub_s S
647             )
648             ;
649	     ((W = W1,not(exist_nil_weights_indiff(Lub, Glb)))
650	      ->
651	        S = Glb;
652		suspend(weight_s(S, W), 2, [S->del_any, W->any])
653	    )
654	).
655
656add_all_not_nil(Lub, Glb, Subset) :-
657	s_delta(Lub, Glb, Sdiff),
658	set2list(Sdiff, LSdiff),
659	addallnotnil(LSdiff, LSubset),
660	list2set(LSubset, Subset).
661
662addallnotnil([], []) :- !.
663addallnotnil([ E | Lub], NewSubset) :-
664	arg(2,E,0), !,
665	addallnotnil(Lub, NewSubset).
666addallnotnil([ E | Lub], [E | NewSubset]) :-
667	addallnotnil(Lub, NewSubset).
668
669/*---------------------------------------------------------------CONSTRAINTS--*/
670
671S sub_s S1 :-
672	set(S),
673	set(S1),
674	!,
675	s_included(S,S1).
676S sub_s S1 :-
677	set(S),
678	set_range(S1,S1Min,S1Max),
679	!,
680	s_included(S,S1Max),
681	s_union(S,S1Min,S1Newmin),
682	modified_bounds(min,S1,S1Min,S1Newmin).
683
684S sub_s S1 :-
685	set(S1),
686	set_range(S,SMin,SMax),
687	!,
688	s_included(SMin,S1),
689	s_intersection(SMax,S1,SNewmax),
690	modified_bounds(max,S,SMax,SNewmax).
691
692S sub_s S1 :-
693	set_range(S1,S1Min,S1Max),
694	set_range(S,SMin,SMax),
695	s_included(SMin,S1Max),
696	s_union(SMin,S1Min,S1Newmin),
697	s_intersection(SMax,S1Max,SNewmax),
698	modified_bounds(min,S1,S1Min,S1Newmin),
699	modified_bounds(max,S,SMax,SNewmax),
700	( var(S),var(S1) -> suspend(S sub_s S1, 2, [S,S1]->del_any) ; true ),
701	wake.
702
703
704/*----------------------------------------------------------------membership--*/
705
706X in_s S :-
707	var(X), !,
708	S \== {},	% nothing can be in the empty set
709	suspend(X in_s S, 2, [X,S]->inst).
710X in_s S :-                          /*X is known */
711	set_range(S,SMin,SMax),!,
712	s_memberchk(X,SMax),
713	s_insertion(X,SMin,Newmin),
714	modified_bounds(min,S,SMin,Newmin),
715	wake.
716X in_s S :-
717	set(S),!,
718	s_memberchk(X,S).
719
720
721X nin_s S :-
722	var(X), !,
723	suspend(X nin_s S, 2, X->inst).
724X nin_s S :-
725	set_range(S,SMin,SMax),!,
726	not s_memberchk(X,SMin),
727	s_remove(X,SMax,Newmax),
728	modified_bounds(max,S,SMax,Newmax),
729	wake.
730X nin_s S :-
731	set(S),
732	\+ s_memberchk(X,S).
733/*----------------------------------------------------disjoint-*/
734
735SetX dis_s SetY :-
736	set(SetX),
737	set(SetY),
738	!,
739	s_dis(SetX,SetY).
740	%s_intersection(SetX,SetY,{}).
741SetX dis_s SetY :-
742	set(SetX),
743	!,
744	set_range(SetY,SYMin,SYMax),
745	s_dis(SetX,SYMin),
746	%s_intersection(SetX,SYMin,{}),
747	s_delta(SYMax,SetX,NewSYmax),
748	modified_bounds(max,SetY,SYMax,NewSYmax),
749	wake.
750SetY dis_s SetX :-
751	set(SetX),
752	!,
753	set_range(SetY,SYMin,SYMax),
754	s_dis(SetX,SYMin),
755	%s_intersection(SetX,SYMin,{}),
756	s_delta(SYMax,SetX,NewSYmax),
757	modified_bounds(max,SetY,SYMax,NewSYmax),
758	wake.
759SetX dis_s SetY :-
760	set_range(SetX,_SXMin,SXMax),
761	set_range(SetY,_SYMin,SYMax),
762	s_dis(SXMax,SYMax),!.
763SetX dis_s SetY :-
764	set_range(SetX,SXMin,SXMax),
765	set_range(SetY,SYMin,SYMax),
766	s_dis(SXMin,SYMin),
767	%s_intersection(SXMin,SYMin,{}),
768	s_delta(SXMax,SYMin,NewSXmax),
769	s_delta(SYMax,SXMin,NewSYmax),
770	modified_bounds(max,SetX,SXMax,NewSXmax),
771	modified_bounds(max,SetY,SYMax,NewSYmax),
772	( var(SetX),var(SetY) ->
773	    suspend(SetX dis_s SetY, 2, [SetX, SetY]->del_glb)
774	; true ),
775	wake.
776
777
778/* -------------------------------- --------------------All_disjoint-*/
779
780all_disjoint([]).
781all_disjoint([Set | Sets]) :-
782	map_disjoint(Set, Sets),
783	all_disjoint(Sets).
784
785map_disjoint(_, []).
786map_disjoint(Set1, [Set2 | Sets]) :-
787	Set1 dis_s Set2,
788	map_disjoint(Set1, Sets).
789
790/*----------------------------------------------------------------OPERATORS--*/
791
792/*-----------------------------------------------------------union (S1,S2,S3)-*/
793
794/* X U Y = S           */
795/* min(S) \ max(X) < Y */
796/* max(X) < max(S)     */
797set_union_domain(SMin,SMax,SXMax,SXMin,SYMax,SYMin,SXnewMin,SXnewMax,SYnewMin,
798	SYnewMax) :-
799	s_delta(SMin,SYMax,RemindingX),
800	s_included(RemindingX, SXMax),
801	s_delta(SMin,SXMax,RemindingY),
802	s_included(RemindingY, SYMax),
803	s_union(SXMin,RemindingX,SXnewMin),
804	s_union(SYMin,RemindingY,SYnewMin),
805	s_intersection(SMax, SXMax, SXnewMax),
806	s_intersection(SMax, SYMax, SYnewMax).
807
808union_set_bounds(XNewmin,XNewmax,YNewmin,YNewmax,SMin,SMax,
809	Snewmin,Snewmax) :-
810	s_union(XNewmin,SMin,TampSmin),      % the resulting set bounds
811	s_union(YNewmin,TampSmin,Snewmin),   % are modified (S3): add elts
812	s_delta(SMax,XNewmax,Saddelts),   % from S1 and S2 min.
813	s_delta(Saddelts,YNewmax,Saddelts1),
814	s_delta(SMax,Saddelts1,Snewmax).
815
816ground_union(SetX, SetY, S) :-
817	set(SetX), set(SetY), !,
818	s_union(SetX, SetY, S).
819ground_union(SetX,SetY,S) :-
820	set(SetX),
821	!,
822	s_delta(S,SetX,YNewMintamp),
823	set_range(SetY,SYMin,SYMax),
824	s_included(YNewMintamp,SYMax),
825	s_union(SYMin,YNewMintamp,YNewMin),
826	s_intersection(SYMax, S, SYnewMax),
827	modified_bounds(min,SetY,SYMin,YNewMin),
828	modified_bounds(max,SetY, SYMax, SYnewMax),
829	wake.
830ground_union(SetY,SetX,S) :-
831	set(SetX),
832	!,
833	s_delta(S,SetX,YNewMintamp),
834	set_range(SetY,SYMin,SYMax),
835	s_included(YNewMintamp,SYMax),
836	s_union(SYMin,YNewMintamp,YNewMin),
837	s_intersection(SYMax, S, SYnewMax),
838	modified_bounds(min,SetY,SYMin,YNewMin),
839	modified_bounds(max,SetY, SYMax, SYnewMax),
840	wake.
841ground_union(SetX,SetY,Slist) :-
842	set_range(SetX,SXMin,SXMax),
843	set_range(SetY,SYMin,SYMax),
844	set_union_domain(Slist,Slist,SXMax,SXMin,SYMax,SYMin,
845	XNewmin,XNewmax,YNewmin,YNewmax),
846	modified_bounds(min,SetX,SXMin,XNewmin),
847	modified_bounds(min,SetY,SYMin,YNewmin),
848	modified_bounds(max,SetX,SXMax,XNewmax),
849	modified_bounds(max,SetY,SYMax,YNewmax),
850	( var(SetX),var(SetY) ->
851	    suspend(ground_union(SetX,SetY,Slist), 2, [SetX,SetY]->del_any)
852	; true ),
853	wake.
854
855union_s(SetX,SetY,S) :-
856	set(SetX),        % At least the first two sets are known
857	set(SetY),
858	!,
859	s_union(SetX, SetY, S).
860union_s(SetX,SetY,S) :-
861	set(S),              %S the resulting set is known
862	!,
863	ground_union(SetX,SetY,S).
864union_s(SetX,SetY,S) :-
865	set(SetX),
866	set_range(S,SMin,SMax),
867	set_range(SetY,SYMin,SYMax),!,
868	s_delta(SMin,SetX,RemindingY),
869	s_included(RemindingY, SYMax),
870	s_union(SYMin,RemindingY,YNewmin),
871	s_intersection(SMax, SYMax, YNewmax),
872	s_union(SetX,YNewmin,SMintmp),
873	s_union(SMintmp,SMin,Snewmin),
874	s_delta(SMax,SetX,Saddelts),
875	s_delta(Saddelts,YNewmax,Saddelts1),
876	s_delta(SMax,Saddelts1,Snewmax),
877	modified_bounds(min,SetY,SYMin,YNewmin),
878	modified_bounds(max,SetY,SYMax,YNewmax),
879	modified_bounds(min,S,SMin,Snewmin),
880	modified_bounds(max,S,SMax,Snewmax),
881	wake,
882	( nonground([SetY,S]) ->
883	    suspend(union_s(SetX,SetY,S), 2, [SetY,S]->del_any) ; true ).
884union_s(SetY,SetX,S) :-
885	set(SetX),
886	set_range(S,SMin,SMax),
887	set_range(SetY,SYMin,SYMax),!,
888	s_delta(SMin,SetX,RemindingY),
889	s_included(RemindingY, SYMax),
890	s_union(SYMin,RemindingY,YNewmin),
891	s_intersection(SMax, SYMax, YNewmax),
892	s_union(SetX,YNewmin,SMintmp),
893	s_union(SMintmp,SMin,Snewmin),
894	s_delta(SMax,SetX,Saddelts),
895	s_delta(Saddelts,YNewmax,Saddelts1),
896	s_delta(SMax,Saddelts1,Snewmax),
897	modified_bounds(min,SetY,SYMin,YNewmin),
898	modified_bounds(max,SetY,SYMax,YNewmax),
899	modified_bounds(min,S,SMin,Snewmin),
900	modified_bounds(max,S,SMax,Snewmax),
901	wake,
902	( nonground([SetY,S]) ->
903	    suspend(union_s(SetX,SetY,S), 2, [SetY,S]->del_any) ; true ).
904union_s(SetX,SetY,S) :-    %S the resulting set is a set domain variable
905	set_range(S,SMin,SMax),
906	set_range(SetX,SXMin,SXMax),
907	set_range(SetY,SYMin,SYMax),
908	!,
909	set_union_domain(SMin,SMax,SXMax,SXMin,SYMax,SYMin,
910	XNewmin,XNewmax,YNewmin,YNewmax),
911	union_set_bounds(XNewmin,XNewmax,YNewmin,YNewmax,SMin,SMax,
912	Snewmin,Snewmax),
913	modified_bounds(min,SetX,SXMin,XNewmin),
914	modified_bounds(min,SetY,SYMin,YNewmin),
915	modified_bounds(max,SetX,SXMax,XNewmax),
916	modified_bounds(max,SetY,SYMax,YNewmax),
917	modified_bounds(min,S,SMin,Snewmin),
918	modified_bounds(max,S,SMax,Snewmax),
919	wake,
920	( nonground([SetX,SetY,S]) ->
921	    suspend(union_s(SetX,SetY,S), 2, [SetX,SetY,S]->del_any) ; true ).
922union_s(SetX,SetY,S) :-
923	var(S),                 /* S is a free variable */
924	set_range(SetX,SXMin,SXMax),
925	set_range(SetY,SYMin,SYMax),!,
926	s_union(SXMin,SYMin,SMin),
927	s_union(SXMax,SYMax,SMax),
928	S def_s SMin..SMax,
929	suspend(union_s(SetX,SetY,S), 2, [SetX,SetY,S]->del_any).
930union_s(SetX,SetY,S) :-
931	var(S),                 /* S is a free variable */
932	set(SetX),
933	set_range(SetY,SYMin,SYMax),!,
934	s_union(SetX,SYMin,SMin),
935	s_union(SetX,SYMax,SMax),
936	S def_s SMin..SMax,
937	suspend(union_s(SetX,SetY,S), 2, [SetY,S]->del_any).
938union_s(SetY,SetX,S) :-
939	var(S),                 /* S is a free variable */
940	set(SetX),
941	set_range(SetY,SYMin,SYMax),
942	s_union(SetX,SYMin,SMin),
943	s_union(SetX,SYMax,SMax),
944	S def_s SMin..SMax,
945	suspend(union_s(SetX,SetY,S), 2, [SetY,S]->del_any).
946
947/*--------------------------------------union of a conjunction (list) of sets-*/
948
949all_union([Union1], Union2) :-
950	!,
951	Union1= Union2.
952all_union([Set1, Set2 | Sets], Union) :-
953	union_s(Set1, Set2, Set1Set2),
954	all_union([Set1Set2 | Sets], Union).
955
956/*-----------------------------------------------------intersection (S1,S2,S)-*/
957
958
959inter_add_remove_elementsfromknown(SMax,[SXMin,SXMax],[SYMin,SYMax],XNewmin,
960	XNewmax,YNewmin,YNewmax) :-
961	inter_add_elementsfromMin(SMax,[SXMin,_SXMax],[SYMin,_SYMax],XNewmin,
962	YNewmin),
963	inter_remove_elementsfromMax(SMax,[SXMin,SXMax],[SYMin,SYMax],
964	XNewmax,YNewmax).
965
966inter_add_elementsfromMin(SMin,[SXMin,_SXMax],[SYMin,_SYMax],XNewmin,
967	YNewmin) :-
968	s_union(SMin,SXMin,XNewmin),
969	s_union(SMin,SYMin,YNewmin).
970
971inter_remove_elementsfromMax(SNewmax,[SXMin,SXMax],[SYMin,SYMax],
972	XNewmax,YNewmax) :-
973	s_intersection(SXMax,SYMax,TampInter),
974	s_delta(TampInter,SNewmax,RemindingInter),
975	s_intersection(SXMin,RemindingInter,ElementstostayinX),
976	s_intersection(SYMin,RemindingInter,ElementstostayinY),
977	s_intersection(ElementstostayinX,ElementstostayinY,Inter),
978	s_delta(ElementstostayinX,Inter,NotinSY), /*remove elements X from maxS2 */
979	s_delta(SYMax,NotinSY,YNewmax),           /* if X in minS1, X in maxS2   */
980	s_delta(ElementstostayinY,Inter,NotinSX), /* X notin S.   */
981	s_delta(SXMax,NotinSX,XNewmax).
982
983/*  the domains of the two first sets is modified */
984sets_inter_newdomains(SMin,SMax,SXMax,SXMin,SYMax,SYMin,
985	XNewmin,XNewmax,YNewmin,YNewmax) :-
986	s_included(SMin,SXMax),
987	s_included(SMin,SYMax),
988	s_intersection(SXMin,SYMin,Commonmin),
989	s_included(Commonmin,SMax),
990	!,
991	s_intersection(SXMax,SYMax,Newinter),
992	s_intersection(Newinter,SMax,SNewmax),
993	(s_equality(SMin,SMax) ->
994	inter_add_remove_elementsfromknown(SMax,[SXMin,SXMax],[SYMin,SYMax],
995	XNewmin,XNewmax,YNewmin,YNewmax);
996	inter_add_elementsfromMin(SMin,[SXMin,SXMax],[SYMin,SYMax],XNewmin,
997	YNewmin),
998	inter_remove_elementsfromMax(SNewmax,[SXMin,SXMax],[SYMin,SYMax],
999	XNewmax,YNewmax)).
1000
1001
1002
1003% the resulting set domain is modified
1004result_intersectionset_bounds(XNewmin,XNewmax,YNewmin,YNewmax,
1005	SMin,SMax,Snewmin,Snewmax) :-
1006	s_intersection(XNewmin,YNewmin,TampSmin),  %Snewmin is the min union
1007	s_union(SMin,TampSmin,Snewmin),              %Snewmax is the max union
1008	s_intersection(XNewmax,YNewmax,TampSmax),
1009	s_intersection(TampSmax,SMax,Snewmax).
1010
1011inter_s(SetX,SetY,S) :-   %first two terms are at least known
1012	set(SetX),
1013	set(SetY),
1014	!,
1015	s_intersection(SetX, SetY, S).
1016inter_s(SetX,SetY,S):-
1017	set(S),
1018	set_range(SetX, SXMin,SXMax),
1019	set_range(SetY,SYMin,SYMax),
1020	!,
1021	sets_inter_newdomains(S,S,SXMax,SXMin,SYMax,SYMin,
1022	Xnewmin,XNewmax,Ynewmin,YNewmax),
1023	modified_bounds(min,SetX,SXMin,Xnewmin),
1024	modified_bounds(min,SetY,SYMin,Ynewmin),
1025	modified_bounds(max,SetX,SXMax,XNewmax),
1026	modified_bounds(max,SetY,SYMax,YNewmax),
1027	wake,
1028	( var(SetX), var(SetY) ->
1029	    suspend(inter_s(SetX,SetY,S), 2, [SetX,SetY]->del_any)
1030	; true ).
1031inter_s(SetX,SetY,S):-
1032	set(S),
1033	set(SetX),
1034	set_range(SetY,SYMin,SYMax),
1035	!,
1036	s_intersection(SetX,SYMax,S1),
1037	s_included(S,S1),
1038	s_union(SYMin,S,Ynewmin),
1039	s_delta(SetX,S,STmp),
1040	s_delta(SYMax,STmp,YNewmax),
1041	modified_bounds(min,SetY,SYMin,Ynewmin),
1042	modified_bounds(max,SetY,SYMax,YNewmax),
1043	wake.
1044inter_s(SetX,SetY,S):-
1045	set(S),
1046	set(SetY),
1047	set_range(SetX,_SXMin,_SXMax),
1048	!,
1049	inter_s(SetY,SetX,S).
1050inter_s(SetX,SetY,S) :-          % the resulting set is a domain variable
1051	set_or_set_range(S,SMin,SMax),
1052	set_or_set_range(SetX,SXMin,SXMax),
1053	set_or_set_range(SetY,SYMin,SYMax),
1054	!,
1055	sets_inter_newdomains(SMin,SMax,SXMax,SXMin,SYMax,SYMin,
1056	XNewmin,XNewmax,YNewmin,YNewmax),
1057	result_intersectionset_bounds(XNewmin,XNewmax,YNewmin,YNewmax,
1058	SMin,SMax,Snewmin,Snewmax),
1059	modified_bounds(min,SetX,SXMin,XNewmin),
1060	modified_bounds(min,SetY,SYMin,YNewmin),
1061	modified_bounds(max,SetX,SXMax,XNewmax),
1062	modified_bounds(max,SetY,SYMax,YNewmax),
1063	modified_bounds(min,S,SMin,Snewmin),
1064	modified_bounds(max,S,SMax,Snewmax),
1065	wake,
1066	( nonground(2, [SetX,SetY,S], _TwoVars) ->
1067	    suspend(inter_s(SetX,SetY,S), 2, [SetX,SetY,S]->del_any)
1068	; true ).
1069inter_s(SetX,SetY,S) :-   /* S is not specified as a domain variable */
1070	var(S),
1071	set_range(SetX,SXMin,SXMax),
1072	set_range(SetY,SYMin,SYMax),
1073	!,
1074	s_intersection(SXMin,SYMin,SMin),
1075	s_intersection(SXMax,SYMax,SMax),
1076	(s_equality(SMin,SMax)
1077         -> S=SMin
1078         ;
1079	    S def_s SMin..SMax,
1080	    ( nonground(2, [SetX,SetY,S], _TwoVars) ->
1081		suspend(inter_s(SetX,SetY,S), 2, [SetX,SetY,S]->del_any)
1082	    ; true )
1083        ).
1084inter_s(SetX,SetY,S) :-   /* S is not specified as a domain variable  */
1085	var(S),
1086	set(SetX),
1087	set_range(SetY,SYMin,SYMax),
1088	!,
1089	(s_included(SetX,SYMin)
1090         ->
1091	 S=SetX
1092         ;
1093	 (s_dis(SYMax,SetX) %s_intersection(SYMax,SetX,{})
1094	     -> S={}
1095         ;
1096	     s_intersection(SetX,SYMin,SMin),
1097	     s_intersection(SetX, SYMax, SMax),
1098	     S def_s SMin..SMax,
1099	     ( nonground([SetY,S]) ->
1100		  suspend(inter_s(SetX,SetY,S), 2, [SetY,S]->del_any)
1101	     ; true )
1102	 )
1103	).
1104inter_s(SetY,SetX,S) :-
1105	var(S),
1106	set(SetX),
1107	set_range(SetY,_SYMin,_SYMax),
1108	inter_s(SetX,SetY,S).
1109/*---------------------------------------------------------------------diff--*/
1110
1111diff_s(SetX,SetY,S) :-
1112	set(SetX),
1113	set(SetY),   /* the first two sets are known */
1114	!,
1115	s_delta(SetX, SetY,S).
1116
1117diff_s(SetX,SetY,S) :-
1118	set(S),              /* the resulting set is known */
1119	!,
1120	set_or_set_range(SetX, SXMin,SXMax),
1121	set_or_set_range(SetY,SYMin,SYMax),
1122	s_dis(SYMin,S),
1123	%s_intersection(SYMin,S,{}),
1124	s_included(S,SXMax),
1125	!,
1126	s_union(S,SXMin,Xnewmin1),
1127	s_delta(SYMin,S,Xnewmin2),
1128	s_union(Xnewmin1,Xnewmin2,Xnewmin),
1129	s_union(SYMax,S,Xnewmax1),
1130	s_intersection(SXMax,Xnewmax1,XNewmax),
1131	s_delta(SYMax,S,YNewmax),
1132	s_delta(Xnewmin,S,Ynewmin1),
1133	s_union(SYMin, Ynewmin1, Ynewmin),
1134	modified_bounds(min,SetX,SXMin,Xnewmin),
1135	modified_bounds(max,SetX,SXMax,XNewmax),
1136	modified_bounds(min,SetY,SYMin,Ynewmin),
1137	modified_bounds(max,SetY,SYMax,YNewmax),
1138	wake,
1139	( var(SetX), var(SetY) ->
1140	    suspend(diff_s(SetX,SetY,S), 2, [SetX,SetY]->del_any)
1141	; true ).
1142diff_s(SetX,SetY,S) :-
1143	set_range(S,SMin,SMax),
1144	!,
1145	set_or_set_range(SetX, SXMin,SXMax),
1146	set_or_set_range(SetY,SYMin,SYMax),
1147	s_dis(SYMin, SMin),
1148	%s_intersection(SYMin,SMin,{}),
1149	s_included(SMin,SXMax),
1150	s_union(SMin,SXMin,Xnewmin1),
1151	s_delta(SYMin, SMax, Xnewmin2),
1152	s_union(Xnewmin1, Xnewmin2, XNewmin), /*+ pour X */
1153	s_union(SMax,SYMin,TampmaxX),
1154	s_intersection(SXMax, TampmaxX, XNewmax), /* remove elements from Max X */
1155        s_delta(XNewmin, SMax, TampminY),
1156	s_union(SYMin, TampminY, YNewmin), /* add elements to Min Y */
1157	s_delta(SYMax,SMin,YNewmax),    /* remove elements from Max Y */
1158	s_delta(SXMin,SYMax,Tampmin),
1159	s_union(Tampmin,SMin, SNewmin),  /*  add elements to Min S */
1160        s_delta(SXMax, SYMin, TampSmax),
1161	s_intersection(SMax,TampSmax, SNewmax),    /*  remove elements from Max S */
1162	modified_bounds(min,SetX,SXMin,XNewmin),
1163	modified_bounds(max,SetX,SXMax,XNewmax),
1164	modified_bounds(min,SetY,SYMin,YNewmin),
1165	modified_bounds(max,SetY,SYMax,YNewmax),
1166	modified_bounds(min,S,SMin,SNewmin),
1167	modified_bounds(max,S,SMax,SNewmax),
1168	wake,
1169	( nonground(2, [SetX,SetY,S], _TwoVars) ->
1170	    suspend(diff_s(SetX,SetY,S), 2, [SetX,SetY,S]->del_any)
1171	; true ).
1172diff_s(SetX,SetY,S) :-
1173	var(S),
1174	set_range(SetX,XMin,XMax),
1175	set_range(SetY,YMin,YMax),!,
1176	s_delta(XMax,YMin,SMax),
1177	s_delta(XMin,YMax,SMin),
1178	S def_s SMin..SMax,
1179	suspend(diff_s(SetX,SetY,S), 2, [S,SetX,SetY]->del_any).
1180diff_s(SetX,SetY,S) :-
1181	var(S),
1182	set(SetX),
1183	set_range(SetY,YMin,YMax),!,
1184	s_delta(SetX,YMax,SMin),
1185	s_delta(SetX,YMin,SMax),
1186	(s_equality(SMin,SMax)
1187         -> S=SMin
1188         ;
1189	 S def_s SMin..SMax,
1190	 suspend(diff_s(SetX,SetY,S), 2, [S,SetY]->del_any)
1191	).
1192diff_s(SetY,SetX,S) :-
1193	var(S),
1194	set(SetX),
1195	set_range(SetY,YMin,YMax),
1196	s_delta(YMin,SetX,SMin),
1197	s_delta(YMax,SetX,SMax),
1198	(s_equality(SMin,SMax)
1199         -> S=SMin
1200         ;
1201	 S def_s SMin..SMax,
1202	 suspend(S sub_s SetY, 2, [S,SetY]->del_any)
1203	).
1204/*---------------------------------------------------------phase de labeling -*/
1205
1206refine(S) :-
1207	nonvar(S), set(S).
1208refine(S) :-
1209	var(S), set_range(S,Min,Max),
1210	s_delta(Max,Min, Diff),
1211	s_memberchk(X, Diff),
1212	( X in_s S ; X nin_s S ),
1213	refine(S).
1214
1215
1216par_refine(S) :-
1217	nonvar(S), set(S).
1218par_refine(S) :-
1219	var(S), set_range(S,Min,Max),
1220	s_delta(Max,Min, Diff),
1221	s_memberchk(X, Diff),
1222	in_or_notin(X, S),
1223	par_refine(S).
1224
1225:- parallel in_or_notin/2.
1226in_or_notin(X, S) :- X in_s S.
1227in_or_notin(X, S) :- X nin_s S.
1228