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% This library contains the predicates used in the code produced by
24% the chr2pl compiler
25
26
27:- module(chr).
28
29:- pragma(deprecated_warnings(off)).
30
31:- comment(categories, ["Constraints","Techniques"]).
32:- comment(summary, "Constraint Handling Rules Library - obsolescent, use library(ech) instead").
33:- comment(author, "Pascal Brisset and Thom Fruehwirth, ECRC").
34:- comment(copyright, "1994-2006 Cisco Systems, Inc").
35:- comment(date, "$Date: 2009/07/16 09:11:25 $").
36:- comment(status, deprecated).
37:- comment(include, "chr_doc.pl").
38
39% This predicate called for the labeling must be dynamic as soon as
40% several handlers are loaded in the same session: the predicate is the
41% scatterred in several files.
42:- export initialization(dynamic('CHRlabel_with' /3)).
43
44%%%%%% Check of a guard %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
45
46% The guard (Goal) is simply called and it's checked that there are no
47% delayed goals left after
48chr_macro(no_delayed_goals(Goal),
49  ( sepia_kernel:last_suspension(LD),
50    Goal,
51    true,                   % force all wakings
52    sepia_kernel:new_suspensions(LD, []))).
53
54% Before the guard (Goal) is called, a 'fail' is attached to every variable
55% of the Goal. Then, as soon as one of these variables is touched
56% (unified), the call will fail.
57chr_macro(no_global_bindings(Goal, Globals),
58  ( make_suspension('CHRfail', 1, Susp),
59    IS,
60    sepia_kernel:last_suspension(LD),
61    Goal,
62    true,                   % force all wakings
63    sepia_kernel:new_suspensions(LD, []),
64    kill_suspension(Susp))) :-
65  IS = insert_suspension(Globals, Susp, constrained of suspend, suspend).
66
67
68:- export no_delayed_goals/1.
69:- inline(no_delayed_goals/1, chr_macro/2).
70no_delayed_goals(Goal) :-
71	no_delayed_goals(Goal).
72
73:- export no_global_bindings/2.
74:- inline(no_global_bindings/2, chr_macro/2).
75no_global_bindings(Goal, Globals) :-
76	no_global_bindings(Goal, Globals).
77
78:- export portray('CHRhead_not_kept'/1, tr_chr/2, []).
79
80:- reexport(chr2pl).
81
82:- import sepia_kernel.
83
84%%%%%%%% Exported predicates %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
85:- export
86	'CHRget_delayed_goals' /2,
87	'CHRkill' /1,
88	'CHRalready_in' /1,
89	'CHRkeep_heads_checking' /6,
90	'CHRkeep_heads_checking' /4,
91	'CHRcheck_and_mark_applied' /5,
92	'CHRcheck_and_mark_applied' /2,
93	'CHRgen_num' /1,
94	'CHRvar' /1,
95	'CHRhead_not_kept' /1,
96	'CHRfail' /0,
97	'CHRnonvar' /1,
98	'CHRdelay' /2,
99	'CHR=' /2,
100	coca /1,
101	chr_trace /0,
102	chr_notrace /0,
103%	chr_opium /0,
104	chr_get_constraint /1,
105	chr_get_constraint /2,
106	chr_label_with/1,
107	chr_delayed_goals_handler/3,
108	chr_start_handler/3,
109	tr_chr/2,
110	chr_resolve/1,
111	chr_labeling/0.
112
113
114:- tool('CHRdelay'/2, 'CHRdelay'/3),
115   tool(chr_labeling/0, chr_labeling/1),
116   tool(chr_resolve/1, chr_resolve/2),
117   tool(chr_label_with/1, chr_label_with/2).
118
119:- coroutine.
120
121
122% CHR attribute: added for ECLiPSe 5.8 and later.
123% This was necessary because of a change in semantics of the constrained-
124% waking list (var-var unifications now only wake suspensions which are
125% in the constrained-lists of both variables). This unify_chr handler forces
126% _all_ constrained-suspensions to be woken when two chr-variables get
127% unified, which is wasteful, but corresponds to the semantics before 5.8.
128% Note that we arbitrarily wake only one variable's constrained-list
129% because the constraints should be able to find their partner either way.
130
131:- meta_attribute(chr, [unify:unify_chr/2]).
132
133unify_chr(_Y, AttrX) :-
134	var(AttrX).
135unify_chr(Y, AttrX) :-
136	nonvar(AttrX),
137	unify_any_chr(Y, AttrX).
138
139    unify_any_chr(Y{AttrY}, AttrX) ?- !,
140	unify_chr_chr(Y, AttrX, AttrY).
141    unify_any_chr(_Y, _AttrX).
142
143    unify_chr_chr(_Y, AttrX, AttrY) :-
144	var(AttrY),
145	AttrY = AttrX.			% transfer the attribute
146    unify_chr_chr(Y, _AttrX, AttrY) :-
147	nonvar(AttrY),
148	notify_constrained(Y).		% wake either X's or Y's list
149
150
151mark_as_chr_variables(Term) :-
152	term_variables(Term, Vars),
153	( foreach(Var,Vars) do
154	    mark_as_chr_variable(Var)
155	).
156
157    mark_as_chr_variable(_{Attr}) ?-
158	Attr = chr.
159    mark_as_chr_variable(X) :-
160	free(X),
161	add_attribute(X, chr).
162
163
164%%%%%%%% CHR primitives used by the code produced by chr2pl %%%%%%%%%%%%%%%
165
166
167%%%%% Return the delayed goals (which may contain a partner for a double-headed
168% rule). If there is a share variable, goals delayed
169'CHRget_delayed_goals'(X, DG) :-
170	nonground(X, Var), !,
171	delayed_goals(Var, DG).
172'CHRget_delayed_goals'(_, DG) :-
173	delayed_goals(DG).
174
175
176%%%%% Set the kill flag to 'true'
177'CHRkill'(true).
178
179
180
181%%%% Checks that a constraint is already in the constraint store (it's usually
182% called each time a constraint is about to be added
183% The check is done only if the goal is not ground
184'CHRalready_in'(Goal) :-
185	arg(1, Goal, Constraint),
186	( nonground(Constraint, OneVar) ->
187	    delayed_goals(OneVar, Goals)
188	 ;
189	    delayed_goals(Goals)
190	),
191	constraint_member(Goals, Constraint).
192
193% The list of suspensions is erminated with a variable
194constraint_member([Goal | _], Constraint1)
195 ?-
196	functor(Goal, _, 4),     %%% The goal is a CHR constraint
197	arg(1, Goal, Constraint2),
198	arg(2, Goal, KF),
199	var(KF), %%% Because of waking order, a delayed constraint may have
200	         %%% its Flag set
201	Constraint2 == Constraint1,
202	!.
203constraint_member([_ | Goals], Goal)
204 ?-
205	constraint_member(Goals, Goal).
206
207
208% When a constraint C is about to be added, in the case that this constraint
209% may be equal to one head H of the rule (recognised statically), a test is
210% done to know if C is really equal to H.
211% The following predicates do the check, possibly kill the constraint H
212% and return a flag set to true if the constraint should be added
213
214% Comparaison with one head
215'CHRkeep_heads_checking'(H, KF, G, CallG) :-
216	( H == G -> true
217         ; 'CHRkill'(KF), CallG = true
218        ).
219
220% Comparaison with two heads
221'CHRkeep_heads_checking'(H1, KF1, H2, KF2, G, CallG) :-
222	( H1 == G -> KF2 = true
223         ; H2 == G -> KF1 = true
224         ; 'CHRkill'(KF1), 'CHRkill'(KF2), CallG = true
225        ).
226
227
228
229%%%%% An augmentation rule should not be applied twice on the same constraints.
230% To avoid such a redundance, a list of pairs (rule, partner) is associated
231% to every constraint. When a augmentation rule is about to be tried
232% this list is checked
233'CHRcheck_and_mark_applied'(RuleName, _KF1, KF2, [[RuleName | KF2] | _PA1], _PA2)
234 ?-
235	!, %%% Rule already used with this partner
236	fail.
237'CHRcheck_and_mark_applied'(RuleName, KF1, KF2, [_ | PA1], PA2)
238 ?-
239	!,
240	'CHRcheck_and_mark_applied'(RuleName, KF1, KF2, PA1, PA2).
241'CHRcheck_and_mark_applied'(RuleName, KF1, KF2, PA1, PA2) :-
242	PA1 = [[RuleName | KF2] | _New_PA1],
243	name_for_the_partner(RuleName, PartnerRuleName),
244	mark_applied([PartnerRuleName | KF1], PA2).
245
246% The rule    r @ h(X), h(Y) ==> Body
247% should fire with H1, H2  and   H2, H1
248% so the name of the rule is not enough, the position of the head must also
249% be stored.
250name_for_the_partner('12'(Name), '21'(Name)) :- !.
251name_for_the_partner('21'(Name), '12'(Name)) :- !.
252name_for_the_partner(Name, Name).
253
254% Goes to the tail (variable) of the list and add a new element.
255mark_applied(X, [_ | PA])
256 ?-
257	!,
258	mark_applied(X, PA).
259mark_applied(X, [X | _New_PA]).
260
261
262%%%%% Same check for simple headed rules
263'CHRcheck_and_mark_applied'(RuleName, [RuleName | _PA])
264 ?-
265	!,
266	fail.
267'CHRcheck_and_mark_applied'(RuleName, [_ | PA])
268 ?-
269	!,
270	'CHRcheck_and_mark_applied'(RuleName, PA).
271'CHRcheck_and_mark_applied'(RuleName, PA) :-
272	PA = [RuleName | _New_PA].
273
274
275%%%%% gensym for numbering contraints, the number is used in the debugger
276:- local variable(gen_num).
277'CHRgen_num'(X) :-
278	getval(gen_num, X),
279	incval(gen_num).
280
281
282%%%%% These predicates are renamed in order to be hidden in the debugger
283'CHRnonvar'(X) :- nonvar(X).
284'CHRvar'(X) :- var(X).
285'CHRhead_not_kept'(true)
286 ?-
287	true.
288'CHR='(X, X).
289'CHRtrue'.
290'CHRfail' :- fail.
291
292
293%%%%% Delays on all the variables in inst, bound suspended lists
294'CHRdelay'(Vars, Goal, Module) :-
295	make_suspension(Goal, 3, Susp, Module),
296	mark_as_chr_variables(Vars),
297	insert_suspension(Vars, Susp, constrained of suspend, suspend).
298
299%%%%%%%% User primitives %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
300
301:- setval(chr_trace, off).
302
303%%% Starts the debug mode using Opium
304%chr_opium :-
305%	get_flag(installation_directory, ID),
306%	concat_string(["make(chr_op,chr_op,[active,untraceable,global],'", ID, "/lib/chr/','", ID, "/lib/chr/')"], Init),
307%	opium(init(Init)),
308%	set_flag((;)/2, leash, notrace),
309%	set_flag(coca/1, leash, stop),
310%	setval(chr_trace, opium).
311
312chr_trace :-
313	set_flag(coca/1, leash, notrace),
314	setval(chr_trace, dbg),
315	set_flag(debugging, creep).
316
317%%% Stops the debugger
318chr_notrace :-
319	set_flag(coca/1, leash, notrace),
320	setval(chr_trace, off),
321	set_flag(debugging, nodebug).
322
323
324
325%%% labeling
326% While there are sone contraints in the store, one is picked and tried to
327% be solved using the 'label_with' rules and the Prolog clauses
328chr_labeling(Module):-
329        ( get_one_constraint(Constraint, Nb, KF),
330	  call('CHRlabel_with'(Constraint, Goal, Nb), Module),
331	  !,
332	  KF = true,
333	  call(Goal, Module),
334	  chr_labeling(Module)
335	;
336	  'CHRtrue'
337	).
338
339get_one_constraint(Constraint, Nb, KF) :-
340	delayed_goals(DG),
341	member(C, DG),
342	C =.. [_, Constraint, KF, _PA, Nb].
343
344
345%%% Does a check using a label_with declaration
346chr_label_with(Constraint, Module) :-
347	call('CHRlabel_with'(Constraint, _Goal, 0), Module).
348
349
350
351%%% Returns (by backtrack) the current constraints
352chr_get_constraint(Constraint) :-
353	delayed_goals(DGs),
354	member(DG, DGs),
355	DG =.. [_, Constraint, true, _PA, _Nb].
356
357
358chr_get_constraint(Var, Constraint) :-
359	delayed_goals(Var, DGs),
360	member(DG, DGs),
361	DG =.. [_, Constraint, true, _PA, _Nb].
362
363
364%%% Solve a constraint using the Prolog clauses
365chr_resolve(Constraint, Module) :-
366	functor(Constraint, Functor, Arity),
367	concat_atom(['clause_', Functor], Goal_Functor),
368	( call(is_predicate(Goal_Functor/Arity), Module)
369         ->
370	  Constraint =.. [Functor | Args],
371	  Goal =.. [Goal_Functor | Args],
372	  call(Goal, Module)
373         ;
374	  error(6, chr_resolve(Constraint))
375        ).
376
377
378%%%%%%%%%% Debugger %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
379
380% coca/1 goals are put in the produced code if the flag 'debug_compile' is
381% set. These goals are the ones recognised by Opium
382% Note about the name: just because it's related to Opium
383coca(try_double(Nb1, H1, Nb2, H2, H1C, H2C, Kind, GC, BC, Rule_Name)) :-
384	chr_dbg(try_double(Nb1,H1,Nb2, H2, H1C, H2C, Kind, GC, BC, Rule_Name)),
385	'CHRtrue'
386        ;
387	coca(delayed_rule(Rule_Name)), !, 'CHRfail'.
388coca(try_rule(Nb, H, Rule_Name, HC, Kind, GuardC, BodyC)) :-
389	chr_dbg(try_rule(Nb, H, Rule_Name, HC, Kind, GuardC, BodyC)),
390	'CHRtrue'
391        ;
392	coca(delayed_rule(Rule_Name)), !, 'CHRfail'.
393coca(try_clause(Nb, Head, HeadC, GuardC)) :-
394	chr_dbg(try_clause(Nb, Head, HeadC, GuardC)),
395	'CHRtrue'
396        ;
397	coca(call_delayed), !, 'CHRfail'.
398coca(Event) :-
399	chr_dbg(Event).
400
401
402
403chr_dbg(Event) :-
404	getval(chr_trace, dbg), !,
405	treat_chr_dbg(Event).
406chr_dbg(_).
407
408
409treat_chr_dbg(add_one_constraint(Nb, Constraint)) :-
410	printf(debug_output, "ADD (%d) %p\n", [Nb, Constraint]).
411treat_chr_dbg(already_in) :-
412	printf(debug_output, "CONSTRAINT ALREADY THERE\n", []).
413treat_chr_dbg(try_clause(Nb, Constraint, Head, Guard)) :-
414	printf(debug_output, "TRY LABEL (%d) %p\nwith\nlabel_with %p if %p\n", [Nb, Constraint, Head, Guard]).
415treat_chr_dbg(clause_fired(CstNb)) :-
416	printf(debug_output, "LABEL FIRED with %d\n", [CstNb]).
417treat_chr_dbg(call_delayed) :-
418	printf(debug_output, "LABEL DELAYED\n", []).
419treat_chr_dbg(try_rule(Nb, Goal, Rule_Name, Head, Kind, Guard, Body)) :-
420	printf(debug_output, "TRY (%d) %p\nwith\n", [Nb, Goal]),
421	( Kind = replacement
422	 ->
423	  Connector = "<=>"
424	;
425	  Connector = "==>"
426	),
427	( nonvar(Rule_Name), Rule_Name = anonymous(Name)
428	 ->
429	  printf(debug_output, "%s: %p %s %p | %p\n", [Name, Head, Connector, Guard, Body])
430	;
431	  printf(debug_output, "%p\n", [Rule_Name])
432	).
433treat_chr_dbg(try_double(Nb1, Goal1, Nb2, Goal2, Head1, Head2, Kind, Guard, Body, Rule_Name)) :-
434	printf(debug_output, "TRY (%d) %p (%d) %p\nwith\n", [Nb1, Goal1, Nb2, Goal2]),
435	double_rule(Head1, Head2, Kind, Guard, Body, Rule),
436	( nonvar(Rule_Name), Rule_Name = anonymous(Name)
437	 ->
438	  printf(debug_output, "%s: %p\n", [Name, Rule])
439	;
440	  printf(debug_output, "%p\n", [Rule_Name])
441	).
442treat_chr_dbg(fired_rule(Rule_Name)) :-
443	( nonvar(Rule_Name), Rule_Name = anonymous(Name)
444	 ->
445	  printf(debug_output, "RULE '%s' FIRED\n", [Name])
446	 ;
447	  printf(debug_output, "RULE '%p' FIRED\n", [Rule_Name])
448	).
449treat_chr_dbg(delayed_rule(Rule_Name)) :-
450        ( nonvar(Rule_Name), Rule_Name = anonymous(Name)
451	 ->
452	  printf(debug_output, "RULE '%s' DELAYED\n", [Name])
453	 ;
454	  printf(debug_output, "RULE '%p' DELAYED\n", [Rule_Name])
455	).
456
457
458%%% Special case for rules which have been translated for keeping heads
459double_rule(Head1, Head2, Kind, Guard, Body, Rule) :-
460	(Kind = keep_first ; Kind = keep_second),
461	remove_keep_heads_checking(Guard, G),
462	!,
463	remove_head_not_kept(Body, B),
464	Rule = (Head1, Head2 <=> G | B).
465double_rule(Head1, Head2, Kind, Guard, Body, Rule) :-
466	( Kind = augmentation
467	 ->
468	  Rule = (Head1, Head2 ==> Guard | Body)
469	; Kind = replacement
470	 ->
471	  Rule = (Head1, Head2 <=> Guard | Body)
472	; Kind = keep_first
473	 ->
474	  Rule = (Head1 \ Head2 <=> Guard | Body)
475	; Kind = keep_second
476	 ->
477	  Rule = (Head1 \ Head2 <=> Guard | Body)
478	).
479
480
481remove_keep_heads_checking((G1, G2), G) :-
482	remove_keep_heads_checking(G2, G3),
483	( G3 = true -> G = G1 ; G = (G1, G3)).
484remove_keep_heads_checking('CHRkeep_heads_checking'(_,_,_,_,_,_), true).
485remove_keep_heads_checking('CHRkeep_heads_checking'(_,_,_,_), true).
486
487
488remove_head_not_kept((G1, G2), (G11, G21)) :- !,
489	remove_head_not_kept(G1, G11),
490	remove_head_not_kept(G2, G21).
491remove_head_not_kept(('CHRhead_not_kept'(_) -> Constraint ; true), Constraint) :- !.
492remove_head_not_kept(G, G).
493
494
495%%%%%%%%%%%% HANDLERS %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
496
497%%% Numbering of constraints
498%%% The counter is initialized statically and dynamically before each
499%%% query
500:- setval(gen_num, 1).
501
502:- define_error("Original handler 154", N),
503   setval(orig_handler_154, N),
504   get_error_handler(154, Handler, Module154),
505   (import Handler from Module154),
506   set_error_handler(N, Handler).
507
508chr_start_handler(_, Goal, Module) :-
509	setval(gen_num, 1),
510	getval(orig_handler_154, N),
511	error(N, Goal, Module).
512
513:- set_error_handler(154, chr_start_handler/3).
514
515
516
517%%% Display of the delayed goals after a computation
518%%% A special printer must be used for constraints
519%%% The original handler for printing delayed goals is replaced by a new one
520%%% which, after displaying the constraints, calls the original handler.
521%%% The link to the original handler is done by a user defined exception.
522
523:- define_error("Original handler 273", N),
524   setval(orig_handler_273, N),
525   get_error_handler(273, Handler, Module273),
526   (import Handler from Module273),
527   set_error_handler(N, Handler).
528
529chr_delayed_goals_handler(_, DG, Module) :-
530	( DG \= []
531         ->
532	  write(answer_output, "\n\nConstraints:\n"),
533	  print_constraints(DG, Rest)
534	; Rest = DG
535        ),
536	( Rest = [_H | _T]
537         ->
538	  getval(orig_handler_273, N),
539	  error(N, Rest, Module)
540        ; true
541        ).
542
543:- set_error_handler(273, chr_delayed_goals_handler/3).
544
545%%% Print the current constraints on the current output, kills them and
546% returns the other delayed goals.
547% The user predicate chr_portray/2, if it exists, is called to do a
548% 'pretty' printing
549print_constraints([], []).
550print_constraints([Susp | DG], Rest) :-
551	suspension_to_goal(Susp, Delayed, _),
552	Delayed =.. [PredName, _Constraint, KF, _PA, Nb],
553	atom_string(PredName, PredNameS),
554	append_strings("CHR", _, PredNameS),
555	!,
556	( integer(Nb)
557         ->
558	  call(printf("(%d) %QVw\n", [Nb, Delayed]), eclipse)
559	 ; %%% constraint not labelled (nodbgcomp)
560	  call(printf("%QVw\n", [Delayed]), eclipse)
561	),
562        KF = true,
563        print_constraints(DG, Rest).
564print_constraints([D | DG], [D | Rest]) :-
565        print_constraints(DG, Rest).
566
567
568
569tr_chr(Clause_Goal, Goal) :-
570	Clause_Goal =.. [Clause_Name | Args],
571	atom_string(Clause_Name, Clause_String),
572	append_strings("clause_", S, Clause_String),
573	!,
574	atom_string(N, S),
575	Goal =.. [N | Args].
576tr_chr('CHRhead_not_kept'(_), 'HEAD REMOVED') :- !.
577% For macros defined in the produced code
578tr_chr(CHR, Co) :-
579	arg(1, CHR, Co).
580
581%%%%%%%%%% Setting flags fo the debugger %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
582
583:- set_flag(coca/1, leash, notrace).
584
585:- (untraceable chr_dbg/1), skipped chr_dbg/1.
586
587:- untraceable chr_labeling/1.
588
589:- set_flag('CHR='/2, leash, notrace).
590
591:- set_flag('CHRget_delayed_goals'/2, skip, on), set_flag('CHRget_delayed_goals'/2, leash, notrace).
592
593:- set_flag('CHRalready_in'/1, skip, on), set_flag('CHRalready_in'/1, leash, notrace).
594
595:- set_flag(subcall/2, leash, notrace), set_flag(call/2, leash, notrace).
596
597:- set_flag('CHRcheck_and_mark_applied'/5, leash, notrace), set_flag('CHRcheck_and_mark_applied'/5, skip, on).
598
599:- set_flag('CHRcheck_and_mark_applied'/2, leash, notrace), set_flag('CHRcheck_and_mark_applied'/2, skip, on).
600
601:- set_flag('CHRgen_num'/1, skip, on), set_flag('CHRgen_num'/1, leash, notrace).
602
603:- skipped(('CHRkeep_heads_checking'/6, 'CHRkeep_heads_checking'/4)),
604   untraceable(('CHRkeep_heads_checking'/6, 'CHRkeep_heads_checking'/4)).
605
606:- set_flag('CHRnonvar'/1, leash, notrace), set_flag('CHRnonvar'/1, skip, on).
607:- set_flag('CHRvar'/1, leash, notrace), set_flag('CHRvar'/1, skip, on).
608
609:- set_flag('CHRfail'/0, leash, notrace), set_flag('CHRfail'/0, skip, on).
610
611:- set_flag('CHRkill'/1, leash, notrace).
612
613:- set_flag('CHRtrue'/0, leash, notrace).
614
615:- set_flag('true'/0, leash, notrace).
616
617:- set_flag(new_suspensions/2, leash, notrace).
618
619:- set_flag(!/0, leash, notrace).
620
621
622:- set_flag('CHRdelay'/2, leash, notrace), set_flag('CHRdelay'/3, leash, notrace).
623
624
625:- (import subcall/3 from sepia_kernel), set_flag(subcall/3, leash, notrace).
626
627
628:- set_flag(chr_trace/0, skip, on), set_flag(chr_trace/0, leash, notrace).
629:- set_flag(chr_notrace/0, skip, on), set_flag(chr_notrace/0, leash, notrace).
630:- set_flag(get_one_constraint/3, leash, notrace), set_flag(get_one_constraint/3, skip, on).
631
632:- set_flag(kill_suspension/1, leash, notrace).
633:- skipped (chr_get_constraint/2, chr_get_constraint/1).
634:- skipped('CHRhead_not_kept'/1).
635:- skipped chr_resolve/1.
636:- untraceable(chr_label_with/2).
637%:- untraceable(insert_suspension/4).
638