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) 1994-2006 Cisco Systems, Inc.  All Rights Reserved.
18%
19% Contributor(s): Pascal Brisset and Thom Fruehwirth, ECRC.
20%
21% END LICENSE BLOCK
22
23:- comment(/(chr, 1), [
24	summary:"Compile File.chr into a .pl file and load the pl file.
25
26",
27	template:"chr(+File)",
28	desc:html("   Compile File.chr containing constraint handling rules into a .pl file
29   and load the pl file.  Note that even if the file cannot be opened by
30   UNIX (Error 170), a nonempty .pl file will be produced and loaded (with
31   no effect).
32
33<P>
34"),
35	args:["+File" : "A file name (with extension chr)."],
36	resat:"   No.",
37	fail_if:"   None.\n\n",
38	exceptions:[5 : "File is not an atom or string.", 170 : "UNIX cannot open the file."],
39	eg:"   Success:
40[eclipse]: chr(minmax).
41minmax.chr compiled traceable 106874 bytes in 3.37 seconds
42minmax.pl  compiled traceable 124980 bytes in 1.83 seconds
43yes.
44
45
46
47",
48	see_also:[/(chr2pl, 1)]]).
49
50:- comment(/(chr2pl, 1), [
51	summary:"Compile File.chr into a .pl file.
52
53",
54	template:"chr2pl(+File)",
55	desc:html("   Compile File.chr containing constraint handling rules into a .pl file.
56   Note that even if the file cannot be opened by UNIX (Error 170), a
57   nonempty .pl file will be produced.
58
59<P>
60"),
61	args:["+File" : "A file name (with extension chr)."],
62	resat:"   No.",
63	fail_if:"   None.\n\n",
64	exceptions:[5 : "File is not an atom or string.", 170 : "UNIX cannot open the file."],
65	eg:"   Success:
66[eclipse]: chr(minmax).
67minmax.chr compiled traceable 106874 bytes in 3.37 seconds
68yes.
69
70
71
72",
73	see_also:[/(chr, 1)]]).
74
75:- comment(/(chr_get_constraint, 1), [
76	summary:"Remove a constraint unifying with Constraint from the constraint store.
77
78",
79	template:"chr_get_constraint(?Constraint)",
80	desc:html("   Removes a constraint unifying with Constraint from the constraint store.
81   Note that if the unification with Constraint binds variables occurring
82   also in other constraints in the constraint store, these constraints may
83   be simplified (see last examples).  Thus it is recommended to use either
84   a free variable or a term with variable arguments for Constraint.  Used
85   by advanced constraint handling rules users to manipulate themselves the
86   constraints defined by constraint handling rules.
87
88<P>
89"),
90	args:["?Constraint" : "A constraint (callable term) defined by constraint handling                rules."],
91	resat:"   Yes.",
92	fail_if:"   Fails if there is no constraint (defined by constraint handling rules)\n   in the constraint store that unifies with Constraint.\n\n",
93	eg:"   Example using the constraint handler for Booleans  bool.chr:
94[eclipse]: chr_get_constraint(C).
95no (more) solution.
96
97[eclipse]: and(X,Y,Z), or(X,Y,Z).
98
99Constraints:
100(1) X_g745 * Y_g777 = Z_g809 % pretty print of and/3 constraint
101(2) X_g745 + Y_g777 = Z_g809 % pretty print of or/3 constraint
102
103yes.
104
105[eclipse]: and(X,Y,Z), or(X,Y,Z), chr_get_constraint(C).
106
107C = X * Y = Z
108
109Constraints:
110(2) X_g765 + Y_g797 = Z_g829
111     More? (;)
112
113C = X + Y = Z
114
115Constraints:
116(1) X_g765 * Y_g797 = Z_g829
117     More? (;)
118no (more) solution.
119
120[eclipse]: and(X,Y,Z), or(X,Y,Z), chr_get_constraint(and(1,A,B)).
121% or/3 - constraint is solved when X is bound to 1
122X = 1
123Y = A
124Z = 1
125A = A
126B = 1
127
128[eclipse]: and(X,Y,Z), or(X,Y,Z), chr_get_constraint(and(1,1,0)).
129no (more) solution. % or/3 - constraint fails
130
131[eclipse]: and(X,Y,Z), chr_get_constraint(and(1,1,0)).
132
133X = 1
134Y = 1
135Z = 0
136
137
138   The predicate chr_labeling/0 can be defined as:
139labeling :-
140   chr_get_constraint(C),
141   chr_label_with(C),
142   !,
143   chr_resolve(C),
144   labeling.
145
146labeling.
147
148
149
150",
151	see_also:[/(chr_labeling, 0), /(chr_label_with, 1), /(chr_resolve, 1), /(chr_get_constraint, 1), /(chr_get_constraint, 2)]]).
152
153:- comment(/(chr_get_constraint, 2), [
154	summary:"Remove a constraint in which the variable Variable occurs and which unifies
155with Constraint from the constraint store.
156
157",
158	template:"chr_get_constraint(Variable,?Constraint)",
159	desc:html("   Removes a constraint in which the variable Variable occurs and which
160   unifies with Constraint from the constraint store.  Note that if the
161   unification with Constraint binds variables occurring also in other
162   constraints in the constraint store, these constraints may be simplified
163   (see last examples).  Thus it is recommended to use either a free
164   variable or a term with variable arguments for Constraint.  Used by
165   advanced constraint handling rules users to manipulate themselves the
166   constraints defined by constraint handling rules.  See also
167   chr_get_constraint/1 for more examples.
168
169<P>
170"),
171	args:["Variable" : "A free variable.", "?Constraint" : "A constraint (callable term) defined by constraint handling                rules."],
172	resat:"   Yes.",
173	fail_if:"   Fails if Variable is not a free variable or if there is no constraint\n   (defined by constraint handling rules) in the constraint store that\n   unifies with Constraint and in which the variable Variable occurs.\n\n",
174	eg:"   Example using the constraint handler for Booleans  bool.chr:
175[eclipse]: and(X,Y,Z), or(A,B,C), chr_get_constraint(Y,Cstr).
176
177X = X
178Z = Z
179A = A
180B = B
181Y = Y
182Cstr = X * Y = Z
183
184Constraints:
185(2) A + B = C   % pretty print for or/3 - constraint
186
187     More? (;)
188
189no (more) solution.
190
191
192   The following predicate labeling(+Varlist) labels the variables in the
193   list Varlist:
194labeling([X|VL]) :-
195   var(X),
196   chr_get_constraint(X,C),
197   chr_label_with(C),
198   !,
199   chr_resolve(C),
200   labeling([X|VL]).
201
202labeling([X|VL]) :-
203   labeling(VL).
204
205labeling([]).
206
207
208
209
210",
211	see_also:[/(chr_labeling, 0), /(chr_label_with, 1), /(chr_resolve, 1), /(chr_get_constraint, 2)]]).
212
213:- comment(/(chr_label_with, 1), [
214	summary:"Checks the label_with declarations of Constraint.
215
216",
217	template:"chr_label_with(+Constraint)",
218	desc:html("   Checks the label_with declarations of Constraint.  Used by advanced
219   constraint handling rules users to write their own labeling procedure
220   for the constraints defined by constraint handling rules.
221
222<P>
223"),
224	args:["+Constraint" : "A chr constraint."],
225	resat:"   Yes.",
226	fail_if:"   Fails if Constraint is a variable or if Constraint does not have a\n   label_with declaration or if the guard of all unifying label_with\n   declarations fail.\n\n",
227	eg:"   Given the following  label_with declaration (from the example
228   constraint handler in file  time-pc.chr:
229label_with path(N, X, Y, L, T, I) if N>1.
230
231[eclipse]: chr_label_with(path(N,X,Y,L,T,I)).
232no (more) solution.
233
234[eclipse]: chr_label_with(path(1,X,Y,L,T,I)).
235no (more) solution.
236
237[eclipse]: chr_label_with(path(2,X,Y,L,T,I)).
238X = X
239Y = Y
240L = L
241T = T
242I = I     More? (;)
243no (more) solution.
244
245
246
247
248",
249	see_also:[/(chr_labeling, 0), /(chr_resolve, 1), /(chr_get_constraint, 1), /(chr_get_constraint, 2)]]).
250
251:- comment(/(chr_labeling, 0), [
252	summary:"Activates the built-in labeling feature for constraint handling rules.
253
254",
255	template:"chr_labeling",
256	desc:html("   The constraint handling rule run-time system provides built-in labeling
257   user-defined constraints.  The built-in labeling is invoked by calling
258   the built-in predicate chr_labeling/0.  Once called, whenever no more
259   constraint handling is possible, the built-in labeling will choose a
260   constraint goal whose label_with declaration is satisfied for labeling.
261   It will introduce choices using the clauses of the constraint.
262
263<P>
264"),
265	args:[],
266	resat:"   Yes.",
267	fail_if:"   None, only on backtracking.\n\n",
268	eg:"
269   A query without and with built-in labeling:
270[eclipse]: minimum(X,Y,Z), maximum(X,Y,W), Z neq W.
271
272X = _g357
273Y = _g389
274Z = _g421
275W = _g1227
276
277Constraints:
278(1) minimum(_g357, _g389, _g421)
279(2) _g421 leq _g357
280(3) _g421 leq _g389
281(4) maximum(_g357, _g389, _g1227)
282(5) _g357 leq _g1227
283(7) _g389 leq _g1227
284(10) _g421 lss _g1227
285
286yes.
287
288[eclipse]: minimum(X,Y,Z), maximum(X,Y,W),
289           Z neq W, chr_labeling.
290
291X = Z = _g363
292Y = W = _g395
293
294Constraints:
295(10) _g363 lss _g395
296
297     More? (;)
298
299X = W = _g363
300Y = Z = _g395
301
302Constraints:
303(17) _g395 lss _g363
304yes.
305
306
307
308",
309	see_also:[/(chr_label_with, 1), /(chr_resolve, 1), /(chr_get_constraint, 1), /(chr_get_constraint, 2)]]).
310
311:- comment(/(chr_notrace, 0), [
312	summary:"Deactivates the standard or Opium debugger extension for constraint
313handling rules.
314
315",
316	template:"chr_notrace",
317	desc:html("   The query chr_trace.  deactivates the standard or opium debugger.  In
318   case of the Opium debugger, its window remains until quited.
319
320<P>
321"),
322	args:[],
323	resat:"   No.",
324	fail_if:"   None.\n\n",
325	eg:"   Success:
326[eclipse]: chr_notrace.
327yes.
328Debugger switched off
329
330
331
332",
333	see_also:[/(chr_opium, 0), /(chr_trace, 0)]]).
334
335:- comment(/(chr_opium, 0), [
336	summary:"Activates the Opium debugger and shows constraint handling.
337
338",
339	template:"chr_opium",
340	desc:html("   In order to use the Opium debugger, the debug_compile flag must have
341   been on (default) during compilation (chr to pl) and loading of the
342   produced ECLiPSe  code.  The query chr_opium.  opens an Opium window in
343   which the ECLiPSe  code will be traced.  The library chr_opium will be
344   automatically loaded.  Note that the Opium debugger for constraint
345   handling rules works with X graphic interface.  The OPIUM_WINDOW
346   environment variable must thus be set.  An Opium execution can be
347   aborted using the a.  command in Opium.
348
349<P>
350   Both debuggers display user-defined constraints and application of
351   constraint handling rules.  In the Opium debugger, this information
352   corresponds to additional ports of the debugger.  The additional ports
353   are:
354
355<P>
356  * add:  A new constraint is added to the constraint store.
357
358<P>
359  * already_in:  A constraint to be added was already present.
360
361<P>
362   The ports related to application of rules are:
363
364<P>
365  * try_rule:  A rule is tried.
366
367<P>
368  * delay_rule:  The last tried rule cannot fire because the guard did not
369    succeed.
370
371<P>
372  * fire_rule:  The last tried rule fires.
373
374<P>
375   The ports related to labeling are:
376  * try_label:  A label_with declaration is checked.
377
378<P>
379  * delay_label:  The last label_with declaration delays because the guard
380    did not succeed.
381
382<P>
383  * fire_label:  The last tried label_with declaration succeeds, so the
384    clauses of the associated constraint will be used for built-in
385    labeling.
386
387<P>
388   When displayed, each constraint is labeled with a unique integer
389   identifier.  Each rule is labeled with its name as given in the chr
390   source using the @ operator.  If a rule does not have a name, it is
391   displayed together with a unique integer identifier.
392
393<P>
394   See the extension manual chapter on constraint handling rules for more
395   information on the Opium scenario used for debugging.
396
397<P>
398"),
399	args:[],
400	resat:"   No.",
401	fail_if:"   None.\n\n",
402	see_also:[/(chr_trace, 0), /(chr_notrace, 0)]]).
403
404:- comment(/(chr_resolve, 1), [
405	summary:"Uses the Prolog clauses to solve a constraint Constraint.
406
407",
408	template:"chr_resolve(+Constraint)",
409	desc:html("   Uses the Prolog clauses to solve a constraint Constraint.  Used by
410   advanced constraint handling rules users to program labeling procedures
411   for the constraints defined by constraint handling rules.
412
413<P>
414"),
415	args:["+Constraint" : "A constraint (callable term) defined by constraint handling                rules."],
416	resat:"   Yes.",
417	fail_if:"   Fails if there are no Prolog clauses for the constraint or if the bodies\n   of all clauses fail.\n\n",
418	exceptions:[4 : "Constraint is a free variable.", 6 : "Constraint is term which is not a constraint (defined by    constraint handling rules)."],
419	eg:"   Example using the constraint handler for Booleans in file  bool.chr:
420[eclipse]: chr_resolve(X).
421instantiation fault in is_predicate(_g671 / _g639)
422
423[eclipse]: chr_resolve(and(X,Y)).
424out of range in chr_resolve(and(X,Y))
425
426[eclipse]: chr_resolve(and(X,Y,Z)).
427
428X = 0
429Y = Y
430Z = 0     More? (;)
431
432X = 1
433Y = Z
434Z = Z
435yes.
436
437[eclipse]: chr_resolve(and(a,b,c)).
438no (more) solution.
439
440
441   The predicate chr_labeling/0 can be defined as:
442labeling :-
443   chr_get_constraint(C),
444   chr_label_with(C),
445   !,
446   chr_resolve(C),
447   labeling.
448
449labeling.
450
451
452
453",
454	see_also:[/(chr_labeling, 0), /(chr_label_with, 1), /(chr_get_constraint, 1), /(chr_get_constraint, 2)]]).
455
456:- comment(/(chr_trace, 0), [
457	summary:"Activates the standard debugger and shows constraint handling.
458
459",
460	template:"chr_trace",
461	desc:html("   In order to use the standard debugger, the debug_compile must have been
462   on (default) during compilation (chr to pl) and loading of the produced
463   ECLiPSe  code.  The query chr_trace.  activates the standard debugger
464   showing more information about the handling of constraints.  In the
465   standard debugger, user-defined constraints are treated as predicates
466   and the information about application of constraint handling rules is
467   displayed without stopping.  The additional information displayed is:
468
469<P>
470  * add:  A new constraint is added to the constraint store.
471
472<P>
473  * already_in:  A constraint to be added was already present.
474
475<P>
476   The ports related to application of rules are:
477
478<P>
479  * try_rule:  A rule is tried.
480
481<P>
482  * delay_rule:  The last tried rule cannot fire because the guard did not
483    succeed.
484
485<P>
486  * fire_rule:  The last tried rule fires.
487
488<P>
489   The ports related to labeling are:
490  * try_label:  A label_with declaration is checked.
491
492<P>
493  * delay_label:  The last label_with declaration delays because the guard
494    did not succeed.
495
496<P>
497  * fire_label:  The last tried label_with declaration succeeds, so the
498    clauses of the associated constraint will be used for built-in
499    labeling.
500
501<P>
502   When displayed, each constraint is labeled with a unique integer
503   identifier.  Each rule is labeled with its name as given in the chr
504   source using the @ operator.  If a rule does not have a name, it is
505   displayed together with a unique integer identifier.
506
507<P>
508"),
509	args:[],
510	resat:"   No.",
511	fail_if:"   None.\n\n",
512	eg:"   Success:
513[eclipse]: chr_trace.
514yes.
515Debugger switched on - creep mode
516[eclipse]: notrace.     % trace only constraints
517Debugger switched off
518yes.
519[eclipse]: minimum(X,Y,Z), maximum(X,Y,Z).
520% trace edited to show only firing rules
521
522ADD (1) minimum(X, Y, Z)
523TRY (1) minimum(_g218, _g220, _g222) with propagation
524RULE 'propagation' FIRED
525
526 ADD (2) leq(_g665, _g601)
527
528 ADD (3) leq(_g665, Var)
529
530ADD (4) maximum(_g601, Var, _g665)
531TRY (4) maximum(_g601, Var, _g665) with propagation
532RULE 'propagation' FIRED
533
534 ADD (5) leq(_g601, _g665)
535 TRY (5) leq(_g601, _g665) (2) leq(_g665, _g601) with antisymmetry
536 RULE 'antisymmetry' FIRED
537
538TRY (4) maximum(_g601, Var, _g601) with max_eq
539RULE 'max_eq' FIRED
540
541 ADD (6) leq(Var, _g601)
542 TRY (3) leq(_g601, Var) (6) leq(Var, _g601) with antisymmetry
543 RULE 'antisymmetry' FIRED
544
545TRY (1) minimum(_g601, _g601, _g601) with min_eq
546RULE 'min_eq' FIRED
547
548 ADD (7) leq(_g601, _g601)
549 TRY (7) leq(_g601, _g601) with reflexivity
550 RULE 'reflexivity' FIRED
551
552X = Y = Z = _g558
553yes.
554
555
556
557",
558	see_also:[/(chr_opium, 0), /(chr_notrace, 0)]]).
559