/* Generated by CHR bootstrap compiler From: /opt/logicmoo_workspace/swipl-devel/packages/chr/chr_translate_bootstrap1.chr Date: Fri Sep 15 03:25:25 2023 DO NOT EDIT. EDIT THE CHR FILE INSTEAD */ :- module(chr_translate_bootstrap1, [ chr_translate/2 ]). :- use_module(chr(chr_runtime)). :- style_check(- (discontiguous)). :- style_check(-singleton). :- style_check(-no_effect). :- use_module(chr(chr_runtime)). :- style_check(- (discontiguous)). :- use_module(library(lists)). :- use_module(library(ordsets)). :- use_module(library(dialect/hprolog)). :- use_module(chr(pairlist)). :- include(chr(chr_op2)). chr_translate(A, B) :- init_chr_pp_flags, partition_clauses(A, C, D, E), ( C==[] -> B=E ; check_rules(D, C), unique_analyse_optimise(D, F), check_attachments(F), set_constraint_indices(C, 1), store_management_preds(C, G), constraints_code(C, F, H), append([E, G, H], B) ), chr_clear. store_management_preds(A, B) :- generate_attach_detach_a_constraint_all(A, C), generate_attach_increment(D), generate_attr_unify_hook(E), append([C, D, E], B). partition_clauses([], [], [], []). partition_clauses([A|B], C, D, E) :- ( rule(A, F) -> C=G, D=[F|H], E=I ; is_declaration(A, J) -> append(J, G, C), D=H, E=I ; is_module_declaration(A, K) -> target_module(K), C=G, D=H, E=[A|I] ; A=handler(_) -> format('CHR compiler WARNING: ~w.\n', [A]), format(' `--> SICStus compatibility: ignoring handler/1 declaration.\n', []), C=G, D=H, E=I ; A=rules(_) -> format('CHR compiler WARNING: ~w.\n', [A]), format(' `--> SICStus compatibility: ignoring rules/1 declaration.\n', []), C=G, D=H, E=I ; A=(:-chr_option(L, M)) -> handle_option(L, M), C=G, D=H, E=I ; C=G, D=H, E=[A|I] ), partition_clauses(B, G, H, I). is_declaration(A, B) :- A=(:-C), ( C=..[chr_constraint, D] ; C=..[chr_constraint, D] ), conj2list(D, B). rule(A, B) :- A= @(C, D), !, rule(D, yes(C), B). rule(A, B) :- rule(A, no, B). rule(A, B, C) :- A=pragma(D, E), !, is_rule(D, F, G), conj2list(E, H), C=pragma(F, G, H, B). rule(A, B, C) :- is_rule(A, D, E), C=pragma(D, E, [], B). is_rule(A, B, C) :- A= ==>(D, E), !, conj2list(D, F), get_ids(F, G, H), C=ids([], G), ( E=(I| J) -> B=rule([], H, I, J) ; B=rule([], H, true, E) ). is_rule(A, B, C) :- A= <=>(D, E), !, ( E=(F| G) -> H=F, I=G ; H=true, I=E ), ( D= \(J, K) -> conj2list(J, L), conj2list(K, M), get_ids(L, N, O, 0, P), get_ids(M, Q, R, P, _), C=ids(Q, N) ; conj2list(D, M), O=[], get_ids(M, Q, R), C=ids(Q, []) ), B=rule(R, O, H, I). get_ids(A, B, C) :- get_ids(A, B, C, 0, _). get_ids([], [], [], A, A). get_ids([A|B], [C|D], [E|F], C, G) :- ( A= #(E, C) -> true ; E=A ), H is C+1, get_ids(B, D, F, H, G). is_module_declaration((:-module(A)), A). is_module_declaration((:-module(A, _)), A). check_rules(A, B) :- check_rules(A, B, 1). check_rules([], _, _). check_rules([A|B], C, D) :- check_rule(A, C, D), E is D+1, check_rules(B, C, E). check_rule(A, B, C) :- A=pragma(D, _, E, _), D=rule(F, G, _, _), append(F, G, H), check_head_constraints(H, B, A, C), check_pragmas(E, A, C). check_head_constraints([], _, _, _). check_head_constraints([A|B], C, D, E) :- functor(A, F, G), ( member(F/G, C) -> check_head_constraints(B, C, D, E) ; format('CHR compiler ERROR: Undeclared constraint ~w in head of ~@.\n', [F/G, format_rule(D, E)]), format(' `--> Constraint should be on of ~w.\n', [C]), fail ). check_pragmas([], _, _). check_pragmas([A|B], C, D) :- check_pragma(A, C, D), check_pragmas(B, C, D). check_pragma(A, B, C) :- var(A), !, format('CHR compiler ERROR: invalid pragma ~w in ~@.\n', [A, format_rule(B, C)]), format(' `--> Pragma should not be a variable!\n', []), fail. check_pragma(passive(A), B, C) :- !, B=pragma(_, ids(D, E), _, _), ( memberchk_eq(A, D) -> true ; memberchk_eq(A, E) -> true ; format('CHR compiler ERROR: invalid identifier ~w in pragma passive in ~@.\n', [A, format_rule(B, C)]), fail ). check_pragma(A, B, C) :- A=unique(_, _), !, format('CHR compiler WARNING: undocumented pragma ~w in ~@.\n', [A, format_rule(B, C)]), format(' `--> Only use this pragma if you know what you are doing.\n', []). check_pragma(A, B, C) :- A=already_in_heads, !, format('CHR compiler WARNING: currently unsupported pragma ~w in ~@.\n', [A, format_rule(B, C)]), format(' `--> Pragma is ignored. Termination and correctness may be affected \n', []). check_pragma(A, B, C) :- A=already_in_head(_), !, format('CHR compiler WARNING: currently unsupported pragma ~w in ~@.\n', [A, format_rule(B, C)]), format(' `--> Pragma is ignored. Termination and correctness may be affected \n', []). check_pragma(A, B, C) :- format('CHR compiler ERROR: invalid pragma ~w in ~@.\n', [A, format_rule(B, C)]), format(' `--> Pragma should be one of passive/1!\n', []), fail. format_rule(A, B) :- A=pragma(_, _, _, C), ( C=yes(D) -> write('rule '), write(D) ; write('rule number '), write(B) ). handle_option(A, B) :- var(A), !, format('CHR compiler ERROR: ~w.\n', [option(A, B)]), format(' `--> First argument should be an atom, not a variable.\n', []), fail. handle_option(A, B) :- var(B), !, format('CHR compiler ERROR: ~w.\n', [option(A, B)]), format(' `--> Second argument should be a nonvariable.\n', []), fail. handle_option(A, B) :- option_definition(A, B, C), !, set_chr_pp_flags(C). handle_option(A, _) :- \+ option_definition(A, _, _), !. handle_option(A, B) :- findall(C, option_definition(A, C, _), D), format('CHR compiler ERROR: ~w.\n', [option(A, B)]), format(' `--> Invalid value ~w: should be one of ~w.\n', [B, D]), fail. option_definition(optimize, experimental, A) :- A=[unique_analyse_optimise-on, check_unnecessary_active-full, reorder_heads-on, set_semantics_rule-on, check_attachments-on, guard_via_reschedule-on]. option_definition(optimize, full, A) :- A=[unique_analyse_optimise-on, check_unnecessary_active-full, reorder_heads-on, set_semantics_rule-on, check_attachments-on, guard_via_reschedule-on]. option_definition(optimize, sicstus, A) :- A=[unique_analyse_optimise-off, check_unnecessary_active-simplification, reorder_heads-off, set_semantics_rule-off, check_attachments-off, guard_via_reschedule-off]. option_definition(optimize, off, A) :- A=[unique_analyse_optimise-off, check_unnecessary_active-off, reorder_heads-off, set_semantics_rule-off, check_attachments-off, guard_via_reschedule-off]. option_definition(debug, off, A) :- A=[debugable-off]. option_definition(debug, on, A) :- A=[debugable-on]. option_definition(check_guard_bindings, on, A) :- A=[guard_locks-on]. option_definition(check_guard_bindings, off, A) :- A=[guard_locks-off]. init_chr_pp_flags :- chr_pp_flag_definition(A, [B|_]), set_chr_pp_flag(A, B), fail. init_chr_pp_flags. set_chr_pp_flags([]). set_chr_pp_flags([A-B|C]) :- set_chr_pp_flag(A, B), set_chr_pp_flags(C). set_chr_pp_flag(A, B) :- atomic_concat('$chr_pp_', A, C), nb_setval(C, B). chr_pp_flag_definition(unique_analyse_optimise, [on, off]). chr_pp_flag_definition(check_unnecessary_active, [full, simplification, off]). chr_pp_flag_definition(reorder_heads, [on, off]). chr_pp_flag_definition(set_semantics_rule, [on, off]). chr_pp_flag_definition(guard_via_reschedule, [on, off]). chr_pp_flag_definition(guard_locks, [on, off]). chr_pp_flag_definition(check_attachments, [on, off]). chr_pp_flag_definition(debugable, [off, on]). chr_pp_flag(A, B) :- atomic_concat('$chr_pp_', A, C), nb_getval(C, D), ( D==[] -> chr_pp_flag_definition(A, [B|_]) ; D=B ). generate_attach_detach_a_constraint_all([], []). generate_attach_detach_a_constraint_all([A|B], C) :- ( is_attached(A) -> generate_attach_a_constraint(A, D), generate_detach_a_constraint(A, E) ; D=[], E=[] ), generate_attach_detach_a_constraint_all(B, F), append([D, E, F], C). generate_attach_a_constraint(A, [B, C]) :- generate_attach_a_constraint_empty_list(A, B), get_max_constraint_index(D), ( D==1 -> generate_attach_a_constraint_1_1(A, C) ; generate_attach_a_constraint_t_p(A, C) ). generate_attach_a_constraint_empty_list(A/B, C) :- atom_concat_list([attach_, A, /, B], D), E=[[], _], F=..[D|E], C=(F:-true). generate_attach_a_constraint_1_1(A/B, C) :- atom_concat_list([attach_, A, /, B], D), E=[[F|G], H], I=..[D|E], J=..[D, G, H], get_target_module(K), L=((get_attr(F, K, M)->N=[H|M], put_attr(F, K, N);put_attr(F, K, [H])), J), C=(I:-L). generate_attach_a_constraint_t_p(A/B, C) :- atom_concat_list([attach_, A, /, B], D), E=[[F|G], H], I=..[D|E], J=..[D, G, H], get_constraint_index(A/B, K), or_pattern(K, L), get_max_constraint_index(M), make_attr(M, N, O, P), nth1(K, O, Q), substitute_eq(Q, O, [H|Q], R), make_attr(M, N, R, S), substitute_eq(Q, O, [H], T), make_attr(M, U, T, V), copy_term_nat(O, W), nth1(K, W, [H]), chr_delete(W, [H], X), set_elems(X, []), make_attr(M, L, W, Y), get_target_module(Z), A1=((get_attr(F, Z, B1)->B1=P, (N/\L=:=L->put_attr(F, Z, S);U is N\/L, put_attr(F, Z, V));put_attr(F, Z, Y)), J), C=(I:-A1). generate_detach_a_constraint(A, [B, C]) :- generate_detach_a_constraint_empty_list(A, B), get_max_constraint_index(D), ( D==1 -> generate_detach_a_constraint_1_1(A, C) ; generate_detach_a_constraint_t_p(A, C) ). generate_detach_a_constraint_empty_list(A/B, C) :- atom_concat_list([detach_, A, /, B], D), E=[[], _], F=..[D|E], C=(F:-true). generate_detach_a_constraint_1_1(A/B, C) :- atom_concat_list([detach_, A, /, B], D), E=[[F|G], H], I=..[D|E], J=..[D, G, H], get_target_module(K), L=((get_attr(F, K, M)->'chr sbag_del_element'(M, H, N), (N==[]->del_attr(F, K);put_attr(F, K, N));true), J), C=(I:-L). generate_detach_a_constraint_t_p(A/B, C) :- atom_concat_list([detach_, A, /, B], D), E=[[F|G], H], I=..[D|E], J=..[D, G, H], get_constraint_index(A/B, K), or_pattern(K, L), and_pattern(K, M), get_max_constraint_index(N), make_attr(N, O, P, Q), nth1(K, P, R), substitute_eq(R, P, [], S), make_attr(N, T, S, U), substitute_eq(R, P, V, W), make_attr(N, O, W, X), get_target_module(Y), Z=((get_attr(F, Y, A1)->A1=Q, (O/\L=:=L->'chr sbag_del_element'(R, H, V), (V==[]->T is O/\M, (T==0->del_attr(F, Y);put_attr(F, Y, U));put_attr(F, Y, X));true);true), J), C=(I:-Z). generate_attach_increment([A, B]) :- generate_attach_increment_empty(A), get_max_constraint_index(C), ( C==1 -> generate_attach_increment_one(B) ; generate_attach_increment_many(C, B) ). generate_attach_increment_empty((attach_increment([], _):-true)). generate_attach_increment_one(A) :- B=attach_increment([C|D], E), get_target_module(F), G=('chr not_locked'(C), (get_attr(C, F, H)->sort(H, I), merge(E, I, J), put_attr(C, F, J);put_attr(C, F, E)), attach_increment(D, E)), A=(B:-G). generate_attach_increment_many(A, B) :- make_attr(A, C, D, E), make_attr(A, F, G, H), I=attach_increment([J|K], E), bagof(L, M^N^O^P^(member2(D, G, M-N), L=(sort(N, O), 'chr merge_attributes'(M, O, P))), Q), list2conj(Q, R), bagof(S, T^U^V^member((T, 'chr merge_attributes'(U, V, S)), Q), W), make_attr(A, X, W, Y), get_target_module(Z), A1=('chr not_locked'(J), (get_attr(J, Z, B1)->B1=H, R, X is C\/F, put_attr(J, Z, Y);put_attr(J, Z, E)), attach_increment(K, E)), B=(I:-A1). generate_attr_unify_hook([A]) :- get_max_constraint_index(B), ( B==1 -> generate_attr_unify_hook_one(A) ; generate_attr_unify_hook_many(B, A) ). generate_attr_unify_hook_one(A) :- B=C:attr_unify_hook(D, E), get_target_module(C), make_run_suspensions(F, G), make_run_suspensions(D, H), I=(sort(D, J), (var(E)->(get_attr(E, C, K)->true;K=[]), sort(K, L), 'chr merge_attributes'(J, L, F), put_attr(E, C, F), G;(compound(E)->term_variables(E, M), attach_increment(M, J);true), H)), A=(B:-I). generate_attr_unify_hook_many(A, B) :- make_attr(A, C, D, E), make_attr(A, F, G, H), bagof(I, J^K^(member(J, D), I=sort(J, K)), L), list2conj(L, M), bagof(K, J^member(sort(J, K), L), N), bagof(O, P^Q^R^S^(member2(N, G, P-Q), O=(sort(Q, R), 'chr merge_attributes'(P, R, S))), T), bagof(S, P^R^U^member((U, 'chr merge_attributes'(P, R, S)), T), V), list2conj(T, W), make_attr(A, X, V, Y), make_attr(A, C, N, Z), A1=B1:attr_unify_hook(E, C1), get_target_module(B1), make_run_suspensions_loop(V, D1), make_run_suspensions_loop(N, E1), F1=(M, (var(C1)->(get_attr(C1, B1, G1)->G1=H, W, X is C\/F, put_attr(C1, B1, Y), D1;put_attr(C1, B1, Z), E1);(compound(C1)->term_variables(C1, H1), attach_increment(H1, Z);true), E1)), B=(A1:-F1). make_run_suspensions(A, B) :- ( chr_pp_flag(debugable, on) -> B='chr run_suspensions_d'(A) ; B='chr run_suspensions'(A) ). make_run_suspensions_loop(A, B) :- ( chr_pp_flag(debugable, on) -> B='chr run_suspensions_loop_d'(A) ; B='chr run_suspensions_loop'(A) ). check_attachments(A) :- ( chr_pp_flag(check_attachments, on) -> check_attachments_(A) ; true ). check_attachments_([]). check_attachments_([A|B]) :- check_attachment(A), check_attachments_(B). check_attachment(A) :- A=pragma(B, _, _, _), B=rule(C, D, E, F), check_attachment_heads1(C, C, D, E), check_attachment_heads2(D, C, F). check_attachment_heads1([], _, _, _). check_attachment_heads1([A|B], C, D, E) :- functor(A, F, G), ( C==[A], D==[], E==true, A=..[_|H], no_matching(H, []) -> attached(F/G, no) ; attached(F/G, maybe) ), check_attachment_heads1(B, C, D, E). no_matching([], _). no_matching([A|B], C) :- var(A), \+ memberchk_eq(A, C), no_matching(B, [A|C]). check_attachment_heads2([], _, _). check_attachment_heads2([A|B], C, D) :- functor(A, E, F), ( C\==[], D==true -> attached(E/F, maybe) ; attached(E/F, yes) ), check_attachment_heads2(B, C, D). all_attached([]). all_attached([A|B]) :- functor(A, C, D), is_attached(C/D), all_attached(B). set_constraint_indices([], A) :- B is A-1, max_constraint_index(B). set_constraint_indices([A|B], C) :- ( is_attached(A) -> constraint_index(A, C), D is C+1, set_constraint_indices(B, D) ; set_constraint_indices(B, C) ). constraints_code(A, B, C) :- post_constraints(A, 1), constraints_code1(1, B, D, []), clean_clauses(D, C). post_constraints([], A) :- B is A-1, constraint_count(B). post_constraints([A/B|C], D) :- constraint(A/B, D), E is D+1, post_constraints(C, E). constraints_code1(A, B, C, D) :- constraint_count(E), ( A>E -> D=C ; constraint_code(A, B, C, F), G is A+1, constraints_code1(G, B, F, D) ). constraint_code(A, B, C, D) :- constraint(E, A), constraint_prelude(E, F), C=[F|G], H=[0], rules_code(B, 1, A, H, I, G, J), gen_cond_attach_clause(E, I, J, D). constraint_prelude(A/B, C) :- vars_susp(B, D, E, F), G=..[A|D], build_head(A, B, [0], F, H), get_target_module(I), ( chr_pp_flag(debugable, on) -> C=(G:-'chr allocate_constraint'(I:H, E, A, D), ('chr debug_event'(call(E)), H;'chr debug_event'(fail(E)), !, fail), ('chr debug_event'(exit(E));'chr debug_event'(redo(E)), fail)) ; C=(G:-H) ). gen_cond_attach_clause(A/B, C, D, E) :- ( is_attached(A/B) -> ( C==[0] -> gen_cond_attach_goal(A/B, F, G, H, I) ; vars_susp(B, H, I, G), gen_uncond_attach_goal(A/B, I, F, _) ), ( chr_pp_flag(debugable, on) -> J=..[A|H], K='chr debug_event'(insert(#(J, I))) ; K=true ), build_head(A, B, C, G, L), M=(L:-K, F), D=[M|E] ; D=E ). gen_cond_attach_goal(A/B, C, D, E, F) :- vars_susp(B, E, F, D), build_head(A, B, [0], D, G), atom_concat_list([attach_, A, /, B], H), I=..[H, J, F], get_target_module(K), C=((var(F)->'chr insert_constraint_internal'(J, F, K:G, A, E);'chr activate_constraint'(J, F, _)), I). gen_uncond_attach_goal(A/B, C, D, E) :- atom_concat_list([attach_, A, /, B], F), G=..[F, H, C], D=('chr activate_constraint'(H, C, E), G). rules_code([], _, _, A, A, B, B). rules_code([A|B], C, D, E, F, G, H) :- rule_code(A, C, D, E, I, G, J), K is C+1, rules_code(B, K, D, I, F, J, H). rule_code(A, B, C, D, E, F, G) :- A=pragma(H, I, _, _), I=ids(J, K), H=rule(L, M, _, _), heads1_code(L, [], J, [], A, C, D, F, N), heads2_code(M, [], K, [], A, B, C, D, E, N, G). heads1_code([], _, _, _, _, _, _, A, A). heads1_code([A|B], C, [D|E], F, G, H, I, J, K) :- G=pragma(L, _, M, _), constraint(N/O, H), ( functor(A, N, O), \+ check_unnecessary_active(A, C, L), \+ memberchk_eq(passive(D), M), all_attached(B), all_attached(C), L=rule(_, P, _, _), all_attached(P) -> append(B, C, Q), append(E, F, R), head1_code(A, Q, R, G, N/O, H, I, J, S) ; J=S ), heads1_code(B, [A|C], E, [D|F], G, H, I, S, K). head1_code(A, B, C, D, E, _, F, G, H) :- D=pragma(I, _, _, _), I=rule(_, J, _, _), ( J==[] -> reorder_heads(A, B, C, K, L), simplification_code(A, K, L, D, E, F, G, H) ; simpagation_head1_code(A, B, C, D, E, F, G, H) ). heads2_code([], _, _, _, _, _, _, A, A, B, B). heads2_code([A|B], C, [D|E], F, G, H, I, J, K, L, M) :- G=pragma(N, _, O, _), constraint(P/Q, I), ( functor(A, P, Q), \+ check_unnecessary_active(A, C, N), \+ memberchk_eq(passive(D), O), \+ set_semantics_rule(G), all_attached(B), all_attached(C), N=rule(R, _, _, _), all_attached(R) -> append(B, C, S), append(E, F, T), length(B, U), head2_code(A, S, T, G, H, U, P/Q, J, L, V), inc_id(J, W), gen_alloc_inc_clause(P/Q, J, V, X) ; L=X, W=J ), heads2_code(B, [A|C], E, [D|F], G, H, I, W, K, X, M). head2_code(A, B, C, D, E, F, G, H, I, J) :- D=pragma(K, _, _, _), K=rule(L, _, _, _), ( L==[] -> reorder_heads(A, B, M), propagation_code(A, M, K, E, F, G, H, I, J) ; simpagation_head2_code(A, B, C, D, G, H, I, J) ). gen_alloc_inc_clause(A/B, C, D, E) :- vars_susp(B, F, G, H), build_head(A, B, C, H, I), inc_id(C, J), build_head(A, B, J, H, K), ( C==[0] -> gen_cond_allocation(F, G, A/B, H, L) ; L=true ), M=(I:-L, K), D=[M|E]. gen_cond_allocation(A, B, C/D, E, F) :- build_head(C, D, [0], E, G), get_target_module(H), F=(var(B)->'chr allocate_constraint'(H:G, B, C, A);true). guard_via_reschedule(A, B, C, D) :- ( chr_pp_flag(guard_via_reschedule, on) -> guard_via_reschedule_main(A, B, C, D) ; append(A, B, E), list2conj(E, D) ). guard_via_reschedule_main(A, B, C, D) :- initialize_unit_dictionary(C, E), build_units(A, B, E, F), dependency_reorder(F, G), units2goal(G, D). units2goal([], true). units2goal([unit(_, A, _, _)|B], (A, C)) :- units2goal(B, C). dependency_reorder(A, B) :- dependency_reorder(A, [], B). dependency_reorder([], A, B) :- reverse(A, B). dependency_reorder([A|B], C, D) :- A=unit(_, _, E, F), ( E==fixed -> G=[A|C] ; dependency_insert(C, A, F, G) ), dependency_reorder(B, G, D). dependency_insert([], A, _, [A]). dependency_insert([A|B], C, D, E) :- A=unit(F, _, _, _), ( memberchk(F, D) -> E=[C, A|B] ; E=[A|G], dependency_insert(B, C, D, G) ). build_units(A, B, C, D) :- build_retrieval_units(A, 1, E, C, F, D, G), build_guard_units(B, E, F, G). build_retrieval_units([], A, A, B, B, C, C). build_retrieval_units([A|B], C, D, E, F, G, H) :- term_variables(A, I), update_unit_dictionary(I, C, E, J, [], K), G=[unit(C, A, movable, K)|L], M is C+1, build_retrieval_units2(B, M, D, J, F, L, H). build_retrieval_units2([], A, A, B, B, C, C). build_retrieval_units2([A|B], C, D, E, F, G, H) :- term_variables(A, I), update_unit_dictionary(I, C, E, J, [], K), G=[unit(C, A, fixed, K)|L], M is C+1, build_retrieval_units(B, M, D, J, F, L, H). initialize_unit_dictionary(A, B) :- term_variables(A, C), pair_all_with(C, 0, B). update_unit_dictionary([], _, A, A, B, B). update_unit_dictionary([A|B], C, D, E, F, G) :- ( lookup_eq(D, A, H) -> ( ( H==C ; memberchk(H, F) ) -> I=F ; I=[H|F] ), J=D ; J=[A-C|D], I=F ), update_unit_dictionary(B, C, J, E, I, G). build_guard_units(A, B, C, D) :- ( A=[E] -> D=[unit(B, E, fixed, [])] ; A=[E|F] -> term_variables(E, G), update_unit_dictionary2(G, B, C, H, [], I), D=[unit(B, E, movable, I)|J], K is B+1, build_guard_units(F, K, H, J) ). update_unit_dictionary2([], _, A, A, B, B). update_unit_dictionary2([A|B], C, D, E, F, G) :- ( lookup_eq(D, A, H) -> ( ( H==C ; memberchk(H, F) ) -> I=F ; I=[H|F] ), J=[A-C|D] ; J=[A-C|D], I=F ), update_unit_dictionary2(B, C, J, E, I, G). unique_analyse_optimise(A, B) :- ( chr_pp_flag(unique_analyse_optimise, on) -> unique_analyse_optimise_main(A, 1, [], B) ; B=A ). unique_analyse_optimise_main([], _, _, []). unique_analyse_optimise_main([A|B], C, D, [E|F]) :- ( discover_unique_pattern(A, C, G) -> H=[G|D] ; H=D ), A=pragma(I, J, K, L), I=rule(M, N, _, _), J=ids(O, P), apply_unique_patterns_to_constraints(M, O, H, Q), apply_unique_patterns_to_constraints(N, P, H, R), append([Q, R, K], S), E=pragma(I, J, S, L), T is C+1, unique_analyse_optimise_main(B, T, H, F). apply_unique_patterns_to_constraints([], _, _, []). apply_unique_patterns_to_constraints([A|B], [C|D], E, F) :- ( member(G, E), apply_unique_pattern(A, C, G, H) -> F=[H|I] ; F=I ), apply_unique_patterns_to_constraints(B, D, E, I). apply_unique_pattern(A, B, C, D) :- C=unique(E, F), subsumes(A, E, G), ( setof(H, I^J^K^(member(I, F), lookup_eq(G, I, J), term_variables(J, K), member(H, K)), L) -> true ; L=[] ), D=unique(B, L). subsumes(A, B, C) :- empty_ds(D), subsumes_aux(A, B, D, E), ds_to_list(E, F), build_unifier(F, C). subsumes_aux(A, B, C, D) :- ( compound(B), functor(B, E, F) -> compound(A), functor(A, E, F), subsumes_aux(F, A, B, C, D) ; A==B -> D=C ; var(B), get_ds(A, C, G) -> G==B, D=C ; var(B), put_ds(A, C, B, D) ). subsumes_aux(0, _, _, A, A) :- !. subsumes_aux(A, B, C, D, E) :- arg(A, B, F), arg(A, C, G), subsumes_aux(F, G, D, H), I is A-1, subsumes_aux(I, B, C, H, E). build_unifier([], []). build_unifier([A-B|C], [B-A|D]) :- build_unifier(C, D). discover_unique_pattern(A, B, C) :- A=pragma(D, _, E, F), ( D=rule([G], [H], I, J) -> true ; D=rule([G, H], [], I, J) ), check_unique_constraints(G, H, I, J, E, K), term_variables(G, L), select_pragma_unique_variables(K, L, M), N=unique(G, M), copy_term_nat(N, C), ( verbosity_on -> format('Found unique pattern ~w in rule ~d~@\n', [ C, B, (F=yes(O)->write([58, 32]), write(O);true) ]) ; true ). select_pragma_unique_variables([], _, []). select_pragma_unique_variables([A-B|C], D, E) :- ( A==B -> E=[A|F] ; once(( \+ memberchk_eq(A, D) ; \+ memberchk_eq(B, D) )), E=F ), select_pragma_unique_variables(C, D, F). check_unique_constraints(A, B, C, _, D, E) :- \+ member(passive(_), D), variable_replacement(A-B, B-A, E), copy_with_variable_replacement(C, F, E), negate(C, G), once(entails(G, F)). negate(true, fail). negate(fail, true). negate(A=B, B>=A). negate(A>=B, B>A). negate(AB, C>=D) :- C==A, D==B. entails(A check_unnecessary_active_main(A, B, C) ; chr_pp_flag(check_unnecessary_active, simplification), C=rule(_, [], _, _) -> check_unnecessary_active_main(A, B, C) ; fail ). check_unnecessary_active_main(A, B, C) :- member(D, B), variable_replacement(D, A, E), copy_with_variable_replacement(C, F, E), identical_rules(C, F), !. set_semantics_rule(A) :- ( chr_pp_flag(set_semantics_rule, on) -> set_semantics_rule_main(A) ; fail ). set_semantics_rule_main(A) :- A=pragma(B, C, D, _), B=rule([_], [_], true, _), C=ids([E], [F]), once(member(unique(E, G), D)), once(member(unique(F, H), D)), G==H, \+ memberchk_eq(passive(E), D). identical_rules(rule(A, B, C, D), rule(E, F, G, H)) :- C==G, identical_bodies(D, H), permutation(A, I), I==E, permutation(B, J), J==F. identical_bodies(A, B) :- ( A=(C=D), B=(E=F) -> ( C==E, D==F ; C==F, E==D ), ! ; A==B ). copy_with_variable_replacement(A, B, C) :- ( var(A) -> ( lookup_eq(C, A, B) -> true ; A=B ) ; functor(A, D, E), functor(B, D, E), A=..[_|F], B=..[_|G], copy_with_variable_replacement_l(F, G, C) ). copy_with_variable_replacement_l([], [], _). copy_with_variable_replacement_l([A|B], [C|D], E) :- copy_with_variable_replacement(A, C, E), copy_with_variable_replacement_l(B, D, E). variable_replacement(A, B, C) :- variable_replacement(A, B, [], C). variable_replacement(A, B, C, D) :- ( var(A) -> var(B), ( lookup_eq(C, A, E) -> E==B, D=C ; D=[A-B|C] ) ; A=..[F|G], nonvar(B), B=..[F|H], variable_replacement_l(G, H, C, D) ). variable_replacement_l([], [], A, A). variable_replacement_l([A|B], [C|D], E, F) :- variable_replacement(A, C, E, G), variable_replacement_l(B, D, G, F). simplification_code(A, B, C, D, E/F, G, H, I) :- D=pragma(J, _, K, _), head_info(A, F, _, L, M, N), build_head(E, F, G, M, O), head_arg_matches(N, [], P, Q), ( B==[] -> R=[], S=Q, T=[] ; rest_heads_retrieval_and_matching(B, C, K, A, T, R, Q, S) ), guard_body_copies2(J, S, U, V), guard_via_reschedule(T, U, O-P, W), gen_uncond_susps_detachments(R, B, X), gen_cond_susp_detachment(L, E/F, Y), ( chr_pp_flag(debugable, on) -> J=rule(_, _, Z, A1), my_term_copy(Z-A1, S, _, B1-C1), D1='chr debug_event'(try([L|E1], [], B1, C1)), F1='chr debug_event'(apply([L|E1], [], B1, C1)) ; D1=true, F1=true ), G1=(O:-P, W, D1, !, F1, X, Y, V), H=[G1|I]. head_arg_matches(A, B, C, D) :- head_arg_matches_(A, B, E, D), list2conj(E, C). head_arg_matches_([], A, [], A). head_arg_matches_([A-B|C], D, E, F) :- ( var(A) -> ( lookup_eq(D, A, G) -> E=[B==G|H], I=D ; I=[A-B|D], E=H ), J=C ; atomic(A) -> E=[B==A|H], D=I, J=C ; A=..[_|K], functor(A, L, M), functor(N, L, M), N=..[_|O], E=[nonvar(B), B=N|H], pairup(K, O, P), append(P, C, J), I=D ), head_arg_matches_(J, I, H, F). rest_heads_retrieval_and_matching(A, B, C, D, E, F, G, H) :- rest_heads_retrieval_and_matching(A, B, C, D, E, F, G, H, [], [], []). rest_heads_retrieval_and_matching(A, B, C, D, E, F, G, H, I, J, K) :- ( A=[_|_] -> rest_heads_retrieval_and_matching_n(A, B, C, I, J, D, E, F, G, H, K) ; E=[], F=[], G=H ). rest_heads_retrieval_and_matching_n([], _, _, _, _, _, [], [], A, A, B) :- instantiate_pattern_goals(B). rest_heads_retrieval_and_matching_n([A|B], [C|D], E, F, G, H, [I, J|K], [L|M], N, O, P) :- passive_head_via(A, [H|F], P, N, I, Q, R), functor(A, S, T), head_info(A, T, U, _, _, V), head_arg_matches(V, N, W, X), Y=..[suspension, _, Z, _, _, _, _|U], get_max_constraint_index(A1), ( A1==1 -> B1=Q ; get_constraint_index(S/T, C1), make_attr(A1, _, D1, Q), nth1(C1, D1, B1) ), different_from_other_susps(A, L, F, G, E1), create_get_mutable_ref(active, Z, F1), G1=(member(L, B1), L=Y, F1, E1, W), ( member(unique(C, H1), E), check_unique_keys(H1, N) -> J=(G1->true) ; J=G1 ), rest_heads_retrieval_and_matching_n(B, D, E, [A|F], [L|G], H, K, M, X, O, R). instantiate_pattern_goals([]). instantiate_pattern_goals([_-attr(A, B, C)|D]) :- get_max_constraint_index(E), ( E==1 -> C=true ; make_attr(E, F, _, A), or_list(B, G), !, C=(F/\G=:=G) ), instantiate_pattern_goals(D). check_unique_keys([], _). check_unique_keys([A|B], C) :- lookup_eq(C, A, _), check_unique_keys(B, C). different_from_other_susps(A, B, C, D, E) :- ( bagof(F, G^(nth1(G, C, H), \+A\=H, nth1(G, D, I), F=(B\==I)), J) -> list2conj(J, E) ; E=true ). passive_head_via(A, B, C, D, E, F, G) :- functor(A, H, I), get_constraint_index(H/I, J), common_variables(A, B, K), translate(K, D, L), or_pattern(J, M), ( permutation(L, N), lookup_eq(C, N, attr(F, O, _)) -> member(M, O), !, G=C, E=true ; E=(P, Q), gen_get_mod_constraints(L, P, F), G=[L-attr(F, [M|_], Q)|C] ). common_variables(A, B, C) :- term_variables(A, D), term_variables(B, E), intersect_eq(D, E, C). gen_get_mod_constraints(A, B, C) :- get_target_module(D), ( A==[] -> B=('chr default_store'(E), get_attr(E, D, F), F=C) ; ( A=[G] -> H='chr via_1'(G, I) ; A=[G, J] -> H='chr via_2'(G, J, I) ; H='chr via'(A, I) ), B=(H, get_attr(I, D, F), F=C) ). guard_body_copies(A, B, C, D) :- guard_body_copies2(A, B, E, D), list2conj(E, C). guard_body_copies2(A, B, C, D) :- A=rule(_, _, E, F), conj2list(E, G), split_off_simple_guard(G, B, H, I), my_term_copy(H-I, B, J, K-L), append(K, [M], C), term_variables(I, N), term_variables(L, O), ( chr_pp_flag(guard_locks, on), bagof('chr lock'(P)-'chr unlock'(P), Q^(member(Q, N), lookup_eq(B, Q, P), memberchk_eq(P, O)), R) -> once(pairup(S, T, R)) ; S=[], T=[] ), list2conj(S, U), list2conj(T, V), list2conj(L, W), M=(U, W, V), my_term_copy(F, J, D). split_off_simple_guard([], _, [], []). split_off_simple_guard([A|B], C, D, E) :- ( simple_guard(A, C) -> D=[A|F], split_off_simple_guard(B, C, F, E) ; D=[], E=[A|B] ). simple_guard(var(_), _). simple_guard(nonvar(_), _). simple_guard(ground(_), _). simple_guard(number(_), _). simple_guard(atom(_), _). simple_guard(integer(_), _). simple_guard(float(_), _). simple_guard(_>_, _). simple_guard(_<_, _). simple_guard(_=<_, _). simple_guard(_>=_, _). simple_guard(_=:=_, _). simple_guard(_==_, _). simple_guard(A is _, B) :- \+ lookup_eq(B, A, _). simple_guard((A, B), C) :- simple_guard(A, C), simple_guard(B, C). simple_guard(\+A, B) :- simple_guard(A, B). my_term_copy(A, B, C) :- my_term_copy(A, B, _, C). my_term_copy(A, B, C, D) :- ( var(A) -> ( lookup_eq(B, A, D) -> C=B ; C=[A-D|B] ) ; functor(A, E, F), functor(D, E, F), A=..[_|G], D=..[_|H], my_term_copy_list(G, B, C, H) ). my_term_copy_list([], A, A, []). my_term_copy_list([A|B], C, D, [E|F]) :- my_term_copy(A, C, G, E), my_term_copy_list(B, G, D, F). gen_cond_susp_detachment(A, B, C) :- ( is_attached(B) -> gen_uncond_susp_detachment(A, B, D), C=(var(A)->true;D) ; C=true ). gen_uncond_susp_detachment(A, B/C, D) :- ( is_attached(B/C) -> atom_concat_list([detach_, B, /, C], E), F=..[E, G, A], ( chr_pp_flag(debugable, on) -> H='chr debug_event'(remove(A)) ; H=true ), D=(H, 'chr remove_constraint_internal'(A, G), F) ; D=true ). gen_uncond_susps_detachments([], [], true). gen_uncond_susps_detachments([A|B], [C|D], (E, F)) :- functor(C, G, H), gen_uncond_susp_detachment(A, G/H, E), gen_uncond_susps_detachments(B, D, F). simpagation_head1_code(A, B, C, D, E/F, G, H, I) :- D=pragma(J, ids(_, K), L, _), J=rule(_, M, N, O), head_info(A, F, _, P, Q, R), head_arg_matches(R, [], S, T), build_head(E, F, G, Q, U), append(B, M, V), append(C, K, W), reorder_heads(A, V, W, X, Y), rest_heads_retrieval_and_matching(X, Y, L, A, Z, A1, T, B1), split_by_ids(Y, A1, C, C1, D1), guard_body_copies2(J, B1, E1, F1), guard_via_reschedule(Z, E1, U-S, G1), gen_uncond_susps_detachments(C1, B, H1), gen_cond_susp_detachment(P, E/F, I1), ( chr_pp_flag(debugable, on) -> my_term_copy(N-O, B1, _, J1-K1), L1='chr debug_event'(try([P|C1], D1, J1, K1)), M1='chr debug_event'(apply([P|C1], D1, J1, K1)) ; L1=true, M1=true ), N1=(U:-S, G1, L1, !, M1, H1, I1, F1), H=[N1|I]. split_by_ids([], [], _, [], []). split_by_ids([A|B], [C|D], E, F, G) :- ( memberchk_eq(A, E) -> F=[C|H], G=I ; F=H, G=[C|I] ), split_by_ids(B, D, E, H, I). simpagation_head2_code(A, B, C, D, E, F, G, H) :- D=pragma(I, ids(J, _), K, _), I=rule(L, _, M, N), reorder_heads(A, L, J, [O|P], [Q|R]), simpagation_head2_prelude(A, O, [B, L, M, N], E, F, G, S), extend_id(F, T), simpagation_head2_worker(A, O, Q, P, R, B, C, I, K, E, T, S, H). simpagation_head2_prelude(A, B, C, D/E, F, G, H) :- head_info(A, E, I, J, K, L), build_head(D, E, F, K, M), head_arg_matches(L, [], N, O), passive_head_via(B, [A], [], O, P, Q, R), instantiate_pattern_goals(R), get_max_constraint_index(S), ( S==1 -> T=Q ; functor(B, U, V), get_constraint_index(U/V, W), make_attr(S, _, X, Q), nth1(W, X, T) ), ( F==[0] -> gen_cond_allocation(I, J, D/E, K, Y) ; Y=true ), extend_id(F, Z), extra_active_delegate_variables(A, C, O, A1), append([T|K], A1, B1), build_head(D, E, Z, B1, C1), D1=(M:-N, P, !, Y, C1), G=[D1|H]. extra_active_delegate_variables(A, B, C, D) :- A=..[_|E], delegate_variables(A, B, C, E, D). passive_delegate_variables(A, B, C, D, E) :- term_variables(B, F), delegate_variables(A, C, D, F, E). delegate_variables(A, B, C, D, E) :- term_variables(A, F), term_variables(B, G), intersect_eq(F, G, H), list_difference_eq(H, D, I), translate(I, C, E). simpagation_head2_worker(A, B, C, D, E, F, G, H, I, J, K, L, M) :- H=rule(_, _, N, O), simpagation_head2_worker_end(A, [B, D, F, N, O], J, K, L, P), simpagation_head2_worker_body(A, B, C, D, E, F, G, H, I, J, K, P, M). simpagation_head2_worker_body(A, B, C, D, E, F, G, H, I, J/K, L, M, N) :- gen_var(O), gen_var(P), head_info(A, K, _, Q, R, S), head_arg_matches(S, [], _, T), H=rule(_, _, U, V), extra_active_delegate_variables(A, [ B, D, F, U, V ], T, W), append([[O|P]|R], W, X), build_head(J, K, L, X, Y), functor(B, _, Z), head_info(B, Z, A1, _, _, B1), head_arg_matches(B1, T, C1, D1), E1=..[suspension, _, F1, _, _, _, _|A1], create_get_mutable_ref(active, F1, G1), H1=(O=E1, G1), ( ( D\==[] ; F\==[] ) -> append(D, F, I1), append(E, G, J1), reorder_heads(B-A, I1, J1, K1, L1), rest_heads_retrieval_and_matching(K1, L1, I, [B, A], M1, N1, D1, O1, [B], [O], []), split_by_ids(L1, N1, E, P1, Q1) ; M1=[], P1=[], Q1=[], O1=D1 ), gen_uncond_susps_detachments([O|P1], [B|D], R1), append([P|R], W, S1), build_head(J, K, L, S1, T1), append([[]|R], W, U1), build_head(J, K, L, U1, V1), guard_body_copies2(H, O1, W1, X1), guard_via_reschedule(M1, W1, v(Y, H1, C1), Y1), ( X1\==true -> gen_uncond_attach_goal(J/K, Q, Z1, A2), gen_state_cond_call(Q, K, T1, A2, B2), gen_state_cond_call(Q, K, V1, A2, C2) ; Z1=true, B2=T1, C2=V1 ), ( chr_pp_flag(debugable, on) -> my_term_copy(U-V, O1, _, D2-E2), F2='chr debug_event'(try([O|P1], [Q|Q1], D2, E2)), G2='chr debug_event'(apply([O|P1], [Q|Q1], D2, E2)) ; F2=true, G2=true ), ( member(unique(C, H2), I), check_unique_keys(H2, T) -> I2=(Y:-H1, C1->(Y1, F2->G2, R1, Z1, X1, C2;V1);T1) ; I2=(Y:-H1, C1, Y1, F2->G2, R1, Z1, X1, B2;T1) ), M=[I2|N]. gen_state_cond_call(A, B, C, D, E) :- length(F, B), G=..[suspension, _, H, _, I, _, _|F], create_get_mutable_ref(active, H, J), create_get_mutable_ref(D, I, K), E=(A=G, J, K->'chr update_mutable'(inactive, H), C;true). simpagation_head2_worker_end(A, B, C/D, E, F, G) :- head_info(A, D, _, _, H, I), head_arg_matches(I, [], _, J), extra_active_delegate_variables(A, B, J, K), append([[]|H], K, L), build_head(C, D, E, L, M), next_id(E, N), build_head(C, D, N, H, O), P=(M:-O), F=[P|G]. propagation_code(A, B, C, D, E, F, G, H, I) :- ( B==[] -> propagation_single_headed(A, C, D, F, G, H, I) ; propagation_multi_headed(A, B, C, D, E, F, G, H, I) ). propagation_single_headed(A, B, C, D/E, F, G, H) :- head_info(A, E, I, J, K, L), build_head(D, E, F, K, M), inc_id(F, N), build_head(D, E, N, K, O), P=O, head_arg_matches(L, [], Q, R), guard_body_copies(B, R, S, T), ( F==[0] -> gen_cond_allocation(I, J, D/E, K, U), V=U ; V=true ), gen_uncond_attach_goal(D/E, J, W, X), gen_state_cond_call(J, E, P, X, Y), ( chr_pp_flag(debugable, on) -> B=rule(_, _, Z, A1), my_term_copy(Z-A1, R, _, B1-C1), D1='chr debug_event'(try([], [J], B1, C1)), E1='chr debug_event'(apply([], [J], B1, C1)) ; D1=true, E1=true ), F1=(M:-Q, V, 'chr novel_production'(J, C), S, D1, !, E1, 'chr extend_history'(J, C), W, T, Y), G=[F1|H]. propagation_multi_headed(A, B, C, D, E, F, G, H, I) :- B=[J|K], propagation_prelude(A, B, C, F, G, H, L), extend_id(G, M), propagation_nested_code(K, [J, A], C, D, E, F, M, L, I). propagation_prelude(A, [B|C], D, E/F, G, H, I) :- head_info(A, F, J, K, L, M), build_head(E, F, G, L, N), head_arg_matches(M, [], O, P), D=rule(_, _, Q, R), extra_active_delegate_variables(A, [B, C, Q, R], P, S), passive_head_via(B, [A], [], P, T, U, V), instantiate_pattern_goals(V), get_max_constraint_index(W), ( W==1 -> X=U ; functor(B, Y, Z), make_attr(W, _, A1, U), get_constraint_index(Y/Z, B1), nth1(B1, A1, X) ), ( G==[0] -> gen_cond_allocation(J, K, E/F, L, C1) ; C1=true ), extend_id(G, D1), append([X|L], S, E1), build_head(E, F, D1, E1, F1), G1=F1, H1=(N:-O, T, !, C1, G1), H=[H1|I]. propagation_nested_code([], [A|B], C, D, E, F, G, H, I) :- propagation_end([A|B], [], C, F, G, H, J), propagation_body(A, B, C, D, E, F, G, J, I). propagation_nested_code([A|B], C, D, E, F, G, H, I, J) :- propagation_end(C, [A|B], D, G, H, I, K), propagation_accumulator([A|B], C, D, G, H, K, L), inc_id(H, M), propagation_nested_code(B, [A|C], D, E, F, G, M, L, J). propagation_body(A, B, C, D, E, F/G, H, I, J) :- C=rule(_, _, K, L), get_prop_inner_loop_vars(B, [A, K, L], M, N, O, P), gen_var(Q), gen_var(R), functor(A, _, S), gen_vars(S, T), U=..[suspension, _, V, _, _, _, _|T], create_get_mutable_ref(active, V, W), X=(Q=U, W), Y=[[Q|R]|M], build_head(F, G, H, Y, Z), A1=[R|M], build_head(F, G, H, A1, B1), C1=B1, A=..[_|D1], pairup(D1, T, E1), head_arg_matches(E1, N, F1, G1), different_from_other_susps(A, Q, B, P, H1), guard_body_copies(C, G1, I1, J1), gen_uncond_attach_goal(F/G, O, K1, L1), gen_state_cond_call(O, G, C1, L1, M1), history_susps(E, [Q|P], O, [], N1), bagof('chr novel_production'(O1, P1), (member(O1, N1), P1=Q1), R1), list2conj(R1, S1), T1=..[t, D|N1], ( chr_pp_flag(debugable, on) -> C=rule(_, _, K, L), my_term_copy(K-L, G1, _, U1-V1), W1='chr debug_event'(try([], [O, Q|P], U1, V1)), X1='chr debug_event'(apply([], [O, Q|P], U1, V1)) ; W1=true, X1=true ), Y1=(Z:-X, H1, F1, Q1=T1, S1, I1, W1->X1, 'chr extend_history'(O, Q1), K1, J1, M1;C1), I=[Y1|J]. history_susps(A, B, C, D, E) :- ( A==0 -> reverse(B, F), append(F, [C|D], E) ; B=[G|H], I is A-1, history_susps(I, H, C, [G|D], E) ). get_prop_inner_loop_vars([A], B, C, D, E, []) :- !, functor(A, _, F), head_info(A, F, _, E, G, H), head_arg_matches(H, [], _, D), extra_active_delegate_variables(A, B, D, I), append(G, I, C). get_prop_inner_loop_vars([A|B], C, D, E, F, [G|H]) :- get_prop_inner_loop_vars(B, [A|C], I, J, F, H), functor(A, _, K), gen_var(L), head_info(A, K, _, G, _, M), head_arg_matches(M, J, _, E), passive_delegate_variables(A, B, C, E, N), append(N, [G, L|I], D). propagation_end([A|B], C, D, E/F, G, H, I) :- D=rule(_, _, J, K), gen_var_susp_list_for(B, [A, C, J, K], _, L, M, N), O=[[]|L], build_head(E, F, G, O, P), ( G=[0|_] -> next_id(G, Q), R=M ; dec_id(G, Q), R=[N|M] ), build_head(E, F, Q, R, S), T=S, U=(P:-T), H=[U|I]. gen_var_susp_list_for([A], B, C, D, E, F) :- !, functor(A, _, G), head_info(A, G, _, F, E, H), head_arg_matches(H, [], _, C), extra_active_delegate_variables(A, B, C, I), append(E, I, D). gen_var_susp_list_for([A|B], C, D, E, F, G) :- gen_var_susp_list_for(B, [A|C], H, F, _, _), functor(A, _, I), gen_var(G), head_info(A, I, _, J, _, K), head_arg_matches(K, H, _, D), passive_delegate_variables(A, B, C, D, L), append(L, [J, G|F], E). propagation_accumulator([A|B], [C|D], E, F/G, H, I, J) :- E=rule(_, _, K, L), pre_vars_and_susps(D, [C, A, B, K, L], M, N, O), gen_var(P), functor(C, _, Q), gen_vars(Q, R), head_info(C, Q, R, S, _, T), head_arg_matches(T, N, U, V), W=..[suspension, _, X, _, _, _, _|R], different_from_other_susps(C, S, D, O, Y), create_get_mutable_ref(active, X, Z), A1=(S=W, Z, Y, U), functor(A, B1, C1), passive_head_via(A, [C|D], [], V, D1, E1, F1), instantiate_pattern_goals(F1), get_max_constraint_index(G1), ( G1==1 -> H1=E1 ; get_constraint_index(B1/C1, I1), make_attr(G1, _, J1, E1), nth1(I1, J1, H1) ), inc_id(H, K1), L1=[[S|P]|M], build_head(F, G, H, L1, M1), passive_delegate_variables(C, D, [A, B, K, L], V, N1), append([H1|N1], [S, P|M], O1), build_head(F, G, K1, O1, P1), Q1=[P|M], build_head(F, G, H, Q1, R1), S1=(M1:-A1, D1->P1;R1), I=[S1|J]. pre_vars_and_susps([A], B, C, D, []) :- !, functor(A, _, E), head_info(A, E, _, _, F, G), head_arg_matches(G, [], _, D), extra_active_delegate_variables(A, B, D, H), append(F, H, C). pre_vars_and_susps([A|B], C, D, E, [F|G]) :- pre_vars_and_susps(B, [A|C], H, I, G), functor(A, _, J), gen_var(K), head_info(A, J, _, F, _, L), head_arg_matches(L, I, _, E), passive_delegate_variables(A, B, C, E, M), append(M, [F, K|H], D). reorder_heads(A, B, C, D, E) :- ( chr_pp_flag(reorder_heads, on) -> reorder_heads_main(A, B, C, D, E) ; D=B, E=C ). reorder_heads_main(A, B, C, D, E) :- term_variables(A, F), reorder_heads1(B, C, F, D, E). reorder_heads1(A, B, C, D, E) :- ( A==[] -> D=[], E=[] ; D=[F|G], E=[H|I], select_best_head(A, B, C, F, H, J, K, L), reorder_heads1(J, K, L, G, I) ). select_best_head(A, B, C, D, E, F, G, H) :- ( bagof(tuple(I, J, K, L, M), (select2(J, K, A, B, L, M), order_score(J, C, L, I)), N) -> true ; N=[] ), max_go_list(N, tuple(_, D, E, F, G)), term_variables(D, O), ( setof(P, (member(P, O), \+memberchk_eq(P, C)), Q) -> true ; Q=[] ), append(Q, C, H). reorder_heads(A, B, C) :- term_variables(A, D), reorder_heads1(B, D, C). reorder_heads1(A, B, C) :- ( A==[] -> C=[] ; C=[D|E], select_best_head(A, B, D, F, G), reorder_heads1(F, G, E) ). select_best_head(A, B, C, D, E) :- ( bagof(tuple(F, G, H), (select(G, A, H), order_score(G, B, H, F)), I) -> true ; I=[] ), max_go_list(I, tuple(_, C, D)), term_variables(C, J), ( setof(K, (member(K, J), \+memberchk_eq(K, B)), L) -> true ; L=[] ), append(L, B, E). order_score(A, B, C, D) :- term_variables(A, E), term_variables(C, F), order_score_vars(E, B, F, 0, D). order_score_vars([], _, _, A, B) :- ( A==0 -> B=99999 ; B=A ). order_score_vars([A|B], C, D, E, F) :- ( memberchk_eq(A, C) -> G is E+1 ; memberchk_eq(A, D) -> G is E+1 ; G=E ), order_score_vars(B, C, D, G, F). create_get_mutable_ref(A, B, C) :- C=(B=mutable(A)). clean_clauses([], []). clean_clauses([A|B], [C|D]) :- clean_clause(A, C), clean_clauses(B, D). clean_clause(A, B) :- ( A=(C:-D) -> clean_goal(D, E), ( E==true -> B=C ; B=(C:-E) ) ; B=A ). clean_goal(A, B) :- var(A), !, B=A. clean_goal((A, B), C) :- !, clean_goal(A, D), clean_goal(B, E), ( D==true -> C=E ; E==true -> C=D ; C=(D, E) ). clean_goal((A->B;C), D) :- !, clean_goal(A, E), ( E==true -> clean_goal(B, F), D=F ; E==fail -> clean_goal(C, G), D=G ; clean_goal(B, F), clean_goal(C, G), D=(E->F;G) ). clean_goal((A;B), C) :- !, clean_goal(A, D), clean_goal(B, E), ( D==fail -> C=E ; E==fail -> C=D ; C=(D;E) ). clean_goal(once(A), B) :- !, clean_goal(A, C), ( C==true -> B=true ; C==fail -> B=fail ; B=once(C) ). clean_goal((A->B), C) :- !, clean_goal(A, D), ( D==true -> clean_goal(B, C) ; D==fail -> C=fail ; clean_goal(B, E), C=(D->E) ). clean_goal(A, A). gen_var(_). gen_vars(A, B) :- length(B, A). head_info(A, B, C, D, E, F) :- vars_susp(B, C, D, E), A=..[_|G], pairup(G, C, F). inc_id([A|B], [C|B]) :- C is A+1. dec_id([A|B], [C|B]) :- C is A-1. extend_id(A, [0|A]). next_id([_, A|B], [C|B]) :- C is A+1. build_head(A, B, C, D, E) :- buildName(A, B, C, F), E=..[F|D]. buildName(A, B, C, D) :- atom_concat(A, /, E), atomic_concat(E, B, F), buildName_(C, F, D). buildName_([], A, A). buildName_([A|B], C, D) :- buildName_(B, C, E), atom_concat(E, '__', F), atomic_concat(F, A, D). vars_susp(A, B, C, D) :- length(B, A), append(B, [C], D). make_attr(A, B, C, D) :- length(C, A), D=..[v, B|C]. or_pattern(A, B) :- C is A-1, B is 1< list2conj(B, C) ; C=(A, D), list2conj(B, D) ). atom_concat_list([A], A) :- !. atom_concat_list([A|B], C) :- atom_concat_list(B, D), atomic_concat(A, D, C). make_atom(A, B) :- ( atom(A) -> B=A ; number(A) -> number_codes(A, C), atom_codes(B, C) ). set_elems([], _). set_elems([A|B], A) :- set_elems(B, A). member2([A|_], [B|_], A-B). member2([_|A], [_|B], C) :- member2(A, B, C). select2(A, B, [A|C], [B|D], C, D). select2(A, B, [C|D], [E|F], [C|G], [E|H]) :- select2(A, B, D, F, G, H). pair_all_with([], _, []). pair_all_with([A|B], C, [A-C|D]) :- pair_all_with(B, C, D). verbosity_on :- current_prolog_flag(verbose, A), A==yes. 'attach_constraint/2'([], _). 'attach_constraint/2'([A|B], C) :- ( get_attr(A, chr_translate_bootstrap1, D) -> D=v(E, F, G, H, I, J, K), ( E/\1=:=1 -> put_attr(A, chr_translate_bootstrap1, v(E, [C|F], G, H, I, J, K)) ; L is E\/1, put_attr(A, chr_translate_bootstrap1, v(L, [C], G, H, I, J, K)) ) ; put_attr(A, chr_translate_bootstrap1, v(1, [C], [], [], [], [], [])) ), 'attach_constraint/2'(B, C). 'detach_constraint/2'([], _). 'detach_constraint/2'([A|B], C) :- ( get_attr(A, chr_translate_bootstrap1, D) -> D=v(E, F, G, H, I, J, K), ( E/\1=:=1 -> 'chr sbag_del_element'(F, C, L), ( L==[] -> M is E/\ -2, ( M==0 -> del_attr(A, chr_translate_bootstrap1) ; put_attr(A, chr_translate_bootstrap1, v(M, [], G, H, I, J, K)) ) ; put_attr(A, chr_translate_bootstrap1, v(E, L, G, H, I, J, K)) ) ; true ) ; true ), 'detach_constraint/2'(B, C). 'attach_constraint_count/1'([], _). 'attach_constraint_count/1'([A|B], C) :- ( get_attr(A, chr_translate_bootstrap1, D) -> D=v(E, F, G, H, I, J, K), ( E/\2=:=2 -> put_attr(A, chr_translate_bootstrap1, v(E, F, [C|G], H, I, J, K)) ; L is E\/2, put_attr(A, chr_translate_bootstrap1, v(L, F, [C], H, I, J, K)) ) ; put_attr(A, chr_translate_bootstrap1, v(2, [], [C], [], [], [], [])) ), 'attach_constraint_count/1'(B, C). 'detach_constraint_count/1'([], _). 'detach_constraint_count/1'([A|B], C) :- ( get_attr(A, chr_translate_bootstrap1, D) -> D=v(E, F, G, H, I, J, K), ( E/\2=:=2 -> 'chr sbag_del_element'(G, C, L), ( L==[] -> M is E/\ -3, ( M==0 -> del_attr(A, chr_translate_bootstrap1) ; put_attr(A, chr_translate_bootstrap1, v(M, F, [], H, I, J, K)) ) ; put_attr(A, chr_translate_bootstrap1, v(E, F, L, H, I, J, K)) ) ; true ) ; true ), 'detach_constraint_count/1'(B, C). 'attach_constraint_index/2'([], _). 'attach_constraint_index/2'([A|B], C) :- ( get_attr(A, chr_translate_bootstrap1, D) -> D=v(E, F, G, H, I, J, K), ( E/\4=:=4 -> put_attr(A, chr_translate_bootstrap1, v(E, F, G, [C|H], I, J, K)) ; L is E\/4, put_attr(A, chr_translate_bootstrap1, v(L, F, G, [C], I, J, K)) ) ; put_attr(A, chr_translate_bootstrap1, v(4, [], [], [C], [], [], [])) ), 'attach_constraint_index/2'(B, C). 'detach_constraint_index/2'([], _). 'detach_constraint_index/2'([A|B], C) :- ( get_attr(A, chr_translate_bootstrap1, D) -> D=v(E, F, G, H, I, J, K), ( E/\4=:=4 -> 'chr sbag_del_element'(H, C, L), ( L==[] -> M is E/\ -5, ( M==0 -> del_attr(A, chr_translate_bootstrap1) ; put_attr(A, chr_translate_bootstrap1, v(M, F, G, [], I, J, K)) ) ; put_attr(A, chr_translate_bootstrap1, v(E, F, G, L, I, J, K)) ) ; true ) ; true ), 'detach_constraint_index/2'(B, C). 'attach_max_constraint_index/1'([], _). 'attach_max_constraint_index/1'([A|B], C) :- ( get_attr(A, chr_translate_bootstrap1, D) -> D=v(E, F, G, H, I, J, K), ( E/\8=:=8 -> put_attr(A, chr_translate_bootstrap1, v(E, F, G, H, [C|I], J, K)) ; L is E\/8, put_attr(A, chr_translate_bootstrap1, v(L, F, G, H, [C], J, K)) ) ; put_attr(A, chr_translate_bootstrap1, v(8, [], [], [], [C], [], [])) ), 'attach_max_constraint_index/1'(B, C). 'detach_max_constraint_index/1'([], _). 'detach_max_constraint_index/1'([A|B], C) :- ( get_attr(A, chr_translate_bootstrap1, D) -> D=v(E, F, G, H, I, J, K), ( E/\8=:=8 -> 'chr sbag_del_element'(I, C, L), ( L==[] -> M is E/\ -9, ( M==0 -> del_attr(A, chr_translate_bootstrap1) ; put_attr(A, chr_translate_bootstrap1, v(M, F, G, H, [], J, K)) ) ; put_attr(A, chr_translate_bootstrap1, v(E, F, G, H, L, J, K)) ) ; true ) ; true ), 'detach_max_constraint_index/1'(B, C). 'attach_target_module/1'([], _). 'attach_target_module/1'([A|B], C) :- ( get_attr(A, chr_translate_bootstrap1, D) -> D=v(E, F, G, H, I, J, K), ( E/\16=:=16 -> put_attr(A, chr_translate_bootstrap1, v(E, F, G, H, I, [C|J], K)) ; L is E\/16, put_attr(A, chr_translate_bootstrap1, v(L, F, G, H, I, [C], K)) ) ; put_attr(A, chr_translate_bootstrap1, v(16, [], [], [], [], [C], [])) ), 'attach_target_module/1'(B, C). 'detach_target_module/1'([], _). 'detach_target_module/1'([A|B], C) :- ( get_attr(A, chr_translate_bootstrap1, D) -> D=v(E, F, G, H, I, J, K), ( E/\16=:=16 -> 'chr sbag_del_element'(J, C, L), ( L==[] -> M is E/\ -17, ( M==0 -> del_attr(A, chr_translate_bootstrap1) ; put_attr(A, chr_translate_bootstrap1, v(M, F, G, H, I, [], K)) ) ; put_attr(A, chr_translate_bootstrap1, v(E, F, G, H, I, L, K)) ) ; true ) ; true ), 'detach_target_module/1'(B, C). 'attach_attached/2'([], _). 'attach_attached/2'([A|B], C) :- ( get_attr(A, chr_translate_bootstrap1, D) -> D=v(E, F, G, H, I, J, K), ( E/\32=:=32 -> put_attr(A, chr_translate_bootstrap1, v(E, F, G, H, I, J, [C|K])) ; L is E\/32, put_attr(A, chr_translate_bootstrap1, v(L, F, G, H, I, J, [C])) ) ; put_attr(A, chr_translate_bootstrap1, v(32, [], [], [], [], [], [C])) ), 'attach_attached/2'(B, C). 'detach_attached/2'([], _). 'detach_attached/2'([A|B], C) :- ( get_attr(A, chr_translate_bootstrap1, D) -> D=v(E, F, G, H, I, J, K), ( E/\32=:=32 -> 'chr sbag_del_element'(K, C, L), ( L==[] -> M is E/\ -33, ( M==0 -> del_attr(A, chr_translate_bootstrap1) ; put_attr(A, chr_translate_bootstrap1, v(M, F, G, H, I, J, [])) ) ; put_attr(A, chr_translate_bootstrap1, v(E, F, G, H, I, J, L)) ) ; true ) ; true ), 'detach_attached/2'(B, C). attach_increment([], _). attach_increment([A|B], v(C, D, E, F, G, H, I)) :- 'chr not_locked'(A), ( get_attr(A, chr_translate_bootstrap1, J) -> J=v(K, L, M, N, O, P, Q), sort(L, R), 'chr merge_attributes'(D, R, S), sort(M, T), 'chr merge_attributes'(E, T, U), sort(N, V), 'chr merge_attributes'(F, V, W), sort(O, X), 'chr merge_attributes'(G, X, Y), sort(P, Z), 'chr merge_attributes'(H, Z, A1), sort(Q, B1), 'chr merge_attributes'(I, B1, C1), D1 is C\/K, put_attr(A, chr_translate_bootstrap1, v(D1, S, U, W, Y, A1, C1)) ; put_attr(A, chr_translate_bootstrap1, v(C, D, E, F, G, H, I)) ), attach_increment(B, v(C, D, E, F, G, H, I)). chr_translate_bootstrap1:attr_unify_hook(v(A, B, C, D, E, F, G), H) :- sort(B, I), sort(C, J), sort(D, K), sort(E, L), sort(F, M), sort(G, N), ( var(H) -> ( get_attr(H, chr_translate_bootstrap1, O) -> O=v(P, Q, R, S, T, U, V), sort(Q, W), 'chr merge_attributes'(I, W, X), sort(R, Y), 'chr merge_attributes'(J, Y, Z), sort(S, A1), 'chr merge_attributes'(K, A1, B1), sort(T, C1), 'chr merge_attributes'(L, C1, D1), sort(U, E1), 'chr merge_attributes'(M, E1, F1), sort(V, G1), 'chr merge_attributes'(N, G1, H1), I1 is A\/P, put_attr(H, chr_translate_bootstrap1, v(I1, X, Z, B1, D1, F1, H1)), 'chr run_suspensions_loop'([ X, Z, B1, D1, F1, H1 ]) ; put_attr(H, chr_translate_bootstrap1, v(A, I, J, K, L, M, N)), 'chr run_suspensions_loop'([ I, J, K, L, M, N ]) ) ; ( compound(H) -> term_variables(H, J1), attach_increment(J1, v(A, I, J, K, L, M, N)) ; true ), 'chr run_suspensions_loop'([ I, J, K, L, M, N ]) ). constraint(A, B) :- 'constraint/2__0'(A, B, _). 'constraint/2__0'(A, B, C) :- 'chr via_1'(A, D), get_attr(D, chr_translate_bootstrap1, E), E=v(F, G, _, _, _, _, _), F/\1=:=1, ( member(H, G), H=suspension(_, I, _, _, _, _, J, K), I=mutable(active), J==A -> true ), !, ( var(C) -> true ; 'chr remove_constraint_internal'(C, L), 'detach_constraint/2'(L, C) ), B=K. 'constraint/2__0'(A, B, C) :- 'chr via_1'(B, D), get_attr(D, chr_translate_bootstrap1, E), E=v(F, G, _, _, _, _, _), F/\1=:=1, member(H, G), H=suspension(_, I, _, _, _, _, J, K), I=mutable(active), K==B, !, ( var(C) -> true ; 'chr remove_constraint_internal'(C, L), 'detach_constraint/2'(L, C) ), A=J. 'constraint/2__0'(A, B, C) :- ( var(C) -> 'chr insert_constraint_internal'(D, C, chr_translate_bootstrap1:'constraint/2__0'(A, B, C), constraint, [A, B]) ; 'chr activate_constraint'(D, C, _) ), 'attach_constraint/2'(D, C). constraint_count(A) :- 'constraint_count/1__0'(A, _). 'constraint_count/1__0'(A, B) :- 'chr default_store'(C), get_attr(C, chr_translate_bootstrap1, D), D=v(E, _, F, _, _, _, _), E/\2=:=2, member(G, F), G=suspension(_, H, _, _, _, _, I), H=mutable(active), !, ( var(B) -> true ; 'chr remove_constraint_internal'(B, J), 'detach_constraint_count/1'(J, B) ), A=I. 'constraint_count/1__0'(A, B) :- ( var(B) -> 'chr insert_constraint_internal'(C, B, chr_translate_bootstrap1:'constraint_count/1__0'(A, B), constraint_count, [A]) ; 'chr activate_constraint'(C, B, _) ), 'attach_constraint_count/1'(C, B). constraint_index(A, B) :- 'constraint_index/2__0'(A, B, _). 'constraint_index/2__0'(A, B, C) :- ( var(C) -> 'chr insert_constraint_internal'(D, C, chr_translate_bootstrap1:'constraint_index/2__0'(A, B, C), constraint_index, [A, B]) ; 'chr activate_constraint'(D, C, _) ), 'attach_constraint_index/2'(D, C). get_constraint_index(A, B) :- 'get_constraint_index/2__0'(A, B, _). 'get_constraint_index/2__0'(A, B, _) :- 'chr via_1'(A, C), get_attr(C, chr_translate_bootstrap1, D), D=v(E, _, _, F, _, _, _), E/\4=:=4, member(G, F), G=suspension(_, H, _, _, _, _, I, J), H=mutable(active), I==A, !, B=J. 'get_constraint_index/2__0'(_, _, _) :- !, fail. max_constraint_index(A) :- 'max_constraint_index/1__0'(A, _). 'max_constraint_index/1__0'(A, B) :- ( var(B) -> 'chr insert_constraint_internal'(C, B, chr_translate_bootstrap1:'max_constraint_index/1__0'(A, B), max_constraint_index, [A]) ; 'chr activate_constraint'(C, B, _) ), 'attach_max_constraint_index/1'(C, B). get_max_constraint_index(A) :- 'get_max_constraint_index/1__0'(A, _). 'get_max_constraint_index/1__0'(A, _) :- 'chr default_store'(B), get_attr(B, chr_translate_bootstrap1, C), C=v(D, _, _, _, E, _, _), D/\8=:=8, member(F, E), F=suspension(_, G, _, _, _, _, H), G=mutable(active), !, A=H. 'get_max_constraint_index/1__0'(_, _) :- !, fail. target_module(A) :- 'target_module/1__0'(A, _). 'target_module/1__0'(A, B) :- ( var(B) -> 'chr insert_constraint_internal'(C, B, chr_translate_bootstrap1:'target_module/1__0'(A, B), target_module, [A]) ; 'chr activate_constraint'(C, B, _) ), 'attach_target_module/1'(C, B). get_target_module(A) :- 'get_target_module/1__0'(A, _). 'get_target_module/1__0'(A, _) :- 'chr default_store'(B), get_attr(B, chr_translate_bootstrap1, C), C=v(D, _, _, _, _, E, _), D/\16=:=16, member(F, E), F=suspension(_, G, _, _, _, _, H), G=mutable(active), !, A=H. 'get_target_module/1__0'(A, _) :- !, A=user. attached(A, B) :- 'attached/2__0'(A, B, _). 'attached/2__0'(A, _, B) :- 'chr via_1'(A, C), get_attr(C, chr_translate_bootstrap1, D), D=v(E, _, _, _, _, _, F), E/\32=:=32, member(G, F), G=suspension(_, H, _, _, _, _, I, J), H=mutable(active), I==A, J==yes, !, ( var(B) -> true ; 'chr remove_constraint_internal'(B, K), 'detach_attached/2'(K, B) ). 'attached/2__0'(A, B, C) :- B==yes, 'chr via_1'(A, D), get_attr(D, chr_translate_bootstrap1, E), E=v(F, _, _, _, _, _, G), F/\32=:=32, !, ( var(C) -> 'chr allocate_constraint'(chr_translate_bootstrap1:'attached/2__0'(A, B, C), C, attached, [A, B]) ; true ), 'attached/2__0__0'(G, A, B, C). 'attached/2__0__0'([], A, B, C) :- 'attached/2__1'(A, B, C). 'attached/2__0__0'([A|B], C, D, E) :- ( A=suspension(_, F, _, _, _, _, G, _), F=mutable(active), G==C -> 'chr remove_constraint_internal'(A, H), 'detach_attached/2'(H, A), 'attached/2__0__0'(B, C, D, E) ; 'attached/2__0__0'(B, C, D, E) ). 'attached/2__0'(A, B, C) :- ( var(C) -> 'chr allocate_constraint'(chr_translate_bootstrap1:'attached/2__0'(A, B, C), C, attached, [A, B]) ; true ), 'attached/2__1'(A, B, C). 'attached/2__1'(A, _, B) :- 'chr via_1'(A, C), get_attr(C, chr_translate_bootstrap1, D), D=v(E, _, _, _, _, _, F), E/\32=:=32, member(G, F), G=suspension(_, H, _, _, _, _, I, J), H=mutable(active), I==A, J==no, !, ( var(B) -> true ; 'chr remove_constraint_internal'(B, K), 'detach_attached/2'(K, B) ). 'attached/2__1'(A, B, C) :- B==no, 'chr via_1'(A, D), get_attr(D, chr_translate_bootstrap1, E), E=v(F, _, _, _, _, _, G), F/\32=:=32, !, 'attached/2__1__0'(G, A, B, C). 'attached/2__1__0'([], A, B, C) :- 'attached/2__2'(A, B, C). 'attached/2__1__0'([A|B], C, D, E) :- ( A=suspension(_, F, _, _, _, _, G, _), F=mutable(active), G==C -> 'chr remove_constraint_internal'(A, H), 'detach_attached/2'(H, A), 'attached/2__1__0'(B, C, D, E) ; 'attached/2__1__0'(B, C, D, E) ). 'attached/2__1'(A, B, C) :- 'attached/2__2'(A, B, C). 'attached/2__2'(A, B, C) :- B==maybe, 'chr via_1'(A, D), get_attr(D, chr_translate_bootstrap1, E), E=v(F, _, _, _, _, _, G), F/\32=:=32, ( member(H, G), H=suspension(_, I, _, _, _, _, J, K), I=mutable(active), J==A, K==maybe -> true ), !, ( var(C) -> true ; 'chr remove_constraint_internal'(C, L), 'detach_attached/2'(L, C) ). 'attached/2__2'(_, _, A) :- 'chr activate_constraint'(B, A, _), 'attach_attached/2'(B, A). is_attached(A) :- 'is_attached/1__0'(A, _). 'is_attached/1__0'(A, _) :- 'chr via_1'(A, B), get_attr(B, chr_translate_bootstrap1, C), C=v(D, _, _, _, _, _, E), D/\32=:=32, member(F, E), F=suspension(_, G, _, _, _, _, H, I), G=mutable(active), H==A, !, ( I==no -> fail ; true ). 'is_attached/1__0'(_, _) :- !. chr_clear :- 'chr_clear/0__0'(_). 'chr_clear/0__0'(A) :- 'chr default_store'(B), get_attr(B, chr_translate_bootstrap1, C), C=v(D, E, _, _, _, _, _), D/\1=:=1, !, ( var(A) -> 'chr allocate_constraint'(chr_translate_bootstrap1:'chr_clear/0__0'(A), A, chr_clear, []) ; true ), 'chr_clear/0__0__0'(E, A). 'chr_clear/0__0__0'([], A) :- 'chr_clear/0__1'(A). 'chr_clear/0__0__0'([A|B], C) :- ( A=suspension(_, D, _, _, _, _, _, _), D=mutable(active) -> 'chr remove_constraint_internal'(A, E), 'detach_constraint/2'(E, A), 'chr_clear/0__0__0'(B, C) ; 'chr_clear/0__0__0'(B, C) ). 'chr_clear/0__0'(A) :- ( var(A) -> 'chr allocate_constraint'(chr_translate_bootstrap1:'chr_clear/0__0'(A), A, chr_clear, []) ; true ), 'chr_clear/0__1'(A). 'chr_clear/0__1'(A) :- 'chr default_store'(B), get_attr(B, chr_translate_bootstrap1, C), C=v(D, _, E, _, _, _, _), D/\2=:=2, !, 'chr_clear/0__1__0'(E, A). 'chr_clear/0__1__0'([], A) :- 'chr_clear/0__2'(A). 'chr_clear/0__1__0'([A|B], C) :- ( A=suspension(_, D, _, _, _, _, _), D=mutable(active) -> 'chr remove_constraint_internal'(A, E), 'detach_constraint_count/1'(E, A), 'chr_clear/0__1__0'(B, C) ; 'chr_clear/0__1__0'(B, C) ). 'chr_clear/0__1'(A) :- 'chr_clear/0__2'(A). 'chr_clear/0__2'(A) :- 'chr default_store'(B), get_attr(B, chr_translate_bootstrap1, C), C=v(D, _, _, E, _, _, _), D/\4=:=4, !, 'chr_clear/0__2__0'(E, A). 'chr_clear/0__2__0'([], A) :- 'chr_clear/0__3'(A). 'chr_clear/0__2__0'([A|B], C) :- ( A=suspension(_, D, _, _, _, _, _, _), D=mutable(active) -> 'chr remove_constraint_internal'(A, E), 'detach_constraint_index/2'(E, A), 'chr_clear/0__2__0'(B, C) ; 'chr_clear/0__2__0'(B, C) ). 'chr_clear/0__2'(A) :- 'chr_clear/0__3'(A). 'chr_clear/0__3'(A) :- 'chr default_store'(B), get_attr(B, chr_translate_bootstrap1, C), C=v(D, _, _, _, E, _, _), D/\8=:=8, !, 'chr_clear/0__3__0'(E, A). 'chr_clear/0__3__0'([], A) :- 'chr_clear/0__4'(A). 'chr_clear/0__3__0'([A|B], C) :- ( A=suspension(_, D, _, _, _, _, _), D=mutable(active) -> 'chr remove_constraint_internal'(A, E), 'detach_max_constraint_index/1'(E, A), 'chr_clear/0__3__0'(B, C) ; 'chr_clear/0__3__0'(B, C) ). 'chr_clear/0__3'(A) :- 'chr_clear/0__4'(A). 'chr_clear/0__4'(A) :- 'chr default_store'(B), get_attr(B, chr_translate_bootstrap1, C), C=v(D, _, _, _, _, E, _), D/\16=:=16, !, 'chr_clear/0__4__0'(E, A). 'chr_clear/0__4__0'([], A) :- 'chr_clear/0__5'(A). 'chr_clear/0__4__0'([A|B], C) :- ( A=suspension(_, D, _, _, _, _, _), D=mutable(active) -> 'chr remove_constraint_internal'(A, E), 'detach_target_module/1'(E, A), 'chr_clear/0__4__0'(B, C) ; 'chr_clear/0__4__0'(B, C) ). 'chr_clear/0__4'(A) :- 'chr_clear/0__5'(A). 'chr_clear/0__5'(A) :- 'chr default_store'(B), get_attr(B, chr_translate_bootstrap1, C), C=v(D, _, _, _, _, _, E), D/\32=:=32, !, 'chr_clear/0__5__0'(E, A). 'chr_clear/0__5__0'([], A) :- 'chr_clear/0__6'(A). 'chr_clear/0__5__0'([A|B], C) :- ( A=suspension(_, D, _, _, _, _, _, _), D=mutable(active) -> 'chr remove_constraint_internal'(A, E), 'detach_attached/2'(E, A), 'chr_clear/0__5__0'(B, C) ; 'chr_clear/0__5__0'(B, C) ). 'chr_clear/0__5'(A) :- 'chr_clear/0__6'(A). 'chr_clear/0__6'(_) :- !.