1%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2% BEGIN LICENSE BLOCK
3% Version: CMPL 1.1
4%
5% The contents of this file are subject to the Cisco-style Mozilla Public
6% License Version 1.1 (the "License"); you may not use this file except
7% in compliance with the License.  You may obtain a copy of the License
8% at www.eclipse-clp.org/license.
9%
10% Software distributed under the License is distributed on an "AS IS"
11% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied.  See
12% the License for the specific language governing rights and limitations
13% under the License.
14%
15% The Original Code is  The Cardinal Constraint Solver for ECLiPSe.
16% The Initial Developer of the Original Code is  Francisco M.C.A. Azevedo.
17% Portions created by the Initial Developer are  Copyright (C) 2000-2004.
18% All Rights Reserved.
19%
20% Contributor(s): Francisco M. C. A. Azevedo <fa@di.fct.unl.pt>.
21%
22% Alternatively, the contents of this file may be used under the terms of
23% either of the GNU General Public License Version 2 or later (the "GPL"),
24% or the GNU Lesser General Public License Version 2.1 or later (the "LGPL"),
25% in which case the provisions of the GPL or the LGPL are applicable instead
26% of those above. If you wish to allow use of your version of this file only
27% under the terms of either the GPL or the LGPL, and not to allow others to
28% use your version of this file under the terms of the MPL, indicate your
29% decision by deleting the provisions above and replace them with the notice
30% and other provisions required by the GPL or the LGPL. If you do not delete
31% the provisions above, a recipient may use your version of this file under
32% the terms of any one of the MPL, the GPL or the LGPL.
33% END LICENSE BLOCK
34%
35% cardinal_minmax.pl      By Francisco Azevedo    2000 - 2004
36%
37% Minimum and Maximum set functions of Cardinal.
38%
39%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
40
41:- lib(fd).
42
43
44%--------
45% minimum_function(+Min, +Set)
46%  Inferences for Set's minimum function.
47%--
48minimum_function(Min, Set):-
49	cardinality(Set, CardSet),
50	integers_only(Set, CardSet),
51	(var(Min) -> MinVar=Min ; MinVar::Min),
52	set_minimum(Set, MinVar),
53	CardSet #>= 1,
54	suspend_and_call(minimum_bounded(MinVar,Set,CardSet,[SuspMB,SuspCLM]), 4,
55		[Set->cardinal:bounded,CardSet->fd:min], SuspMB),
56	suspend_and_call(check_lower_min(MinVar,Set), 4, MinVar->fd:min, SuspCLM),
57	(ground(MinVar) -> min_inst(MinVar,Set,[SuspMB,SuspCLM])
58	;suspend(min_inst(MinVar,Set,[SuspMB,SuspCLM,SuspMI]), 3, MinVar->inst, SuspMI)
59	).
60
61%--------
62% integers_only(+Set, +CardSet)
63%  Force Set (with cardinality CardSet) to have only integers.
64%--
65integers_only(Set, CardSet):-
66	domain(Set, CardSet, [Glb:NIn,Poss:_]),
67	\+ (member(X,Glb), \+ integer(X)),
68	integers_list(Poss, NewPoss, NIn,NewNMax),
69	set_poss(Set, NewPoss,NewNMax).
70
71%--------
72% integers_list(+List, -Integers, Ni,No)
73%  Integers is the list of the No-Ni integers of List.
74%--
75integers_list([], [], N,N).
76integers_list([H|T], [H|Is], Ni,No):- integer(H), !, N1 is Ni+1, integers_list(T,Is,N1,No).
77integers_list([_|T], Is, Ni,No):- integers_list(T,Is,Ni,No).
78
79%--------
80% minimum_bounded(+Min, +Set, +CardSet, +Susps)
81%  Update Set's minimum function Min due to the Set's domain change (bounded Set).
82% CardSet is Set's cardinality.
83%--
84:-demon minimum_bounded/4.
85minimum_bounded(Min, Set, _, Susps):- nonvar(Set), !, kill_suspensions(Susps), Set=[Min|_].
86minimum_bounded(Min, Set, CardSet, Susps):-
87	domain(Set, [Glb:NIn,Poss:NMax]),
88	mindomain(CardSet, MinCardSet),
89%	MinPoss is MinCardSet-NIn, LengthPoss is NMax-NIn, MaxNthMinPoss is LengthPoss-MinPoss+1,
90	MaxNthMinPoss is NMax-MinCardSet+1,
91	till_nth(MaxNthMinPoss, Poss, PossTillNth),
92	PossTillNth = [MinPoss|_],
93	(Glb=[] -> MinGlb = MinPoss ; Glb=[MinGlb|_], Min #<= MinGlb),
94	(MinGlb < MinPoss -> kill_suspensions(Susps), Min #= MinGlb
95	;insert(PossTillNth, MinGlb, DomMin, _, Tail),
96	 (Tail=[], MinCardSet > NIn -> Min::PossTillNth ; Min::DomMin)
97	).
98
99%--------
100% check_lower_min(+Min, +Set)
101%  Update Set's domain due to the lower bound change of the Set's minimum function Min.
102%--
103:-demon check_lower_min/2.
104check_lower_min(Min, Set):-
105	mindomain(Min, LowerMin),
106	domain(Set, [Glb:_,Poss:NMax]),
107	(Glb=[] -> true ; Glb=[MinGlb|_], MinGlb >= LowerMin),
108	LowerMin_1 is LowerMin-1,
109	insert_count(Poss, LowerMin_1, _, _, NewPoss, 0,NOut),
110	NewNMax is NMax-NOut,
111	set_poss(Set, NewPoss, NewNMax).
112
113%--------
114% min_inst(+Min, +Set, +Susps)
115%  Update Set's domain due to the instantiation of the Set's minimum function Min.
116%--
117min_inst(Min, Set, Susps):-
118	kill_suspensions(Susps),
119	Min `@ Set,
120	domain(Set, [[Min|_]:_,Poss:NMax]),
121	insert_count(Poss, Min, _, _, NewPoss, 0,NOut),
122	NewNMax is NMax-NOut,
123	set_poss(Set, NewPoss, NewNMax).
124
125
126
127
128%--------
129% maximum_function(+Max, +Set)
130%  Inferences for Set's maximum function.
131%--
132maximum_function(Max, Set):-
133	cardinality(Set, CardSet),
134	integers_only(Set, CardSet),
135	(var(Max) -> MaxVar=Max ; MaxVar::Max),
136	set_maximum(Set, MaxVar),
137	CardSet #>= 1,
138	suspend_and_call(maximum_bounded(MaxVar,Set,CardSet,[SuspMB,SuspCUM]), 4,
139		[Set->cardinal:bounded,CardSet->fd:min], SuspMB),
140	suspend_and_call(check_upper_max(MaxVar,Set), 4, MaxVar->fd:max, SuspCUM),
141	(ground(MaxVar) -> max_inst(MaxVar,Set,[SuspMB,SuspCUM])
142	;suspend(max_inst(MaxVar,Set,[SuspMB,SuspCUM,SuspMI]), 3, MaxVar->inst, SuspMI)
143	).
144
145%--------
146% maximum_bounded(+Max, +Set, +CardSet, +Susps)
147%  Update Set's maximum function Max due to the Set's Poss change (bounded Set).
148% CardSet is Set's cardinality.
149%--
150:-demon maximum_bounded/4.
151maximum_bounded(Max, Set, _, Susps):- nonvar(Set), !, kill_suspensions(Susps), reverse(Set,[Max|_]).
152maximum_bounded(Max, Set, CardSet, Susps):-
153	domain(Set, [Glb:NIn,Poss:_NMax]),
154	mindomain(CardSet, MinCardSet),
155	MinNthMaxPoss is MinCardSet-NIn,
156	(MinNthMaxPoss > 0 -> from_nth(MinNthMaxPoss, Poss, PossFromNth) ; PossFromNth=Poss),
157	reverse(PossFromNth, [MaxPoss|_]),
158	(Glb=[] -> MaxGlb = MaxPoss ; reverse(Glb,[MaxGlb|_]), Max #>= MaxGlb),
159	(MaxGlb > MaxPoss -> kill_suspensions(Susps), Max #= MaxGlb
160	;MinCardSet > NIn, PossFromNth=[MinPoss|_], MaxGlb < MinPoss -> Max::PossFromNth
161	;Max::[MaxGlb|PossFromNth]
162	).
163
164%--------
165% check_upper_max(+Max, +Set)
166%  Update Set's domain due to the upper bound change of the Set's maximum function Max.
167%--
168:-demon check_upper_max/2.
169check_upper_max(Max, Set):-
170	maxdomain(Max, UpperMax),
171	domain(Set, [Glb:NIn,Poss:_]),
172	(Glb=[] -> true ; reverse(Glb,[MaxGlb|_]), MaxGlb =< UpperMax),
173	UpperMax1 is UpperMax+1,
174	insert_count(Poss, UpperMax1, _, NewPoss-[], _, 0,NPoss),
175	NewNMax is NIn+NPoss,
176	set_poss(Set, NewPoss, NewNMax).
177
178%--------
179% max_inst(+Max, +Set, +Susps)
180%  Update Set's domain due to the instantiation of the Set's maximum function Max.
181%--
182max_inst(Max, Set, Susps):-
183	kill_suspensions(Susps),
184	Max `@ Set,
185	domain(Set, [Glb:NIn,Poss:_]),
186	reverse(Glb, [Max|_]),
187	insert_count(Poss, Max, _, NewPoss-[], _, 0,NPoss),
188	NewNMax is NIn+NPoss,
189	set_poss(Set, NewPoss, NewNMax).
190