2all_not_holds(A, B, C) :-
    3	D=suspension(E, active, _, 0, flux:all_not_holds___3__0(A, B, C, D), all_not_holds, A, B, C),
    4	term_variables(term(A, B, C), G),
    5	'chr gen_id'(E),
    6	nb_getval('$chr_store_global_list_flux____all_not_holds___3', F),
    7	b_setval('$chr_store_global_list_flux____all_not_holds___3',
    8		 [D|F]),
    9	attach_all_not_holds___3(G, D),
   10	setarg(2, D, inactive),
   11	'chr debug_event'(insert(all_not_holds(A, B, C)#D)),
   12	(   'chr debugging'
   13	->  (   'chr debug_event'(call(D)),
   14		all_not_holds___3__0(A, B, C, D)
   15	    ;   'chr debug_event'(fail(D)), !,
   16		fail
   17	    ),
   18	    (   'chr debug_event'(exit(D))
   19	    ;   'chr debug_event'(redo(D)),
   20		fail
   21	    )
   22	;   all_not_holds___3__0(A, B, C, D)
   23	).
   24
   25not_holds___2__3(E, A, F) :-
   26	(   'chr newvia_1'(A, B)
   27	->  get_attr(B, flux, C),
   28	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
   29	;   nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
   30		      D)
   31	), !,
   32	not_holds___2__3__0__7(D, E, A, F).
   33not_holds___2__3(A, B, C) :-
   34	not_holds___2__4(A, B, C).
   35
   36attribute_goals(_, A, A).
   37
   38all_holds(A, B) :-
   39	C=suspension(D, active, _, 0, flux:all_holds___2__0(A, B, C), all_holds, A, B),
   40	'chr gen_id'(D),
   41	nb_getval('$chr_store_global_list_flux____all_holds___2', E),
   42	b_setval('$chr_store_global_list_flux____all_holds___2',
   43		 [C|E]),
   44	attach_all_holds___2([], C),
   45	setarg(2, C, inactive),
   46	'chr debug_event'(insert(all_holds(A, B)#C)),
   47	(   'chr debugging'
   48	->  (   'chr debug_event'(call(C)),
   49		all_holds___2__0(A, B, C)
   50	    ;   'chr debug_event'(fail(C)), !,
   51		fail
   52	    ),
   53	    (   'chr debug_event'(exit(C))
   54	    ;   'chr debug_event'(redo(C)),
   55		fail
   56	    )
   57	;   all_holds___2__0(A, B, C)
   58	).
   59
   60all_not_holds___3__3(E, F, A, G) :-
   61	(   'chr newvia_1'(A, B)
   62	->  get_attr(B, flux, C),
   63	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
   64	;   nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
   65		      D)
   66	), !,
   67	all_not_holds___3__3__0__6(D, E, F, A, G).
   68all_not_holds___3__3(A, B, C, D) :-
   69	all_not_holds___3__4(A, B, C, D).
   70
   71attach_increment([], _).
   72attach_increment([A|G2], B) :-
   73	(   get_attr(A, flux, C)
   74	->  B=v(Q1, E, H, K, N, Q, T, W, Z, C1, F1, I1, L1, O1),
   75	    C=v(R1, D, G, J, M, P, S, V, Y, B1, E1, H1, K1, N1),
   76	    sort(D, F),
   77	    'chr merge_attributes'(E, F, T1),
   78	    sort(G, I),
   79	    'chr merge_attributes'(H, I, U1),
   80	    sort(J, L),
   81	    'chr merge_attributes'(K, L, V1),
   82	    sort(M, O),
   83	    'chr merge_attributes'(N, O, W1),
   84	    sort(P, R),
   85	    'chr merge_attributes'(Q, R, X1),
   86	    sort(S, U),
   87	    'chr merge_attributes'(T, U, Y1),
   88	    sort(V, X),
   89	    'chr merge_attributes'(W, X, Z1),
   90	    sort(Y, A1),
   91	    'chr merge_attributes'(Z, A1, A2),
   92	    sort(B1, D1),
   93	    'chr merge_attributes'(C1, D1, B2),
   94	    sort(E1, G1),
   95	    'chr merge_attributes'(F1, G1, C2),
   96	    sort(H1, J1),
   97	    'chr merge_attributes'(I1, J1, D2),
   98	    sort(K1, M1),
   99	    'chr merge_attributes'(L1, M1, E2),
  100	    sort(N1, P1),
  101	    'chr merge_attributes'(O1, P1, F2),
  102	    S1 is Q1\/R1,
  103	    put_attr(A,
  104		     flux,
  105		     v(S1,
  106		       T1,
  107		       U1,
  108		       V1,
  109		       W1,
  110		       X1,
  111		       Y1,
  112		       Z1,
  113		       A2,
  114		       B2,
  115		       C2,
  116		       D2,
  117		       E2,
  118		       F2))
  119	;   put_attr(A, flux, B)
  120	),
  121	attach_increment(G2, B).
  122
  123detach_cancel___2([], _).
  124detach_cancel___2([A|T], E) :-
  125	(   get_attr(A, flux, B)
  126	->  B=v(C, H, I, J, K, L, M, N, O, P, Q, R, D, S),
  127	    (   C/\2048=:=2048
  128	    ->  'chr sbag_del_element'(D, E, F),
  129		(   F==[]
  130		->  G is C/\ -2049,
  131		    (   G==0
  132		    ->  del_attr(A, flux)
  133		    ;   put_attr(A,
  134				 flux,
  135				 v(G,
  136				   H,
  137				   I,
  138				   J,
  139				   K,
  140				   L,
  141				   M,
  142				   N,
  143				   O,
  144				   P,
  145				   Q,
  146				   R,
  147				   [],
  148				   S))
  149		    )
  150		;   put_attr(A,
  151			     flux,
  152			     v(C,
  153			       H,
  154			       I,
  155			       J,
  156			       K,
  157			       L,
  158			       M,
  159			       N,
  160			       O,
  161			       P,
  162			       Q,
  163			       R,
  164			       F,
  165			       S))
  166		)
  167	    ;   true
  168	    )
  169	;   true
  170	),
  171	detach_cancel___2(T, E).
  172
  173flux_version(3.1).
  174
  175if_then_or_holds(A, B, C) :-
  176	D=suspension(E, active, _, 0, flux:if_then_or_holds___3__0(A, B, C, D), if_then_or_holds, A, B, C),
  177	term_variables(term(A, B, C), G),
  178	'chr gen_id'(E),
  179	nb_getval('$chr_store_global_list_flux____if_then_or_holds___3', F),
  180	b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
  181		 [D|F]),
  182	attach_if_then_or_holds___3(G, D),
  183	setarg(2, D, inactive),
  184	'chr debug_event'(insert(if_then_or_holds(A, B, C)#D)),
  185	(   'chr debugging'
  186	->  (   'chr debug_event'(call(D)),
  187		if_then_or_holds___3__0(A, B, C, D)
  188	    ;   'chr debug_event'(fail(D)), !,
  189		fail
  190	    ),
  191	    (   'chr debug_event'(exit(D))
  192	    ;   'chr debug_event'(redo(D)),
  193		fail
  194	    )
  195	;   if_then_or_holds___3__0(A, B, C, D)
  196	).
  197
  198detach_or_holds___2([], _).
  199detach_or_holds___2([A|T], E) :-
  200	(   get_attr(A, flux, B)
  201	->  B=v(C, H, I, J, D, K, L, M, N, O, P, Q, R, S),
  202	    (   C/\8=:=8
  203	    ->  'chr sbag_del_element'(D, E, F),
  204		(   F==[]
  205		->  G is C/\ -9,
  206		    (   G==0
  207		    ->  del_attr(A, flux)
  208		    ;   put_attr(A,
  209				 flux,
  210				 v(G,
  211				   H,
  212				   I,
  213				   J,
  214				   [],
  215				   K,
  216				   L,
  217				   M,
  218				   N,
  219				   O,
  220				   P,
  221				   Q,
  222				   R,
  223				   S))
  224		    )
  225		;   put_attr(A,
  226			     flux,
  227			     v(C,
  228			       H,
  229			       I,
  230			       J,
  231			       F,
  232			       K,
  233			       L,
  234			       M,
  235			       N,
  236			       O,
  237			       P,
  238			       Q,
  239			       R,
  240			       S))
  241		)
  242	    ;   true
  243	    )
  244	;   true
  245	),
  246	detach_or_holds___2(T, E).
  247
  248detach_cancelled___2([], _).
  249detach_cancelled___2([A|T], E) :-
  250	(   get_attr(A, flux, B)
  251	->  B=v(C, H, I, J, K, L, M, N, O, P, Q, R, S, D),
  252	    (   C/\4096=:=4096
  253	    ->  'chr sbag_del_element'(D, E, F),
  254		(   F==[]
  255		->  G is C/\ -4097,
  256		    (   G==0
  257		    ->  del_attr(A, flux)
  258		    ;   put_attr(A,
  259				 flux,
  260				 v(G,
  261				   H,
  262				   I,
  263				   J,
  264				   K,
  265				   L,
  266				   M,
  267				   N,
  268				   O,
  269				   P,
  270				   Q,
  271				   R,
  272				   S,
  273				   []))
  274		    )
  275		;   put_attr(A,
  276			     flux,
  277			     v(C,
  278			       H,
  279			       I,
  280			       J,
  281			       K,
  282			       L,
  283			       M,
  284			       N,
  285			       O,
  286			       P,
  287			       Q,
  288			       R,
  289			       S,
  290			       F))
  291		)
  292	    ;   true
  293	    )
  294	;   true
  295	),
  296	detach_cancelled___2(T, E).
  297
  298all_not_holds___3__2(E, F, A, G) :-
  299	(   'chr newvia_1'(A, B)
  300	->  get_attr(B, flux, C),
  301	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
  302	;   nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
  303		      D)
  304	), !,
  305	all_not_holds___3__2__0__5(D, E, F, A, G).
  306all_not_holds___3__2(A, B, C, D) :-
  307	all_not_holds___3__3(A, B, C, D).
  308
  309all_not_holds___3__3__0__6([], A, B, C, D) :-
  310	all_not_holds___3__4(A, B, C, D).
  311all_not_holds___3__3__0__6([A|Y], E, F, C, J) :-
  312	(   A=suspension(_, active, _, _, _, _, W, D, B),
  313	    B==C,
  314	    member(H, D, X),
  315	    copy_fluent(E, F, G, I),
  316	    G=H,
  317	    \+ call(#\+(I)),
  318	    'chr debug_event'(try([A],
  319				  [J],
  320				  (member(L, O, N), copy_fluent(E, F, K, M), K=L, \+call(#\+(M))),
  321				  if_then_or_holds(P, N, C)))
  322	->  'chr debug_event'(apply([A],
  323				    [J],
  324				    (member(L, O, N), copy_fluent(E, F, K, M), K=L, \+call(#\+(M))),
  325				    if_then_or_holds(P,
  326						     N,
  327						     C))),
  328	    'chr debug_event'(remove(A)),
  329	    A=suspension(_, _, _, _, _, if_then_or_holds, Q, R, S),
  330	    setarg(2, A, removed),
  331	    term_variables(term(Q, R, S), V),
  332	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
  333		      T),
  334	    'chr sbag_del_element'(T, A, U),
  335	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
  336		     U),
  337	    detach_if_then_or_holds___3(V, A),
  338	    setarg(2, J, active),
  339	    if_then_or_holds(W, X, C),
  340	    (   J=suspension(_, active, _, _, _, _, _, _, _)
  341	    ->  setarg(2, J, inactive),
  342		all_not_holds___3__3__0__6(Y,
  343					   E,
  344					   F,
  345					   C,
  346					   J)
  347	    ;   true
  348	    )
  349	;   all_not_holds___3__3__0__6(Y,
  350				       E,
  351				       F,
  352				       C,
  353				       J)
  354	).
  355
  356duplicate_free(A) :-
  357	B=suspension(C, active, _, 0, flux:duplicate_free___1__0(A, B), duplicate_free, A),
  358	term_variables(A, E),
  359	'chr gen_id'(C),
  360	nb_getval('$chr_store_global_list_flux____duplicate_free___1', D),
  361	b_setval('$chr_store_global_list_flux____duplicate_free___1',
  362		 [B|D]),
  363	attach_duplicate_free___1(E, B),
  364	setarg(2, B, inactive),
  365	'chr debug_event'(insert(duplicate_free(A)#B)),
  366	(   'chr debugging'
  367	->  (   'chr debug_event'(call(B)),
  368		duplicate_free___1__0(A, B)
  369	    ;   'chr debug_event'(fail(B)), !,
  370		fail
  371	    ),
  372	    (   'chr debug_event'(exit(B))
  373	    ;   'chr debug_event'(redo(B)),
  374		fail
  375	    )
  376	;   duplicate_free___1__0(A, B)
  377	).
  378
  379cancelled___2__0(A, B, I) :-
  380	(   'chr newvia_2'(A, B, C)
  381	->  get_attr(C, flux, D),
  382	    D=v(_, _, _, _, _, _, _, _, _, _, _, _, E, _)
  383	;   nb_getval('$chr_store_global_list_flux____cancel___2', E)
  384	),
  385	member(F, E),
  386	F=suspension(_, active, _, _, _, _, G, H),
  387	G==A,
  388	H==B,
  389	'chr debug_event'(try([F, I], [], true, true)), !,
  390	'chr debug_event'(apply([F, I], [], true, true)),
  391	'chr debug_event'(remove(F)),
  392	F=suspension(_, _, _, _, _, cancel, J, K),
  393	setarg(2, F, removed),
  394	term_variables(term(J, K), N),
  395	nb_getval('$chr_store_global_list_flux____cancel___2', L),
  396	'chr sbag_del_element'(L, F, M),
  397	b_setval('$chr_store_global_list_flux____cancel___2', M),
  398	detach_cancel___2(N, F),
  399	'chr debug_event'(remove(I)),
  400	I=suspension(_, _, _, _, _, cancelled, O, P),
  401	setarg(2, I, removed),
  402	term_variables(term(O, P), S),
  403	nb_getval('$chr_store_global_list_flux____cancelled___2', Q),
  404	'chr sbag_del_element'(Q, I, R),
  405	b_setval('$chr_store_global_list_flux____cancelled___2', R),
  406	detach_cancelled___2(S, I).
  407cancelled___2__0(_, _, A) :-
  408	setarg(2, A, active).
  409
  410if_then_holds___3__0(B, C, D, A) :-
  411	'chr debug_event'(try([A],
  412			      [],
  413			      true,
  414			      if_then_or_holds(B, [C], D))), !,
  415	'chr debug_event'(apply([A],
  416				[],
  417				true,
  418				if_then_or_holds(B, [C], D))),
  419	'chr debug_event'(remove(A)),
  420	A=suspension(_, _, _, _, _, if_then_holds, _, _, _),
  421	setarg(2, A, removed),
  422	nb_getval('$chr_store_global_list_flux____if_then_holds___3', E),
  423	'chr sbag_del_element'(E, A, F),
  424	b_setval('$chr_store_global_list_flux____if_then_holds___3', F),
  425	if_then_or_holds(B, [C], D).
  426if_then_holds___3__0(_, _, _, A) :-
  427	setarg(2, A, active).
  428
  429detach_if_then_holds___3([], _).
  430detach_if_then_holds___3([A|T], E) :-
  431	(   get_attr(A, flux, B)
  432	->  B=v(C, H, I, J, K, L, M, N, O, D, P, Q, R, S),
  433	    (   C/\256=:=256
  434	    ->  'chr sbag_del_element'(D, E, F),
  435		(   F==[]
  436		->  G is C/\ -257,
  437		    (   G==0
  438		    ->  del_attr(A, flux)
  439		    ;   put_attr(A,
  440				 flux,
  441				 v(G,
  442				   H,
  443				   I,
  444				   J,
  445				   K,
  446				   L,
  447				   M,
  448				   N,
  449				   O,
  450				   [],
  451				   P,
  452				   Q,
  453				   R,
  454				   S))
  455		    )
  456		;   put_attr(A,
  457			     flux,
  458			     v(C,
  459			       H,
  460			       I,
  461			       J,
  462			       K,
  463			       L,
  464			       M,
  465			       N,
  466			       O,
  467			       F,
  468			       P,
  469			       Q,
  470			       R,
  471			       S))
  472		)
  473	    ;   true
  474	    )
  475	;   true
  476	),
  477	detach_if_then_holds___3(T, E).
  478
  479or_holds(A, B) :-
  480	C=suspension(D, active, _, 0, flux:or_holds___2__0(A, B, C), or_holds, A, B),
  481	term_variables(term(A, B), F),
  482	'chr gen_id'(D),
  483	nb_getval('$chr_store_global_list_flux____or_holds___2', E),
  484	b_setval('$chr_store_global_list_flux____or_holds___2',
  485		 [C|E]),
  486	attach_or_holds___2(F, C),
  487	setarg(2, C, inactive),
  488	'chr debug_event'(insert(or_holds(A, B)#C)),
  489	(   'chr debugging'
  490	->  (   'chr debug_event'(call(C)),
  491		or_holds___2__0(A, B, C)
  492	    ;   'chr debug_event'(fail(C)), !,
  493		fail
  494	    ),
  495	    (   'chr debug_event'(exit(C))
  496	    ;   'chr debug_event'(redo(C)),
  497		fail
  498	    )
  499	;   or_holds___2__0(A, B, C)
  500	).
  501
  502not_holds___2__1(J, A, L) :-
  503	(   'chr newvia_1'(A, B)
  504	->  get_attr(B, flux, C),
  505	    C=v(_, _, _, _, _, _, _, _, D, _, _, _, _, _)
  506	;   nb_getval('$chr_store_global_list_flux____all_not_holds___3',
  507		      D)
  508	),
  509	member(E, D),
  510	E=suspension(_, active, _, _, _, _, G, H, F),
  511	F==A,
  512	copy_fluent(G, H, I, K),
  513	I=J,
  514	\+ call(#\+(K)),
  515	'chr debug_event'(try([L],
  516			      [E],
  517			      (copy_fluent(G, H, M, N), M=J, \+call(#\+(N))),
  518			      true)), !,
  519	'chr debug_event'(apply([L],
  520				[E],
  521				(copy_fluent(G, H, M, N), M=J, \+call(#\+(N))),
  522				true)),
  523	'chr debug_event'(remove(L)),
  524	L=suspension(_, _, _, _, _, not_holds, O, P),
  525	setarg(2, L, removed),
  526	term_variables(term(O, P), S),
  527	nb_getval('$chr_store_global_list_flux____not_holds___2', Q),
  528	'chr sbag_del_element'(Q, L, R),
  529	b_setval('$chr_store_global_list_flux____not_holds___2', R),
  530	detach_not_holds___2(S, L).
  531not_holds___2__1(E, A, F) :-
  532	(   'chr newvia_1'(A, B)
  533	->  get_attr(B, flux, C),
  534	    C=v(_, _, _, _, D, _, _, _, _, _, _, _, _, _)
  535	;   nb_getval('$chr_store_global_list_flux____or_holds___2', D)
  536	), !,
  537	not_holds___2__1__0__5(D, E, A, F).
  538not_holds___2__1(A, B, C) :-
  539	not_holds___2__2(A, B, C).
  540
  541all_holds(A, B, C) :-
  542	D=suspension(E, active, t, 0, flux:all_holds___3__0(A, B, C, D), all_holds, A, B, C),
  543	term_variables(term(A, B, C), G),
  544	'chr gen_id'(E),
  545	nb_getval('$chr_store_global_list_flux____all_holds___3', F),
  546	b_setval('$chr_store_global_list_flux____all_holds___3',
  547		 [D|F]),
  548	attach_all_holds___3(G, D),
  549	setarg(2, D, inactive),
  550	'chr debug_event'(insert(all_holds(A, B, C)#D)),
  551	(   'chr debugging'
  552	->  (   'chr debug_event'(call(D)),
  553		all_holds___3__0(A, B, C, D)
  554	    ;   'chr debug_event'(fail(D)), !,
  555		fail
  556	    ),
  557	    (   'chr debug_event'(exit(D))
  558	    ;   'chr debug_event'(redo(D)),
  559		fail
  560	    )
  561	;   all_holds___3__0(A, B, C, D)
  562	).
  563
  564all_not_holds___3__2__0__5([], A, B, C, D) :-
  565	all_not_holds___3__3(A, B, C, D).
  566all_not_holds___3__2__0__5([A|S], D, E, C, I) :-
  567	(   A=suspension(_, active, _, _, _, _, G, _, B),
  568	    B==C,
  569	    copy_fluent(D, E, F, H),
  570	    F=G,
  571	    \+ call(#\+(H)),
  572	    'chr debug_event'(try([A],
  573				  [I],
  574				  (copy_fluent(D, E, J, K), J=L, \+call(#\+(K))),
  575				  true))
  576	->  'chr debug_event'(apply([A],
  577				    [I],
  578				    (copy_fluent(D, E, J, K), J=L, \+call(#\+(K))),
  579				    true)),
  580	    'chr debug_event'(remove(A)),
  581	    A=suspension(_, _, _, _, _, if_then_or_holds, M, N, O),
  582	    setarg(2, A, removed),
  583	    term_variables(term(M, N, O), R),
  584	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
  585		      P),
  586	    'chr sbag_del_element'(P, A, Q),
  587	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
  588		     Q),
  589	    detach_if_then_or_holds___3(R, A),
  590	    setarg(2, I, active),
  591	    (   I=suspension(_, active, _, _, _, _, _, _, _)
  592	    ->  setarg(2, I, inactive),
  593		all_not_holds___3__2__0__5(S,
  594					   D,
  595					   E,
  596					   C,
  597					   I)
  598	    ;   true
  599	    )
  600	;   all_not_holds___3__2__0__5(S,
  601				       D,
  602				       E,
  603				       C,
  604				       I)
  605	).
  606
  607all_not_holds___3__4(C, E, A, B) :-
  608	nonvar(A),
  609	A=[D|K],
  610	'chr debug_event'(try([B],
  611			      [],
  612			      true,
  613			      ((\+ (C=D, call(E))->true;copy_fluent(C=D, E, F=G, I), F=G, eq(D, G, H), neq_all(C, D, J), call(H#/\ #\+(I)#\/J)), all_not_holds(C, E, K)))), !,
  614	'chr debug_event'(apply([B],
  615				[],
  616				true,
  617				((\+ (C=D, call(E))->true;copy_fluent(C=D, E, F=G, I), F=G, eq(D, G, H), neq_all(C, D, J), call(H#/\ #\+(I)#\/J)), all_not_holds(C, E, K)))),
  618	'chr debug_event'(remove(B)),
  619	B=suspension(_, _, _, _, _, all_not_holds, L, M, N),
  620	setarg(2, B, removed),
  621	term_variables(term(L, M, N), Q),
  622	nb_getval('$chr_store_global_list_flux____all_not_holds___3', O),
  623	'chr sbag_del_element'(O, B, P),
  624	b_setval('$chr_store_global_list_flux____all_not_holds___3', P),
  625	detach_all_not_holds___3(Q, B),
  626	(   \+ ( C=D,
  627		 call(E)
  628	       )
  629	->  true
  630	;   copy_fluent(C=D, E, R=S, U),
  631	    R=S,
  632	    eq(D, S, T),
  633	    neq_all(C, D, V),
  634	    call(T#/\ #\+(U)#\/V)
  635	),
  636	all_not_holds(C, E, K).
  637all_not_holds___3__4(_, _, _, A) :-
  638	setarg(2, A, active).
  639
  640detach_all_holds___2([], _).
  641detach_all_holds___2([A|T], E) :-
  642	(   get_attr(A, flux, B)
  643	->  B=v(C, H, I, J, K, L, D, M, N, O, P, Q, R, S),
  644	    (   C/\32=:=32
  645	    ->  'chr sbag_del_element'(D, E, F),
  646		(   F==[]
  647		->  G is C/\ -33,
  648		    (   G==0
  649		    ->  del_attr(A, flux)
  650		    ;   put_attr(A,
  651				 flux,
  652				 v(G,
  653				   H,
  654				   I,
  655				   J,
  656				   K,
  657				   L,
  658				   [],
  659				   M,
  660				   N,
  661				   O,
  662				   P,
  663				   Q,
  664				   R,
  665				   S))
  666		    )
  667		;   put_attr(A,
  668			     flux,
  669			     v(C,
  670			       H,
  671			       I,
  672			       J,
  673			       K,
  674			       L,
  675			       F,
  676			       M,
  677			       N,
  678			       O,
  679			       P,
  680			       Q,
  681			       R,
  682			       S))
  683		)
  684	    ;   true
  685	    )
  686	;   true
  687	),
  688	detach_all_holds___2(T, E).
  689
  690attach_all_not_holds___3([], _).
  691attach_all_not_holds___3([A|T], K) :-
  692	(   get_attr(A, flux, B)
  693	->  B=v(C, D, E, F, G, H, I, J, L, M, N, O, P, Q),
  694	    (   C/\128=:=128
  695	    ->  R=v(C, D, E, F, G, H, I, J, [K|L], M, N, O, P, Q)
  696	    ;   S is C\/128,
  697		R=v(S, D, E, F, G, H, I, J, [K], M, N, O, P, Q)
  698	    ),
  699	    put_attr(A, flux, R)
  700	;   put_attr(A,
  701		     flux,
  702		     v(128, [], [], [], [], [], [], [], [K], [], [], [], [], []))
  703	),
  704	attach_all_not_holds___3(T, K).
  705
  706not_holds_all(A, B) :-
  707	C=suspension(D, active, _, 0, flux:not_holds_all___2__0(A, B, C), not_holds_all, A, B),
  708	term_variables(term(A, B), F),
  709	'chr gen_id'(D),
  710	nb_getval('$chr_store_global_list_flux____not_holds_all___2', E),
  711	b_setval('$chr_store_global_list_flux____not_holds_all___2',
  712		 [C|E]),
  713	attach_not_holds_all___2(F, C),
  714	setarg(2, C, inactive),
  715	'chr debug_event'(insert(not_holds_all(A, B)#C)),
  716	(   'chr debugging'
  717	->  (   'chr debug_event'(call(C)),
  718		not_holds_all___2__0(A, B, C)
  719	    ;   'chr debug_event'(fail(C)), !,
  720		fail
  721	    ),
  722	    (   'chr debug_event'(exit(C))
  723	    ;   'chr debug_event'(redo(C)),
  724		fail
  725	    )
  726	;   not_holds_all___2__0(A, B, C)
  727	).
  728
  729detach_if_then_or_holds___3([], _).
  730detach_if_then_or_holds___3([A|T], E) :-
  731	(   get_attr(A, flux, B)
  732	->  B=v(C, H, I, J, K, L, M, N, O, P, D, Q, R, S),
  733	    (   C/\512=:=512
  734	    ->  'chr sbag_del_element'(D, E, F),
  735		(   F==[]
  736		->  G is C/\ -513,
  737		    (   G==0
  738		    ->  del_attr(A, flux)
  739		    ;   put_attr(A,
  740				 flux,
  741				 v(G,
  742				   H,
  743				   I,
  744				   J,
  745				   K,
  746				   L,
  747				   M,
  748				   N,
  749				   O,
  750				   P,
  751				   [],
  752				   Q,
  753				   R,
  754				   S))
  755		    )
  756		;   put_attr(A,
  757			     flux,
  758			     v(C,
  759			       H,
  760			       I,
  761			       J,
  762			       K,
  763			       L,
  764			       M,
  765			       N,
  766			       O,
  767			       P,
  768			       F,
  769			       Q,
  770			       R,
  771			       S))
  772		)
  773	    ;   true
  774	    )
  775	;   true
  776	),
  777	detach_if_then_or_holds___3(T, E).
  778
  779attach_cancelled___2([], _).
  780attach_cancelled___2([A|T], P) :-
  781	(   get_attr(A, flux, B)
  782	->  B=v(C, D, E, F, G, H, I, J, K, L, M, N, O, Q),
  783	    (   C/\4096=:=4096
  784	    ->  R=v(C, D, E, F, G, H, I, J, K, L, M, N, O, [P|Q])
  785	    ;   S is C\/4096,
  786		R=v(S, D, E, F, G, H, I, J, K, L, M, N, O, [P])
  787	    ),
  788	    put_attr(A, flux, R)
  789	;   put_attr(A,
  790		     flux,
  791		     v(4096, [], [], [], [], [], [], [], [], [], [], [], [], [P]))
  792	),
  793	attach_cancelled___2(T, P).
  794
  795not_holds___2__2(E, A, F) :-
  796	(   'chr newvia_1'(A, B)
  797	->  get_attr(B, flux, C),
  798	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
  799	;   nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
  800		      D)
  801	), !,
  802	not_holds___2__2__0__6(D, E, A, F).
  803not_holds___2__2(A, B, C) :-
  804	not_holds___2__3(A, B, C).
  805
  806cancel___2__5(A, B, I) :-
  807	(   'chr newvia_2'(A, B, C)
  808	->  get_attr(C, flux, D),
  809	    D=v(_, _, _, _, _, _, _, _, _, _, _, _, _, E)
  810	;   nb_getval('$chr_store_global_list_flux____cancelled___2', E)
  811	),
  812	member(F, E),
  813	F=suspension(_, active, _, _, _, _, G, H),
  814	G==A,
  815	H==B,
  816	'chr debug_event'(try([I, F], [], true, true)), !,
  817	'chr debug_event'(apply([I, F], [], true, true)),
  818	'chr debug_event'(remove(F)),
  819	F=suspension(_, _, _, _, _, cancelled, J, K),
  820	setarg(2, F, removed),
  821	term_variables(term(J, K), N),
  822	nb_getval('$chr_store_global_list_flux____cancelled___2', L),
  823	'chr sbag_del_element'(L, F, M),
  824	b_setval('$chr_store_global_list_flux____cancelled___2', M),
  825	detach_cancelled___2(N, F),
  826	'chr debug_event'(remove(I)),
  827	I=suspension(_, _, _, _, _, cancel, O, P),
  828	setarg(2, I, removed),
  829	term_variables(term(O, P), S),
  830	nb_getval('$chr_store_global_list_flux____cancel___2', Q),
  831	'chr sbag_del_element'(Q, I, R),
  832	b_setval('$chr_store_global_list_flux____cancel___2', R),
  833	detach_cancel___2(S, I).
  834cancel___2__5(_, _, A) :-
  835	setarg(2, A, active).
  836
  837if_then_or_holds(A, B, C, D) :-
  838	E=suspension(G, active, _, 0, flux:if_then_or_holds___4__0(A, B, C, D, E), if_then_or_holds, A, B, C, D),
  839	term_variables(B, I, F),
  840	term_variables(D, F),
  841	'chr gen_id'(G),
  842	nb_getval('$chr_store_global_list_flux____if_then_or_holds___4', H),
  843	b_setval('$chr_store_global_list_flux____if_then_or_holds___4',
  844		 [E|H]),
  845	attach_if_then_or_holds___4(I, E),
  846	setarg(2, E, inactive),
  847	'chr debug_event'(insert(if_then_or_holds(A, B, C, D)#E)),
  848	(   'chr debugging'
  849	->  (   'chr debug_event'(call(E)),
  850		if_then_or_holds___4__0(A,
  851					B,
  852					C,
  853					D,
  854					E)
  855	    ;   'chr debug_event'(fail(E)), !,
  856		fail
  857	    ),
  858	    (   'chr debug_event'(exit(E))
  859	    ;   'chr debug_event'(redo(E)),
  860		fail
  861	    )
  862	;   if_then_or_holds___4__0(A, B, C, D, E)
  863	).
  864
  865or_holds___3__0(A, G, B, C) :-
  866	nonvar(A),
  867	A=[D|F],
  868	nonvar(B),
  869	B=[E|H],
  870	'chr debug_event'(try([C],
  871			      [],
  872			      true,
  873			      (D==E->true;D\=E->or_holds(F, [D|G], [E|H]);D=..[K|I], E=..[L|J], or_holds(F, [eq(I, J), D|G], [E|H])))), !,
  874	'chr debug_event'(apply([C],
  875				[],
  876				true,
  877				(D==E->true;D\=E->or_holds(F, [D|G], [E|H]);D=..[K|I], E=..[L|J], or_holds(F, [eq(I, J), D|G], [E|H])))),
  878	'chr debug_event'(remove(C)),
  879	C=suspension(_, _, _, _, _, or_holds, M, _, N),
  880	setarg(2, C, removed),
  881	term_variables(M, R, O),
  882	term_variables(N, O),
  883	nb_getval('$chr_store_global_list_flux____or_holds___3', P),
  884	'chr sbag_del_element'(P, C, Q),
  885	b_setval('$chr_store_global_list_flux____or_holds___3', Q),
  886	detach_or_holds___3(R, C),
  887	(   D==E
  888	->  true
  889	;   D\=E
  890	->  or_holds(F, [D|G], [E|H])
  891	;   D=..[_|S],
  892	    E=..[_|T],
  893	    or_holds(F,
  894		     [eq(S, T), D|G],
  895		     [E|H])
  896	).
  897or_holds___3__0(A, D, B, C) :-
  898	A==[],
  899	nonvar(B),
  900	B=[_|E],
  901	'chr debug_event'(try([C], [], true, or_holds(D, E))), !,
  902	'chr debug_event'(apply([C], [], true, or_holds(D, E))),
  903	'chr debug_event'(remove(C)),
  904	C=suspension(_, _, _, _, _, or_holds, F, _, G),
  905	setarg(2, C, removed),
  906	term_variables(F, K, H),
  907	term_variables(G, H),
  908	nb_getval('$chr_store_global_list_flux____or_holds___3', I),
  909	'chr sbag_del_element'(I, C, J),
  910	b_setval('$chr_store_global_list_flux____or_holds___3', J),
  911	detach_or_holds___3(K, C),
  912	or_holds(D, E).
  913or_holds___3__0(_, _, _, A) :-
  914	setarg(2, A, active).
  915
  916inst(A, B) :-
  917	\+ ( term_variables(A, D),
  918	     term_variables(B, C),
  919	     bound_free(C, D, G, E),
  920	     copy_term_vars(E, B, F),
  921	     \+ no_global_bindings(A=F, G)
  922	   ).
  923
  924cancel___2__4(E, A, F) :-
  925	(   'chr newvia_1'(A, B)
  926	->  get_attr(B, flux, C),
  927	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
  928	;   nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
  929		      D)
  930	), !,
  931	cancel___2__4__0__5(D, E, A, F).
  932cancel___2__4(A, B, C) :-
  933	cancel___2__5(A, B, C).
  934
  935not_holds___2__0(C, A, B) :-
  936	nonvar(A),
  937	A=[D|E],
  938	'chr debug_event'(try([B],
  939			      [],
  940			      true,
  941			      (neq(C, D), not_holds(C, E)))), !,
  942	'chr debug_event'(apply([B],
  943				[],
  944				true,
  945				(neq(C, D), not_holds(C, E)))),
  946	'chr debug_event'(remove(B)),
  947	B=suspension(_, _, _, _, _, not_holds, F, G),
  948	setarg(2, B, removed),
  949	term_variables(term(F, G), J),
  950	nb_getval('$chr_store_global_list_flux____not_holds___2', H),
  951	'chr sbag_del_element'(H, B, I),
  952	b_setval('$chr_store_global_list_flux____not_holds___2', I),
  953	detach_not_holds___2(J, B),
  954	neq(C, D),
  955	not_holds(C, E).
  956not_holds___2__0(_, A, B) :-
  957	A==[],
  958	'chr debug_event'(try([B], [], true, true)), !,
  959	'chr debug_event'(apply([B], [], true, true)),
  960	'chr debug_event'(remove(B)),
  961	B=suspension(_, _, _, _, _, not_holds, C, D),
  962	setarg(2, B, removed),
  963	term_variables(term(C, D), G),
  964	nb_getval('$chr_store_global_list_flux____not_holds___2', E),
  965	'chr sbag_del_element'(E, B, F),
  966	b_setval('$chr_store_global_list_flux____not_holds___2', F),
  967	detach_not_holds___2(G, B).
  968not_holds___2__0(E, A, F) :-
  969	(   'chr newvia_1'(A, B)
  970	->  get_attr(B, flux, C),
  971	    C=v(_, _, _, _, _, _, _, D, _, _, _, _, _, _)
  972	;   nb_getval('$chr_store_global_list_flux____all_holds___3', D)
  973	), !,
  974	not_holds___2__0__0__3(D, E, A, F).
  975not_holds___2__0(A, B, C) :-
  976	not_holds___2__1(A, B, C).
  977
  978attach_all_holds___3([], _).
  979attach_all_holds___3([A|T], J) :-
  980	(   get_attr(A, flux, B)
  981	->  B=v(C, D, E, F, G, H, I, K, L, M, N, O, P, Q),
  982	    (   C/\64=:=64
  983	    ->  R=v(C, D, E, F, G, H, I, [J|K], L, M, N, O, P, Q)
  984	    ;   S is C\/64,
  985		R=v(S, D, E, F, G, H, I, [J], L, M, N, O, P, Q)
  986	    ),
  987	    put_attr(A, flux, R)
  988	;   put_attr(A,
  989		     flux,
  990		     v(64, [], [], [], [], [], [], [J], [], [], [], [], [], []))
  991	),
  992	attach_all_holds___3(T, J).
  993
  994if_then_or_holds___3__0(J, O, A, L) :-
  995	(   'chr newvia_1'(A, B)
  996	->  get_attr(B, flux, C),
  997	    C=v(_, _, _, _, _, _, _, D, _, _, _, _, _, _)
  998	;   nb_getval('$chr_store_global_list_flux____all_holds___3', D)
  999	),
 1000	member(E, D),
 1001	E=suspension(_, active, _, _, _, _, G, H, F),
 1002	F==A,
 1003	(   copy_fluent(G, H, I, K),
 1004	    I=J,
 1005	    \+ call(#\+(K)),
 1006	    'chr debug_event'(try([L],
 1007				  [E],
 1008				  (copy_fluent(G, H, M, N), M=J, \+call(#\+(N))),
 1009				  or_holds(O, A))), !,
 1010	    'chr debug_event'(apply([L],
 1011				    [E],
 1012				    (copy_fluent(G, H, M, N), M=J, \+call(#\+(N))),
 1013				    or_holds(O, A))),
 1014	    'chr debug_event'(remove(L)),
 1015	    L=suspension(_, _, _, _, _, if_then_or_holds, P, Q, R),
 1016	    setarg(2, L, removed),
 1017	    term_variables(term(P, Q, R), U),
 1018	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 1019		      S),
 1020	    'chr sbag_del_element'(S, L, T),
 1021	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
 1022		     T),
 1023	    detach_if_then_or_holds___3(U, L),
 1024	    or_holds(O, A)
 1025	;   member(W, O),
 1026	    copy_fluent(G, H, V, X),
 1027	    V=W,
 1028	    \+ call(#\+(X)),
 1029	    'chr debug_event'(try([L],
 1030				  [E],
 1031				  (member(Z, O), copy_fluent(G, H, Y, A1), Y=Z, \+call(#\+(A1))),
 1032				  true)), !,
 1033	    'chr debug_event'(apply([L],
 1034				    [E],
 1035				    (member(Z, O), copy_fluent(G, H, Y, A1), Y=Z, \+call(#\+(A1))),
 1036				    true)),
 1037	    'chr debug_event'(remove(L)),
 1038	    L=suspension(_, _, _, _, _, if_then_or_holds, B1, C1, D1),
 1039	    setarg(2, L, removed),
 1040	    term_variables(term(B1, C1, D1), G1),
 1041	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 1042		      E1),
 1043	    'chr sbag_del_element'(E1, L, F1),
 1044	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
 1045		     F1),
 1046	    detach_if_then_or_holds___3(G1, L)
 1047	).
 1048if_then_or_holds___3__0(J, U, A, L) :-
 1049	(   'chr newvia_1'(A, B)
 1050	->  get_attr(B, flux, C),
 1051	    C=v(_, _, _, _, _, _, _, _, D, _, _, _, _, _)
 1052	;   nb_getval('$chr_store_global_list_flux____all_not_holds___3',
 1053		      D)
 1054	),
 1055	member(E, D),
 1056	E=suspension(_, active, _, _, _, _, G, H, F),
 1057	F==A,
 1058	(   copy_fluent(G, H, I, K),
 1059	    I=J,
 1060	    \+ call(#\+(K)),
 1061	    'chr debug_event'(try([L],
 1062				  [E],
 1063				  (copy_fluent(G, H, M, N), M=J, \+call(#\+(N))),
 1064				  true)), !,
 1065	    'chr debug_event'(apply([L],
 1066				    [E],
 1067				    (copy_fluent(G, H, M, N), M=J, \+call(#\+(N))),
 1068				    true)),
 1069	    'chr debug_event'(remove(L)),
 1070	    L=suspension(_, _, _, _, _, if_then_or_holds, O, P, Q),
 1071	    setarg(2, L, removed),
 1072	    term_variables(term(O, P, Q), T),
 1073	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 1074		      R),
 1075	    'chr sbag_del_element'(R, L, S),
 1076	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
 1077		     S),
 1078	    detach_if_then_or_holds___3(T, L)
 1079	;   member(W, U, I1),
 1080	    copy_fluent(G, H, V, X),
 1081	    V=W,
 1082	    \+ call(#\+(X)),
 1083	    'chr debug_event'(try([L],
 1084				  [E],
 1085				  (member(Z, U, B1), copy_fluent(G, H, Y, A1), Y=Z, \+call(#\+(A1))),
 1086				  if_then_or_holds(J, B1, A))), !,
 1087	    'chr debug_event'(apply([L],
 1088				    [E],
 1089				    (member(Z, U, B1), copy_fluent(G, H, Y, A1), Y=Z, \+call(#\+(A1))),
 1090				    if_then_or_holds(J, B1, A))),
 1091	    'chr debug_event'(remove(L)),
 1092	    L=suspension(_, _, _, _, _, if_then_or_holds, C1, D1, E1),
 1093	    setarg(2, L, removed),
 1094	    term_variables(term(C1, D1, E1), H1),
 1095	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 1096		      F1),
 1097	    'chr sbag_del_element'(F1, L, G1),
 1098	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
 1099		     G1),
 1100	    detach_if_then_or_holds___3(H1, L),
 1101	    if_then_or_holds(J, I1, A)
 1102	).
 1103if_then_or_holds___3__0(C, A, D, B) :-
 1104	A==[],
 1105	'chr debug_event'(try([B], [], true, not_holds(C, D))), !,
 1106	'chr debug_event'(apply([B], [], true, not_holds(C, D))),
 1107	'chr debug_event'(remove(B)),
 1108	B=suspension(_, _, _, _, _, if_then_or_holds, E, F, G),
 1109	setarg(2, B, removed),
 1110	term_variables(term(E, F, G), J),
 1111	nb_getval('$chr_store_global_list_flux____if_then_or_holds___3', H),
 1112	'chr sbag_del_element'(H, B, I),
 1113	b_setval('$chr_store_global_list_flux____if_then_or_holds___3', I),
 1114	detach_if_then_or_holds___3(J, B),
 1115	not_holds(C, D).
 1116if_then_or_holds___3__0(_, _, A, B) :-
 1117	A==[],
 1118	'chr debug_event'(try([B], [], true, true)), !,
 1119	'chr debug_event'(apply([B], [], true, true)),
 1120	'chr debug_event'(remove(B)),
 1121	B=suspension(_, _, _, _, _, if_then_or_holds, C, D, E),
 1122	setarg(2, B, removed),
 1123	term_variables(term(C, D, E), H),
 1124	nb_getval('$chr_store_global_list_flux____if_then_or_holds___3', F),
 1125	'chr sbag_del_element'(F, B, G),
 1126	b_setval('$chr_store_global_list_flux____if_then_or_holds___3', G),
 1127	detach_if_then_or_holds___3(H, B).
 1128if_then_or_holds___3__0(_, A, _, E) :-
 1129	member(eq(B, C), A),
 1130	or_neq(exists, B, C, D),
 1131	\+ call(D),
 1132	'chr debug_event'(try([E],
 1133			      [],
 1134			      (member(eq(F, G), A), or_neq(exists, F, G, H), \+call(H)),
 1135			      true)), !,
 1136	'chr debug_event'(apply([E],
 1137				[],
 1138				(member(eq(F, G), A), or_neq(exists, F, G, H), \+call(H)),
 1139				true)),
 1140	'chr debug_event'(remove(E)),
 1141	E=suspension(_, _, _, _, _, if_then_or_holds, I, J, K),
 1142	setarg(2, E, removed),
 1143	term_variables(term(I, J, K), N),
 1144	nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 1145		  L),
 1146	'chr sbag_del_element'(L, E, M),
 1147	b_setval('$chr_store_global_list_flux____if_then_or_holds___3', M),
 1148	detach_if_then_or_holds___3(N, E).
 1149if_then_or_holds___3__0(I, A, K, E) :-
 1150	member(eq(B, C), A, R),
 1151	\+ ( and_eq(B, C, D),
 1152	     call(D)
 1153	   ),
 1154	'chr debug_event'(try([E],
 1155			      [],
 1156			      (member(eq(F, G), A, J), \+ (and_eq(F, G, H), call(H))),
 1157			      if_then_or_holds(I, J, K))), !,
 1158	'chr debug_event'(apply([E],
 1159				[],
 1160				(member(eq(F, G), A, J), \+ (and_eq(F, G, H), call(H))),
 1161				if_then_or_holds(I, J, K))),
 1162	'chr debug_event'(remove(E)),
 1163	E=suspension(_, _, _, _, _, if_then_or_holds, L, M, N),
 1164	setarg(2, E, removed),
 1165	term_variables(term(L, M, N), Q),
 1166	nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 1167		  O),
 1168	'chr sbag_del_element'(O, E, P),
 1169	b_setval('$chr_store_global_list_flux____if_then_or_holds___3', P),
 1170	detach_if_then_or_holds___3(Q, E),
 1171	if_then_or_holds(I, R, K).
 1172if_then_or_holds___3__0(C, E, A, B) :-
 1173	nonvar(A),
 1174	A=[D|F],
 1175	'chr debug_event'(try([B],
 1176			      [],
 1177			      true,
 1178			      (C==D->or_holds(E, [D|F]);C\=D->if_then_or_holds(C, E, [], [D|F]);C=..[I|G], D=..[J|H], or_holds([neq(G, H)|E], [D|F]), if_then_or_holds(C, E, [], [D|F])))), !,
 1179	'chr debug_event'(apply([B],
 1180				[],
 1181				true,
 1182				(C==D->or_holds(E, [D|F]);C\=D->if_then_or_holds(C, E, [], [D|F]);C=..[I|G], D=..[J|H], or_holds([neq(G, H)|E], [D|F]), if_then_or_holds(C, E, [], [D|F])))),
 1183	'chr debug_event'(remove(B)),
 1184	B=suspension(_, _, _, _, _, if_then_or_holds, K, L, M),
 1185	setarg(2, B, removed),
 1186	term_variables(term(K, L, M), P),
 1187	nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 1188		  N),
 1189	'chr sbag_del_element'(N, B, O),
 1190	b_setval('$chr_store_global_list_flux____if_then_or_holds___3', O),
 1191	detach_if_then_or_holds___3(P, B),
 1192	(   C==D
 1193	->  or_holds(E, [D|F])
 1194	;   C\=D
 1195	->  if_then_or_holds(C, E, [], [D|F])
 1196	;   C=..[_|Q],
 1197	    D=..[_|R],
 1198	    or_holds([neq(Q, R)|E], [D|F]),
 1199	    if_then_or_holds(C, E, [], [D|F])
 1200	).
 1201if_then_or_holds___3__0(H, P, A, I) :-
 1202	(   'chr newvia_1'(A, B)
 1203	->  get_attr(B, flux, C),
 1204	    C=v(_, D, _, _, _, _, _, _, _, _, _, _, _, _)
 1205	;   nb_getval('$chr_store_global_list_flux____not_holds___2', D)
 1206	),
 1207	member(E, D),
 1208	E=suspension(_, active, _, _, _, _, G, F),
 1209	F==A,
 1210	(   G==H,
 1211	    'chr debug_event'(try([I], [E], G==H, true)), !,
 1212	    'chr debug_event'(apply([I], [E], G==H, true)),
 1213	    'chr debug_event'(remove(I)),
 1214	    I=suspension(_, _, _, _, _, if_then_or_holds, J, K, L),
 1215	    setarg(2, I, removed),
 1216	    term_variables(term(J, K, L), O),
 1217	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 1218		      M),
 1219	    'chr sbag_del_element'(M, I, N),
 1220	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
 1221		     N),
 1222	    detach_if_then_or_holds___3(O, I)
 1223	;   member(Q, P, Z),
 1224	    G==Q,
 1225	    'chr debug_event'(try([I],
 1226				  [E],
 1227				  (member(R, P, S), G==R),
 1228				  if_then_or_holds(H, S, A))), !,
 1229	    'chr debug_event'(apply([I],
 1230				    [E],
 1231				    (member(R, P, S), G==R),
 1232				    if_then_or_holds(H, S, A))),
 1233	    'chr debug_event'(remove(I)),
 1234	    I=suspension(_, _, _, _, _, if_then_or_holds, T, U, V),
 1235	    setarg(2, I, removed),
 1236	    term_variables(term(T, U, V), Y),
 1237	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 1238		      W),
 1239	    'chr sbag_del_element'(W, I, X),
 1240	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
 1241		     X),
 1242	    detach_if_then_or_holds___3(Y, I),
 1243	    if_then_or_holds(H, Z, A)
 1244	).
 1245if_then_or_holds___3__0(H, P, A, I) :-
 1246	(   'chr newvia_1'(A, B)
 1247	->  get_attr(B, flux, C),
 1248	    C=v(_, _, _, _, _, _, _, _, _, _, _, _, D, _)
 1249	;   nb_getval('$chr_store_global_list_flux____cancel___2', D)
 1250	),
 1251	member(E, D),
 1252	E=suspension(_, active, _, _, _, _, G, F),
 1253	F==A,
 1254	(   \+ G\=H,
 1255	    'chr debug_event'(try([I],
 1256				  [E],
 1257				  \+G\=H,
 1258				  true)), !,
 1259	    'chr debug_event'(apply([I],
 1260				    [E],
 1261				    \+G\=H,
 1262				    true)),
 1263	    'chr debug_event'(remove(I)),
 1264	    I=suspension(_, _, _, _, _, if_then_or_holds, J, K, L),
 1265	    setarg(2, I, removed),
 1266	    term_variables(term(J, K, L), O),
 1267	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 1268		      M),
 1269	    'chr sbag_del_element'(M, I, N),
 1270	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
 1271		     N),
 1272	    detach_if_then_or_holds___3(O, I)
 1273	;   member(Q, P),
 1274	    \+ G\=Q,
 1275	    'chr debug_event'(try([I],
 1276				  [E],
 1277				  (member(R, P), \+G\=R),
 1278				  true)), !,
 1279	    'chr debug_event'(apply([I],
 1280				    [E],
 1281				    (member(R, P), \+G\=R),
 1282				    true)),
 1283	    'chr debug_event'(remove(I)),
 1284	    I=suspension(_, _, _, _, _, if_then_or_holds, S, T, U),
 1285	    setarg(2, I, removed),
 1286	    term_variables(term(S, T, U), X),
 1287	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 1288		      V),
 1289	    'chr sbag_del_element'(V, I, W),
 1290	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
 1291		     W),
 1292	    detach_if_then_or_holds___3(X, I)
 1293	).
 1294if_then_or_holds___3__0(_, _, _, A) :-
 1295	setarg(2, A, active).
 1296
 1297cancel___2__3(E, A, F) :-
 1298	(   'chr newvia_1'(A, B)
 1299	->  get_attr(B, flux, C),
 1300	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
 1301	;   nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 1302		      D)
 1303	), !,
 1304	cancel___2__3__0__4(D, E, A, F).
 1305cancel___2__3(A, B, C) :-
 1306	cancel___2__4(A, B, C).
 1307
 1308detach_all_holds___3([], _).
 1309detach_all_holds___3([A|T], E) :-
 1310	(   get_attr(A, flux, B)
 1311	->  B=v(C, H, I, J, K, L, M, D, N, O, P, Q, R, S),
 1312	    (   C/\64=:=64
 1313	    ->  'chr sbag_del_element'(D, E, F),
 1314		(   F==[]
 1315		->  G is C/\ -65,
 1316		    (   G==0
 1317		    ->  del_attr(A, flux)
 1318		    ;   put_attr(A,
 1319				 flux,
 1320				 v(G,
 1321				   H,
 1322				   I,
 1323				   J,
 1324				   K,
 1325				   L,
 1326				   M,
 1327				   [],
 1328				   N,
 1329				   O,
 1330				   P,
 1331				   Q,
 1332				   R,
 1333				   S))
 1334		    )
 1335		;   put_attr(A,
 1336			     flux,
 1337			     v(C,
 1338			       H,
 1339			       I,
 1340			       J,
 1341			       K,
 1342			       L,
 1343			       M,
 1344			       F,
 1345			       N,
 1346			       O,
 1347			       P,
 1348			       Q,
 1349			       R,
 1350			       S))
 1351		)
 1352	    ;   true
 1353	    )
 1354	;   true
 1355	),
 1356	detach_all_holds___3(T, E).
 1357
 1358cancel___2__0__0__1([], A, B, C) :-
 1359	cancel___2__1(A, B, C).
 1360cancel___2__0__0__1([A|M], D, C, F) :-
 1361	(   A=suspension(_, active, _, _, _, _, E, B),
 1362	    B==C,
 1363	    \+ D\=E,
 1364	    'chr debug_event'(try([A],
 1365				  [F],
 1366				  \+D\=G,
 1367				  true))
 1368	->  'chr debug_event'(apply([A],
 1369				    [F],
 1370				    \+D\=G,
 1371				    true)),
 1372	    'chr debug_event'(remove(A)),
 1373	    A=suspension(_, _, _, _, _, not_holds, H, I),
 1374	    setarg(2, A, removed),
 1375	    term_variables(term(H, I), L),
 1376	    nb_getval('$chr_store_global_list_flux____not_holds___2', J),
 1377	    'chr sbag_del_element'(J, A, K),
 1378	    b_setval('$chr_store_global_list_flux____not_holds___2', K),
 1379	    detach_not_holds___2(L, A),
 1380	    setarg(2, F, active),
 1381	    (   F=suspension(_, active, _, _, _, _, _, _)
 1382	    ->  setarg(2, F, inactive),
 1383		cancel___2__0__0__1(M, D, C, F)
 1384	    ;   true
 1385	    )
 1386	;   cancel___2__0__0__1(M, D, C, F)
 1387	).
 1388
 1389attach_not_holds___2([], _).
 1390attach_not_holds___2([A|T], D) :-
 1391	(   get_attr(A, flux, B)
 1392	->  B=v(C, E, F, G, H, I, J, K, L, M, N, O, P, Q),
 1393	    (   C/\1=:=1
 1394	    ->  R=v(C, [D|E], F, G, H, I, J, K, L, M, N, O, P, Q)
 1395	    ;   S is C\/1,
 1396		R=v(S, [D], F, G, H, I, J, K, L, M, N, O, P, Q)
 1397	    ),
 1398	    put_attr(A, flux, R)
 1399	;   put_attr(A,
 1400		     flux,
 1401		     v(1, [D], [], [], [], [], [], [], [], [], [], [], [], []))
 1402	),
 1403	attach_not_holds___2(T, D).
 1404
 1405if_then_or_holds___4__0(F, A, H, B, C) :-
 1406	nonvar(A),
 1407	A=[D|G],
 1408	nonvar(B),
 1409	B=[E|I],
 1410	'chr debug_event'(try([C],
 1411			      [],
 1412			      true,
 1413			      (D==E->true;D\=E->if_then_or_holds(F, G, [D|H], [E|I]);D=..[L|J], E=..[M|K], if_then_or_holds(F, G, [eq(J, K), D|H], [E|I])))), !,
 1414	'chr debug_event'(apply([C],
 1415				[],
 1416				true,
 1417				(D==E->true;D\=E->if_then_or_holds(F, G, [D|H], [E|I]);D=..[L|J], E=..[M|K], if_then_or_holds(F, G, [eq(J, K), D|H], [E|I])))),
 1418	'chr debug_event'(remove(C)),
 1419	C=suspension(_, _, _, _, _, if_then_or_holds, _, N, _, O),
 1420	setarg(2, C, removed),
 1421	term_variables(N, S, P),
 1422	term_variables(O, P),
 1423	nb_getval('$chr_store_global_list_flux____if_then_or_holds___4',
 1424		  Q),
 1425	'chr sbag_del_element'(Q, C, R),
 1426	b_setval('$chr_store_global_list_flux____if_then_or_holds___4', R),
 1427	detach_if_then_or_holds___4(S, C),
 1428	(   D==E
 1429	->  true
 1430	;   D\=E
 1431	->  if_then_or_holds(F,
 1432			     G,
 1433			     [D|H],
 1434			     [E|I])
 1435	;   D=..[_|T],
 1436	    E=..[_|U],
 1437	    if_then_or_holds(F,
 1438			     G,
 1439			     [eq(T, U), D|H],
 1440			     [E|I])
 1441	).
 1442if_then_or_holds___4__0(D, A, E, B, C) :-
 1443	A==[],
 1444	nonvar(B),
 1445	B=[_|F],
 1446	'chr debug_event'(try([C],
 1447			      [],
 1448			      true,
 1449			      if_then_or_holds(D, E, F))), !,
 1450	'chr debug_event'(apply([C],
 1451				[],
 1452				true,
 1453				if_then_or_holds(D, E, F))),
 1454	'chr debug_event'(remove(C)),
 1455	C=suspension(_, _, _, _, _, if_then_or_holds, _, G, _, H),
 1456	setarg(2, C, removed),
 1457	term_variables(G, L, I),
 1458	term_variables(H, I),
 1459	nb_getval('$chr_store_global_list_flux____if_then_or_holds___4', J),
 1460	'chr sbag_del_element'(J, C, K),
 1461	b_setval('$chr_store_global_list_flux____if_then_or_holds___4', K),
 1462	detach_if_then_or_holds___4(L, C),
 1463	if_then_or_holds(D, E, F).
 1464if_then_or_holds___4__0(_, _, _, _, A) :-
 1465	setarg(2, A, active).
 1466
 1467all_holds___3__0(C, E, A, B) :-
 1468	nonvar(A),
 1469	A=[D|F],
 1470	'chr debug_event'(try([B],
 1471			      [],
 1472			      true,
 1473			      (\+ (C=D, call(E))->all_holds(C, E, F);C=..[J|G], D=..[K|H], or_neq(exists, G, H, I), all_holds(C, E#/\I, F)))), !,
 1474	'chr debug_event'(apply([B],
 1475				[],
 1476				true,
 1477				(\+ (C=D, call(E))->all_holds(C, E, F);C=..[J|G], D=..[K|H], or_neq(exists, G, H, I), all_holds(C, E#/\I, F)))),
 1478	'chr debug_event'(remove(B)),
 1479	B=suspension(_, _, _, _, _, all_holds, L, M, N),
 1480	setarg(2, B, removed),
 1481	term_variables(term(L, M, N), Q),
 1482	nb_getval('$chr_store_global_list_flux____all_holds___3', O),
 1483	'chr sbag_del_element'(O, B, P),
 1484	b_setval('$chr_store_global_list_flux____all_holds___3', P),
 1485	detach_all_holds___3(Q, B),
 1486	(   \+ ( C=D,
 1487		 call(E)
 1488	       )
 1489	->  all_holds(C, E, F)
 1490	;   C=..[_|R],
 1491	    D=..[_|S],
 1492	    or_neq(exists, R, S, T),
 1493	    all_holds(C, E#/\T, F)
 1494	).
 1495all_holds___3__0(E, F, A, G) :-
 1496	(   'chr newvia_1'(A, B)
 1497	->  get_attr(B, flux, C),
 1498	    C=v(_, D, _, _, _, _, _, _, _, _, _, _, _, _)
 1499	;   nb_getval('$chr_store_global_list_flux____not_holds___2', D)
 1500	), !,
 1501	all_holds___3__0__0__2(D, E, F, A, G).
 1502all_holds___3__0(A, B, C, D) :-
 1503	all_holds___3__1(A, B, C, D).
 1504
 1505cancel___2__2(E, A, F) :-
 1506	(   'chr newvia_1'(A, B)
 1507	->  get_attr(B, flux, C),
 1508	    C=v(_, _, _, _, D, _, _, _, _, _, _, _, _, _)
 1509	;   nb_getval('$chr_store_global_list_flux____or_holds___2', D)
 1510	), !,
 1511	cancel___2__2__0__3(D, E, A, F).
 1512cancel___2__2(A, B, C) :-
 1513	cancel___2__3(A, B, C).
 1514
 1515not_holds(A, B) :-
 1516	C=suspension(D, active, t, 0, flux:not_holds___2__0(A, B, C), not_holds, A, B),
 1517	term_variables(term(A, B), F),
 1518	'chr gen_id'(D),
 1519	nb_getval('$chr_store_global_list_flux____not_holds___2', E),
 1520	b_setval('$chr_store_global_list_flux____not_holds___2',
 1521		 [C|E]),
 1522	attach_not_holds___2(F, C),
 1523	setarg(2, C, inactive),
 1524	'chr debug_event'(insert(not_holds(A, B)#C)),
 1525	(   'chr debugging'
 1526	->  (   'chr debug_event'(call(C)),
 1527		not_holds___2__0(A, B, C)
 1528	    ;   'chr debug_event'(fail(C)), !,
 1529		fail
 1530	    ),
 1531	    (   'chr debug_event'(exit(C))
 1532	    ;   'chr debug_event'(redo(C)),
 1533		fail
 1534	    )
 1535	;   not_holds___2__0(A, B, C)
 1536	).
 1537
 1538detach_all_not_holds___3([], _).
 1539detach_all_not_holds___3([A|T], E) :-
 1540	(   get_attr(A, flux, B)
 1541	->  B=v(C, H, I, J, K, L, M, N, D, O, P, Q, R, S),
 1542	    (   C/\128=:=128
 1543	    ->  'chr sbag_del_element'(D, E, F),
 1544		(   F==[]
 1545		->  G is C/\ -129,
 1546		    (   G==0
 1547		    ->  del_attr(A, flux)
 1548		    ;   put_attr(A,
 1549				 flux,
 1550				 v(G,
 1551				   H,
 1552				   I,
 1553				   J,
 1554				   K,
 1555				   L,
 1556				   M,
 1557				   N,
 1558				   [],
 1559				   O,
 1560				   P,
 1561				   Q,
 1562				   R,
 1563				   S))
 1564		    )
 1565		;   put_attr(A,
 1566			     flux,
 1567			     v(C,
 1568			       H,
 1569			       I,
 1570			       J,
 1571			       K,
 1572			       L,
 1573			       M,
 1574			       N,
 1575			       F,
 1576			       O,
 1577			       P,
 1578			       Q,
 1579			       R,
 1580			       S))
 1581		)
 1582	    ;   true
 1583	    )
 1584	;   true
 1585	),
 1586	detach_all_not_holds___3(T, E).
 1587
 1588or_neq_c(G, A, B, J) :-
 1589	functor(A, C, E),
 1590	functor(B, D, F),
 1591	(   C=D,
 1592	    E=F
 1593	->  A=..[_|H],
 1594	    B=..[_|I],
 1595	    or_neq(G, H, I, J)
 1596	;   J=(0#=0)
 1597	).
 1598
 1599detach_not_holds___2([], _).
 1600detach_not_holds___2([A|T], E) :-
 1601	(   get_attr(A, flux, B)
 1602	->  B=v(C, D, H, I, J, K, L, M, N, O, P, Q, R, S),
 1603	    (   C/\1=:=1
 1604	    ->  'chr sbag_del_element'(D, E, F),
 1605		(   F==[]
 1606		->  G is C/\ -2,
 1607		    (   G==0
 1608		    ->  del_attr(A, flux)
 1609		    ;   put_attr(A,
 1610				 flux,
 1611				 v(G,
 1612				   [],
 1613				   H,
 1614				   I,
 1615				   J,
 1616				   K,
 1617				   L,
 1618				   M,
 1619				   N,
 1620				   O,
 1621				   P,
 1622				   Q,
 1623				   R,
 1624				   S))
 1625		    )
 1626		;   put_attr(A,
 1627			     flux,
 1628			     v(C,
 1629			       F,
 1630			       H,
 1631			       I,
 1632			       J,
 1633			       K,
 1634			       L,
 1635			       M,
 1636			       N,
 1637			       O,
 1638			       P,
 1639			       Q,
 1640			       R,
 1641			       S))
 1642		)
 1643	    ;   true
 1644	    )
 1645	;   true
 1646	),
 1647	detach_not_holds___2(T, E).
 1648
 1649cancel___2__1(E, A, F) :-
 1650	(   'chr newvia_1'(A, B)
 1651	->  get_attr(B, flux, C),
 1652	    C=v(_, _, D, _, _, _, _, _, _, _, _, _, _, _)
 1653	;   nb_getval('$chr_store_global_list_flux____not_holds_all___2',
 1654		      D)
 1655	), !,
 1656	cancel___2__1__0__2(D, E, A, F).
 1657cancel___2__1(A, B, C) :-
 1658	cancel___2__2(A, B, C).
 1659
 1660neq(A, B, C) :-
 1661	or_neq_c(exists, A, B, C).
 1662
 1663attach_if_then_or_holds___4([], _).
 1664attach_if_then_or_holds___4([A|T], N) :-
 1665	(   get_attr(A, flux, B)
 1666	->  B=v(C, D, E, F, G, H, I, J, K, L, M, O, P, Q),
 1667	    (   C/\1024=:=1024
 1668	    ->  R=v(C, D, E, F, G, H, I, J, K, L, M, [N|O], P, Q)
 1669	    ;   S is C\/1024,
 1670		R=v(S, D, E, F, G, H, I, J, K, L, M, [N], P, Q)
 1671	    ),
 1672	    put_attr(A, flux, R)
 1673	;   put_attr(A,
 1674		     flux,
 1675		     v(1024, [], [], [], [], [], [], [], [], [], [], [N], [], []))
 1676	),
 1677	attach_if_then_or_holds___4(T, N).
 1678
 1679cancel___2__2__0__3([], A, B, C) :-
 1680	cancel___2__3(A, B, C).
 1681cancel___2__2__0__3([A|O], E, C, G) :-
 1682	(   A=suspension(_, active, _, _, _, _, D, B),
 1683	    B==C,
 1684	    member(F, D),
 1685	    \+ E\=F,
 1686	    'chr debug_event'(try([A],
 1687				  [G],
 1688				  (member(H, I), \+E\=H),
 1689				  true))
 1690	->  'chr debug_event'(apply([A],
 1691				    [G],
 1692				    (member(H, I), \+E\=H),
 1693				    true)),
 1694	    'chr debug_event'(remove(A)),
 1695	    A=suspension(_, _, _, _, _, or_holds, J, K),
 1696	    setarg(2, A, removed),
 1697	    term_variables(term(J, K), N),
 1698	    nb_getval('$chr_store_global_list_flux____or_holds___2', L),
 1699	    'chr sbag_del_element'(L, A, M),
 1700	    b_setval('$chr_store_global_list_flux____or_holds___2', M),
 1701	    detach_or_holds___2(N, A),
 1702	    setarg(2, G, active),
 1703	    (   G=suspension(_, active, _, _, _, _, _, _)
 1704	    ->  setarg(2, G, inactive),
 1705		cancel___2__2__0__3(O, E, C, G)
 1706	    ;   true
 1707	    )
 1708	;   cancel___2__2__0__3(O, E, C, G)
 1709	).
 1710
 1711attr_unify_hook(v(C2, A, B, C, D, E, F, G, H, I, J, K, L, M), N) :-
 1712	sort(A, Q),
 1713	sort(B, T),
 1714	sort(C, W),
 1715	sort(D, Z),
 1716	sort(E, C1),
 1717	sort(F, F1),
 1718	sort(G, I1),
 1719	sort(H, L1),
 1720	sort(I, O1),
 1721	sort(J, R1),
 1722	sort(K, U1),
 1723	sort(L, X1),
 1724	sort(M, A2),
 1725	(   var(N)
 1726	->  (   get_attr(N, flux, O)
 1727	    ->  O=v(D2, P, S, V, Y, B1, E1, H1, K1, N1, Q1, T1, W1, Z1),
 1728		sort(P, R),
 1729		'chr merge_attributes'(Q, R, F2),
 1730		sort(S, U),
 1731		'chr merge_attributes'(T, U, G2),
 1732		sort(V, X),
 1733		'chr merge_attributes'(W, X, H2),
 1734		sort(Y, A1),
 1735		'chr merge_attributes'(Z, A1, I2),
 1736		sort(B1, D1),
 1737		'chr merge_attributes'(C1, D1, J2),
 1738		sort(E1, G1),
 1739		'chr merge_attributes'(F1, G1, K2),
 1740		sort(H1, J1),
 1741		'chr merge_attributes'(I1, J1, L2),
 1742		sort(K1, M1),
 1743		'chr merge_attributes'(L1, M1, M2),
 1744		sort(N1, P1),
 1745		'chr merge_attributes'(O1, P1, N2),
 1746		sort(Q1, S1),
 1747		'chr merge_attributes'(R1, S1, O2),
 1748		sort(T1, V1),
 1749		'chr merge_attributes'(U1, V1, P2),
 1750		sort(W1, Y1),
 1751		'chr merge_attributes'(X1, Y1, Q2),
 1752		sort(Z1, B2),
 1753		'chr merge_attributes'(A2, B2, R2),
 1754		E2 is C2\/D2,
 1755		put_attr(N,
 1756			 flux,
 1757			 v(E2,
 1758			   F2,
 1759			   G2,
 1760			   H2,
 1761			   I2,
 1762			   J2,
 1763			   K2,
 1764			   L2,
 1765			   M2,
 1766			   N2,
 1767			   O2,
 1768			   P2,
 1769			   Q2,
 1770			   R2)),
 1771		'$run_suspensions_not_holds___2'(F2),
 1772		'$run_suspensions_not_holds_all___2'(G2),
 1773		'$run_suspensions_duplicate_free___1'(H2),
 1774		'$run_suspensions_or_holds___2'(I2),
 1775		'$run_suspensions_or_holds___3'(J2),
 1776		'$run_suspensions_all_holds___2'(F1),
 1777		'$run_suspensions_all_holds___3'(L2),
 1778		'$run_suspensions_all_not_holds___3'(M2),
 1779		'$run_suspensions_if_then_holds___3'(O1),
 1780		'$run_suspensions_if_then_or_holds___3'(O2),
 1781		'$run_suspensions_if_then_or_holds___4'(P2),
 1782		'$run_suspensions_cancel___2'(Q2),
 1783		'$run_suspensions_cancelled___2'(A2)
 1784	    ;   put_attr(N,
 1785			 flux,
 1786			 v(C2,
 1787			   Q,
 1788			   T,
 1789			   W,
 1790			   Z,
 1791			   C1,
 1792			   F1,
 1793			   I1,
 1794			   L1,
 1795			   O1,
 1796			   R1,
 1797			   U1,
 1798			   X1,
 1799			   A2)),
 1800		'$run_suspensions_not_holds___2'(Q),
 1801		'$run_suspensions_not_holds_all___2'(T),
 1802		'$run_suspensions_duplicate_free___1'(W),
 1803		'$run_suspensions_or_holds___2'(Z),
 1804		'$run_suspensions_or_holds___3'(C1),
 1805		'$run_suspensions_all_holds___2'(F1),
 1806		'$run_suspensions_all_holds___3'(I1),
 1807		'$run_suspensions_all_not_holds___3'(L1),
 1808		'$run_suspensions_if_then_holds___3'(O1),
 1809		'$run_suspensions_if_then_or_holds___3'(R1),
 1810		'$run_suspensions_if_then_or_holds___4'(U1),
 1811		'$run_suspensions_cancel___2'(X1),
 1812		'$run_suspensions_cancelled___2'(A2)
 1813	    )
 1814	;   (   compound(N)
 1815	    ->  term_variables(N, S2),
 1816		attach_increment(S2,
 1817				 v(C2,
 1818				   Q,
 1819				   T,
 1820				   W,
 1821				   Z,
 1822				   C1,
 1823				   F1,
 1824				   I1,
 1825				   L1,
 1826				   O1,
 1827				   R1,
 1828				   U1,
 1829				   X1,
 1830				   A2))
 1831	    ;   true
 1832	    ),
 1833	    '$run_suspensions_not_holds___2'(Q),
 1834	    '$run_suspensions_not_holds_all___2'(T),
 1835	    '$run_suspensions_duplicate_free___1'(W),
 1836	    '$run_suspensions_or_holds___2'(Z),
 1837	    '$run_suspensions_or_holds___3'(C1),
 1838	    '$run_suspensions_all_holds___2'(F1),
 1839	    '$run_suspensions_all_holds___3'(I1),
 1840	    '$run_suspensions_all_not_holds___3'(L1),
 1841	    '$run_suspensions_if_then_holds___3'(O1),
 1842	    '$run_suspensions_if_then_or_holds___3'(R1),
 1843	    '$run_suspensions_if_then_or_holds___4'(U1),
 1844	    '$run_suspensions_cancel___2'(X1),
 1845	    '$run_suspensions_cancelled___2'(A2)
 1846	).
 1847
 1848or_neq(G, A, B) :-
 1849	functor(A, C, E),
 1850	functor(B, D, F),
 1851	(   C=D,
 1852	    E=F
 1853	->  A=..[_|H],
 1854	    B=..[_|I],
 1855	    or_neq(G, H, I, J),
 1856	    call(J)
 1857	;   true
 1858	).
 1859
 1860attach_or_holds___3([], _).
 1861attach_or_holds___3([A|T], H) :-
 1862	(   get_attr(A, flux, B)
 1863	->  B=v(C, D, E, F, G, I, J, K, L, M, N, O, P, Q),
 1864	    (   C/\16=:=16
 1865	    ->  R=v(C, D, E, F, G, [H|I], J, K, L, M, N, O, P, Q)
 1866	    ;   S is C\/16,
 1867		R=v(S, D, E, F, G, [H], J, K, L, M, N, O, P, Q)
 1868	    ),
 1869	    put_attr(A, flux, R)
 1870	;   put_attr(A,
 1871		     flux,
 1872		     v(16, [], [], [], [], [H], [], [], [], [], [], [], [], []))
 1873	),
 1874	attach_or_holds___3(T, H).
 1875
 1876binding(A, [B|E], [D|F], C) :-
 1877	(   A==B
 1878	->  C=D
 1879	;   binding(A, E, F, C)
 1880	).
 1881
 1882all_holds___3__1(G, H, A, O) :-
 1883	(   'chr newvia_1'(A, B)
 1884	->  get_attr(B, flux, C),
 1885	    C=v(_, _, _, _, _, _, _, _, D, _, _, _, _, _)
 1886	;   nb_getval('$chr_store_global_list_flux____all_not_holds___3',
 1887		      D)
 1888	),
 1889	member(E, D),
 1890	E=suspension(_, active, _, _, _, _, I, J, F),
 1891	F==A,
 1892	copy_fluent(G, H, K, M),
 1893	copy_fluent(I, J, L, N),
 1894	K=L,
 1895	call(M#/\N),
 1896	'chr debug_event'(try([O, E],
 1897			      [],
 1898			      (copy_fluent(G, H, P, R), copy_fluent(I, J, Q, S), P=Q, call(R#/\S)),
 1899			      false)), !,
 1900	'chr debug_event'(apply([O, E],
 1901				[],
 1902				(copy_fluent(G, H, P, R), copy_fluent(I, J, Q, S), P=Q, call(R#/\S)),
 1903				false)),
 1904	'chr debug_event'(remove(E)),
 1905	E=suspension(_, _, _, _, _, all_not_holds, T, U, V),
 1906	setarg(2, E, removed),
 1907	term_variables(term(T, U, V), Y),
 1908	nb_getval('$chr_store_global_list_flux____all_not_holds___3', W),
 1909	'chr sbag_del_element'(W, E, X),
 1910	b_setval('$chr_store_global_list_flux____all_not_holds___3', X),
 1911	detach_all_not_holds___3(Y, E),
 1912	'chr debug_event'(remove(O)),
 1913	O=suspension(_, _, _, _, _, all_holds, Z, A1, B1),
 1914	setarg(2, O, removed),
 1915	term_variables(term(Z, A1, B1), E1),
 1916	nb_getval('$chr_store_global_list_flux____all_holds___3', C1),
 1917	'chr sbag_del_element'(C1, O, D1),
 1918	b_setval('$chr_store_global_list_flux____all_holds___3', D1),
 1919	detach_all_holds___3(E1, O),
 1920	false.
 1921all_holds___3__1(E, F, A, G) :-
 1922	(   'chr newvia_1'(A, B)
 1923	->  get_attr(B, flux, C),
 1924	    C=v(_, _, _, _, D, _, _, _, _, _, _, _, _, _)
 1925	;   nb_getval('$chr_store_global_list_flux____or_holds___2', D)
 1926	), !,
 1927	all_holds___3__1__0__4(D, E, F, A, G).
 1928all_holds___3__1(A, B, C, D) :-
 1929	all_holds___3__2(A, B, C, D).
 1930
 1931all_holds___3__2__0__5([], A, B, C, D) :-
 1932	all_holds___3__3(A, B, C, D).
 1933all_holds___3__2__0__5([A|U], D, E, C, I) :-
 1934	(   A=suspension(_, active, _, _, _, _, G, T, B),
 1935	    B==C,
 1936	    copy_fluent(D, E, F, H),
 1937	    F=G,
 1938	    \+ call(#\+(H)),
 1939	    'chr debug_event'(try([A],
 1940				  [I],
 1941				  (copy_fluent(D, E, J, K), J=L, \+call(#\+(K))),
 1942				  or_holds(M, C)))
 1943	->  'chr debug_event'(apply([A],
 1944				    [I],
 1945				    (copy_fluent(D, E, J, K), J=L, \+call(#\+(K))),
 1946				    or_holds(M, C))),
 1947	    'chr debug_event'(remove(A)),
 1948	    A=suspension(_, _, _, _, _, if_then_or_holds, N, O, P),
 1949	    setarg(2, A, removed),
 1950	    term_variables(term(N, O, P), S),
 1951	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 1952		      Q),
 1953	    'chr sbag_del_element'(Q, A, R),
 1954	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
 1955		     R),
 1956	    detach_if_then_or_holds___3(S, A),
 1957	    setarg(2, I, active),
 1958	    or_holds(T, C),
 1959	    (   I=suspension(_, active, _, _, _, _, _, _, _)
 1960	    ->  setarg(2, I, inactive),
 1961		all_holds___3__2__0__5(U,
 1962				       D,
 1963				       E,
 1964				       C,
 1965				       I)
 1966	    ;   true
 1967	    )
 1968	;   all_holds___3__2__0__5(U, D, E, C, I)
 1969	).
 1970
 1971cancel___2__0(E, A, F) :-
 1972	(   'chr newvia_1'(A, B)
 1973	->  get_attr(B, flux, C),
 1974	    C=v(_, D, _, _, _, _, _, _, _, _, _, _, _, _)
 1975	;   nb_getval('$chr_store_global_list_flux____not_holds___2', D)
 1976	), !,
 1977	cancel___2__0__0__1(D, E, A, F).
 1978cancel___2__0(A, B, C) :-
 1979	cancel___2__1(A, B, C).
 1980
 1981cancelled(A, B) :-
 1982	C=suspension(D, active, _, 0, flux:cancelled___2__0(A, B, C), cancelled, A, B),
 1983	term_variables(term(A, B), F),
 1984	'chr gen_id'(D),
 1985	nb_getval('$chr_store_global_list_flux____cancelled___2', E),
 1986	b_setval('$chr_store_global_list_flux____cancelled___2',
 1987		 [C|E]),
 1988	attach_cancelled___2(F, C),
 1989	setarg(2, C, inactive),
 1990	'chr debug_event'(insert(cancelled(A, B)#C)),
 1991	(   'chr debugging'
 1992	->  (   'chr debug_event'(call(C)),
 1993		cancelled___2__0(A, B, C)
 1994	    ;   'chr debug_event'(fail(C)), !,
 1995		fail
 1996	    ),
 1997	    (   'chr debug_event'(exit(C))
 1998	    ;   'chr debug_event'(redo(C)),
 1999		fail
 2000	    )
 2001	;   cancelled___2__0(A, B, C)
 2002	).
 2003
 2004attach_or_holds___2([], _).
 2005attach_or_holds___2([A|T], G) :-
 2006	(   get_attr(A, flux, B)
 2007	->  B=v(C, D, E, F, H, I, J, K, L, M, N, O, P, Q),
 2008	    (   C/\8=:=8
 2009	    ->  R=v(C, D, E, F, [G|H], I, J, K, L, M, N, O, P, Q)
 2010	    ;   S is C\/8,
 2011		R=v(S, D, E, F, [G], I, J, K, L, M, N, O, P, Q)
 2012	    ),
 2013	    put_attr(A, flux, R)
 2014	;   put_attr(A,
 2015		     flux,
 2016		     v(8, [], [], [], [G], [], [], [], [], [], [], [], [], []))
 2017	),
 2018	attach_or_holds___2(T, G).
 2019
 2020attach_if_then_or_holds___3([], _).
 2021attach_if_then_or_holds___3([A|T], M) :-
 2022	(   get_attr(A, flux, B)
 2023	->  B=v(C, D, E, F, G, H, I, J, K, L, N, O, P, Q),
 2024	    (   C/\512=:=512
 2025	    ->  R=v(C, D, E, F, G, H, I, J, K, L, [M|N], O, P, Q)
 2026	    ;   S is C\/512,
 2027		R=v(S, D, E, F, G, H, I, J, K, L, [M], O, P, Q)
 2028	    ),
 2029	    put_attr(A, flux, R)
 2030	;   put_attr(A,
 2031		     flux,
 2032		     v(512, [], [], [], [], [], [], [], [], [], [M], [], [], []))
 2033	),
 2034	attach_if_then_or_holds___3(T, M).
 2035
 2036cancel___2__1__0__2([], A, B, C) :-
 2037	cancel___2__2(A, B, C).
 2038cancel___2__1__0__2([A|M], D, C, F) :-
 2039	(   A=suspension(_, active, _, _, _, _, E, B),
 2040	    B==C,
 2041	    \+ D\=E,
 2042	    'chr debug_event'(try([A],
 2043				  [F],
 2044				  \+D\=G,
 2045				  true))
 2046	->  'chr debug_event'(apply([A],
 2047				    [F],
 2048				    \+D\=G,
 2049				    true)),
 2050	    'chr debug_event'(remove(A)),
 2051	    A=suspension(_, _, _, _, _, not_holds_all, H, I),
 2052	    setarg(2, A, removed),
 2053	    term_variables(term(H, I), L),
 2054	    nb_getval('$chr_store_global_list_flux____not_holds_all___2',
 2055		      J),
 2056	    'chr sbag_del_element'(J, A, K),
 2057	    b_setval('$chr_store_global_list_flux____not_holds_all___2',
 2058		     K),
 2059	    detach_not_holds_all___2(L, A),
 2060	    setarg(2, F, active),
 2061	    (   F=suspension(_, active, _, _, _, _, _, _)
 2062	    ->  setarg(2, F, inactive),
 2063		cancel___2__1__0__2(M, D, C, F)
 2064	    ;   true
 2065	    )
 2066	;   cancel___2__1__0__2(M, D, C, F)
 2067	).
 2068
 2069all_holds___2__0(B, C, A) :-
 2070	'chr debug_event'(try([A],
 2071			      [],
 2072			      true,
 2073			      all_holds(B, 0#=0, C))), !,
 2074	'chr debug_event'(apply([A],
 2075				[],
 2076				true,
 2077				all_holds(B, 0#=0, C))),
 2078	'chr debug_event'(remove(A)),
 2079	A=suspension(_, _, _, _, _, all_holds, _, _),
 2080	setarg(2, A, removed),
 2081	nb_getval('$chr_store_global_list_flux____all_holds___2', D),
 2082	'chr sbag_del_element'(D, A, E),
 2083	b_setval('$chr_store_global_list_flux____all_holds___2', E),
 2084	all_holds(B, 0#=0, C).
 2085all_holds___2__0(_, _, A) :-
 2086	setarg(2, A, active).
 2087
 2088cancel(A, B) :-
 2089	C=suspension(D, active, _, 0, flux:cancel___2__0(A, B, C), cancel, A, B),
 2090	term_variables(term(A, B), F),
 2091	'chr gen_id'(D),
 2092	nb_getval('$chr_store_global_list_flux____cancel___2', E),
 2093	b_setval('$chr_store_global_list_flux____cancel___2', [C|E]),
 2094	attach_cancel___2(F, C),
 2095	setarg(2, C, inactive),
 2096	'chr debug_event'(insert(cancel(A, B)#C)),
 2097	(   'chr debugging'
 2098	->  (   'chr debug_event'(call(C)),
 2099		cancel___2__0(A, B, C)
 2100	    ;   'chr debug_event'(fail(C)), !,
 2101		fail
 2102	    ),
 2103	    (   'chr debug_event'(exit(C))
 2104	    ;   'chr debug_event'(redo(C)),
 2105		fail
 2106	    )
 2107	;   cancel___2__0(A, B, C)
 2108	).
 2109
 2110bound_free([], A, A, []).
 2111bound_free([C|A], B, D, F) :-
 2112	bound_free(A, B, E, G),
 2113	(   is_domain(C)
 2114	->  D=[C|E],
 2115	    F=G
 2116	;   D=E,
 2117	    F=[C|G]
 2118	).
 2119
 2120all_holds___3__1__0__4([], A, B, C, D) :-
 2121	all_holds___3__2(A, B, C, D).
 2122all_holds___3__1__0__4([A|T], E, F, C, J) :-
 2123	(   A=suspension(_, active, _, _, _, _, D, B),
 2124	    B==C,
 2125	    member(H, D),
 2126	    copy_fluent(E, F, G, I),
 2127	    G=H,
 2128	    \+ call(#\+(I)),
 2129	    'chr debug_event'(try([A],
 2130				  [J],
 2131				  (member(L, N), copy_fluent(E, F, K, M), K=L, \+call(#\+(M))),
 2132				  true))
 2133	->  'chr debug_event'(apply([A],
 2134				    [J],
 2135				    (member(L, N), copy_fluent(E, F, K, M), K=L, \+call(#\+(M))),
 2136				    true)),
 2137	    'chr debug_event'(remove(A)),
 2138	    A=suspension(_, _, _, _, _, or_holds, O, P),
 2139	    setarg(2, A, removed),
 2140	    term_variables(term(O, P), S),
 2141	    nb_getval('$chr_store_global_list_flux____or_holds___2', Q),
 2142	    'chr sbag_del_element'(Q, A, R),
 2143	    b_setval('$chr_store_global_list_flux____or_holds___2', R),
 2144	    detach_or_holds___2(S, A),
 2145	    setarg(2, J, active),
 2146	    (   J=suspension(_, active, _, _, _, _, _, _, _)
 2147	    ->  setarg(2, J, inactive),
 2148		all_holds___3__1__0__4(T,
 2149				       E,
 2150				       F,
 2151				       C,
 2152				       J)
 2153	    ;   true
 2154	    )
 2155	;   all_holds___3__1__0__4(T, E, F, C, J)
 2156	).
 2157
 2158attach_all_holds___2([], _).
 2159attach_all_holds___2([A|T], I) :-
 2160	(   get_attr(A, flux, B)
 2161	->  B=v(C, D, E, F, G, H, J, K, L, M, N, O, P, Q),
 2162	    (   C/\32=:=32
 2163	    ->  R=v(C, D, E, F, G, H, [I|J], K, L, M, N, O, P, Q)
 2164	    ;   S is C\/32,
 2165		R=v(S, D, E, F, G, H, [I], K, L, M, N, O, P, Q)
 2166	    ),
 2167	    put_attr(A, flux, R)
 2168	;   put_attr(A,
 2169		     flux,
 2170		     v(32, [], [], [], [], [], [I], [], [], [], [], [], [], []))
 2171	),
 2172	attach_all_holds___2(T, I).
 2173
 2174all_holds___3__0__0__2([], A, B, C, D) :-
 2175	all_holds___3__1(A, B, C, D).
 2176all_holds___3__0__0__2([A|M], F, G, C, D) :-
 2177	(   A=suspension(_, active, _, _, _, _, I, B),
 2178	    B==C,
 2179	    E=t(7, D, A),
 2180	    '$novel_production'(D, E),
 2181	    '$novel_production'(A, E),
 2182	    copy_fluent(F, G, K, L),
 2183	    'chr debug_event'(try([],
 2184				  [D, A],
 2185				  copy_fluent(F, G, H, J),
 2186				  (H=I, call(#\+(J)))))
 2187	->  'chr debug_event'(apply([],
 2188				    [D, A],
 2189				    copy_fluent(F,
 2190						G,
 2191						H,
 2192						J),
 2193				    (H=I, call(#\+(J))))),
 2194	    '$extend_history'(D, E),
 2195	    setarg(2, D, active),
 2196	    K=I,
 2197	    call(#\+(L)),
 2198	    (   D=suspension(_, active, _, _, _, _, _, _, _)
 2199	    ->  setarg(2, D, inactive),
 2200		all_holds___3__0__0__2(M,
 2201				       F,
 2202				       G,
 2203				       C,
 2204				       D)
 2205	    ;   true
 2206	    )
 2207	;   all_holds___3__0__0__2(M, F, G, C, D)
 2208	).
 2209
 2210cancel___2__4__0__5([], A, B, C) :-
 2211	cancel___2__5(A, B, C).
 2212cancel___2__4__0__5([A|P], E, C, G) :-
 2213	(   A=suspension(_, active, _, _, _, _, _, D, B),
 2214	    B==C,
 2215	    member(F, D),
 2216	    \+ E\=F,
 2217	    'chr debug_event'(try([A],
 2218				  [G],
 2219				  (member(H, I), \+E\=H),
 2220				  true))
 2221	->  'chr debug_event'(apply([A],
 2222				    [G],
 2223				    (member(H, I), \+E\=H),
 2224				    true)),
 2225	    'chr debug_event'(remove(A)),
 2226	    A=suspension(_, _, _, _, _, if_then_or_holds, J, K, L),
 2227	    setarg(2, A, removed),
 2228	    term_variables(term(J, K, L), O),
 2229	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 2230		      M),
 2231	    'chr sbag_del_element'(M, A, N),
 2232	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
 2233		     N),
 2234	    detach_if_then_or_holds___3(O, A),
 2235	    setarg(2, G, active),
 2236	    (   G=suspension(_, active, _, _, _, _, _, _)
 2237	    ->  setarg(2, G, inactive),
 2238		cancel___2__4__0__5(P, E, C, G)
 2239	    ;   true
 2240	    )
 2241	;   cancel___2__4__0__5(P, E, C, G)
 2242	).
 2243
 2244all_holds___3__2(E, F, A, G) :-
 2245	(   'chr newvia_1'(A, B)
 2246	->  get_attr(B, flux, C),
 2247	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
 2248	;   nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 2249		      D)
 2250	), !,
 2251	all_holds___3__2__0__5(D, E, F, A, G).
 2252all_holds___3__2(A, B, C, D) :-
 2253	all_holds___3__3(A, B, C, D).
 2254
 2255attach_cancel___2([], _).
 2256attach_cancel___2([A|T], O) :-
 2257	(   get_attr(A, flux, B)
 2258	->  B=v(C, D, E, F, G, H, I, J, K, L, M, N, P, Q),
 2259	    (   C/\2048=:=2048
 2260	    ->  R=v(C, D, E, F, G, H, I, J, K, L, M, N, [O|P], Q)
 2261	    ;   S is C\/2048,
 2262		R=v(S, D, E, F, G, H, I, J, K, L, M, N, [O], Q)
 2263	    ),
 2264	    put_attr(A, flux, R)
 2265	;   put_attr(A,
 2266		     flux,
 2267		     v(2048, [], [], [], [], [], [], [], [], [], [], [], [O], []))
 2268	),
 2269	attach_cancel___2(T, O).
 2270
 2271if_then_holds(A, B, C) :-
 2272	D=suspension(E, active, _, 0, flux:if_then_holds___3__0(A, B, C, D), if_then_holds, A, B, C),
 2273	'chr gen_id'(E),
 2274	nb_getval('$chr_store_global_list_flux____if_then_holds___3', F),
 2275	b_setval('$chr_store_global_list_flux____if_then_holds___3',
 2276		 [D|F]),
 2277	attach_if_then_holds___3([], D),
 2278	setarg(2, D, inactive),
 2279	'chr debug_event'(insert(if_then_holds(A, B, C)#D)),
 2280	(   'chr debugging'
 2281	->  (   'chr debug_event'(call(D)),
 2282		if_then_holds___3__0(A, B, C, D)
 2283	    ;   'chr debug_event'(fail(D)), !,
 2284		fail
 2285	    ),
 2286	    (   'chr debug_event'(exit(D))
 2287	    ;   'chr debug_event'(redo(D)),
 2288		fail
 2289	    )
 2290	;   if_then_holds___3__0(A, B, C, D)
 2291	).
 2292
 2293neq(A, B) :-
 2294	or_neq(exists, A, B).
 2295
 2296neq_all(A, B) :-
 2297	or_neq(forall, A, B).
 2298
 2299detach_or_holds___3([], _).
 2300detach_or_holds___3([A|T], E) :-
 2301	(   get_attr(A, flux, B)
 2302	->  B=v(C, H, I, J, K, D, L, M, N, O, P, Q, R, S),
 2303	    (   C/\16=:=16
 2304	    ->  'chr sbag_del_element'(D, E, F),
 2305		(   F==[]
 2306		->  G is C/\ -17,
 2307		    (   G==0
 2308		    ->  del_attr(A, flux)
 2309		    ;   put_attr(A,
 2310				 flux,
 2311				 v(G,
 2312				   H,
 2313				   I,
 2314				   J,
 2315				   K,
 2316				   [],
 2317				   L,
 2318				   M,
 2319				   N,
 2320				   O,
 2321				   P,
 2322				   Q,
 2323				   R,
 2324				   S))
 2325		    )
 2326		;   put_attr(A,
 2327			     flux,
 2328			     v(C,
 2329			       H,
 2330			       I,
 2331			       J,
 2332			       K,
 2333			       F,
 2334			       L,
 2335			       M,
 2336			       N,
 2337			       O,
 2338			       P,
 2339			       Q,
 2340			       R,
 2341			       S))
 2342		)
 2343	    ;   true
 2344	    )
 2345	;   true
 2346	),
 2347	detach_or_holds___3(T, E).
 2348
 2349cancel___2__3__0__4([], A, B, C) :-
 2350	cancel___2__4(A, B, C).
 2351cancel___2__3__0__4([A|N], D, C, F) :-
 2352	(   A=suspension(_, active, _, _, _, _, E, _, B),
 2353	    B==C,
 2354	    \+ D\=E,
 2355	    'chr debug_event'(try([A],
 2356				  [F],
 2357				  \+D\=G,
 2358				  true))
 2359	->  'chr debug_event'(apply([A],
 2360				    [F],
 2361				    \+D\=G,
 2362				    true)),
 2363	    'chr debug_event'(remove(A)),
 2364	    A=suspension(_, _, _, _, _, if_then_or_holds, H, I, J),
 2365	    setarg(2, A, removed),
 2366	    term_variables(term(H, I, J), M),
 2367	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 2368		      K),
 2369	    'chr sbag_del_element'(K, A, L),
 2370	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
 2371		     L),
 2372	    detach_if_then_or_holds___3(M, A),
 2373	    setarg(2, F, active),
 2374	    (   F=suspension(_, active, _, _, _, _, _, _)
 2375	    ->  setarg(2, F, inactive),
 2376		cancel___2__3__0__4(N, D, C, F)
 2377	    ;   true
 2378	    )
 2379	;   cancel___2__3__0__4(N, D, C, F)
 2380	).
 2381
 2382not_holds___2__0__0__3([], A, B, C) :-
 2383	not_holds___2__1(A, B, C).
 2384not_holds___2__0__0__3([A|M], I, C, D) :-
 2385	(   A=suspension(_, active, _, _, _, _, F, G, B),
 2386	    B==C,
 2387	    E=t(7, A, D),
 2388	    '$novel_production'(A, E),
 2389	    '$novel_production'(D, E),
 2390	    copy_fluent(F, G, K, L),
 2391	    'chr debug_event'(try([],
 2392				  [A, D],
 2393				  copy_fluent(F, G, H, J),
 2394				  (H=I, call(#\+(J)))))
 2395	->  'chr debug_event'(apply([],
 2396				    [A, D],
 2397				    copy_fluent(F,
 2398						G,
 2399						H,
 2400						J),
 2401				    (H=I, call(#\+(J))))),
 2402	    '$extend_history'(D, E),
 2403	    setarg(2, D, active),
 2404	    K=I,
 2405	    call(#\+(L)),
 2406	    (   D=suspension(_, active, _, _, _, _, _, _)
 2407	    ->  setarg(2, D, inactive),
 2408		not_holds___2__0__0__3(M, I, C, D)
 2409	    ;   true
 2410	    )
 2411	;   not_holds___2__0__0__3(M, I, C, D)
 2412	).
 2413
 2414detach_if_then_or_holds___4([], _).
 2415detach_if_then_or_holds___4([A|T], E) :-
 2416	(   get_attr(A, flux, B)
 2417	->  B=v(C, H, I, J, K, L, M, N, O, P, Q, D, R, S),
 2418	    (   C/\1024=:=1024
 2419	    ->  'chr sbag_del_element'(D, E, F),
 2420		(   F==[]
 2421		->  G is C/\ -1025,
 2422		    (   G==0
 2423		    ->  del_attr(A, flux)
 2424		    ;   put_attr(A,
 2425				 flux,
 2426				 v(G,
 2427				   H,
 2428				   I,
 2429				   J,
 2430				   K,
 2431				   L,
 2432				   M,
 2433				   N,
 2434				   O,
 2435				   P,
 2436				   Q,
 2437				   [],
 2438				   R,
 2439				   S))
 2440		    )
 2441		;   put_attr(A,
 2442			     flux,
 2443			     v(C,
 2444			       H,
 2445			       I,
 2446			       J,
 2447			       K,
 2448			       L,
 2449			       M,
 2450			       N,
 2451			       O,
 2452			       P,
 2453			       Q,
 2454			       F,
 2455			       R,
 2456			       S))
 2457		)
 2458	    ;   true
 2459	    )
 2460	;   true
 2461	),
 2462	detach_if_then_or_holds___4(T, E).
 2463
 2464attach_not_holds_all___2([], _).
 2465attach_not_holds_all___2([A|T], E) :-
 2466	(   get_attr(A, flux, B)
 2467	->  B=v(C, D, F, G, H, I, J, K, L, M, N, O, P, Q),
 2468	    (   C/\2=:=2
 2469	    ->  R=v(C, D, [E|F], G, H, I, J, K, L, M, N, O, P, Q)
 2470	    ;   S is C\/2,
 2471		R=v(S, D, [E], G, H, I, J, K, L, M, N, O, P, Q)
 2472	    ),
 2473	    put_attr(A, flux, R)
 2474	;   put_attr(A,
 2475		     flux,
 2476		     v(2, [], [E], [], [], [], [], [], [], [], [], [], [], []))
 2477	),
 2478	attach_not_holds_all___2(T, E).
 2479
 2480not_holds___2__1__0__5([], A, B, C) :-
 2481	not_holds___2__2(A, B, C).
 2482not_holds___2__1__0__5([A|Q], E, C, G) :-
 2483	(   A=suspension(_, active, _, _, _, _, D, B),
 2484	    B==C,
 2485	    member(F, D, P),
 2486	    E==F,
 2487	    'chr debug_event'(try([A],
 2488				  [G],
 2489				  (member(H, J, I), E==H),
 2490				  or_holds(I, C)))
 2491	->  'chr debug_event'(apply([A],
 2492				    [G],
 2493				    (member(H, J, I), E==H),
 2494				    or_holds(I, C))),
 2495	    'chr debug_event'(remove(A)),
 2496	    A=suspension(_, _, _, _, _, or_holds, K, L),
 2497	    setarg(2, A, removed),
 2498	    term_variables(term(K, L), O),
 2499	    nb_getval('$chr_store_global_list_flux____or_holds___2', M),
 2500	    'chr sbag_del_element'(M, A, N),
 2501	    b_setval('$chr_store_global_list_flux____or_holds___2', N),
 2502	    detach_or_holds___2(O, A),
 2503	    setarg(2, G, active),
 2504	    or_holds(P, C),
 2505	    (   G=suspension(_, active, _, _, _, _, _, _)
 2506	    ->  setarg(2, G, inactive),
 2507		not_holds___2__1__0__5(Q, E, C, G)
 2508	    ;   true
 2509	    )
 2510	;   not_holds___2__1__0__5(Q, E, C, G)
 2511	).
 2512
 2513all_holds___3__4(_, _, _, A) :-
 2514	setarg(2, A, active).
 2515
 2516or_holds___2__0(G, A, M) :-
 2517	(   'chr newvia_1'(A, B)
 2518	->  get_attr(B, flux, C),
 2519	    C=v(_, _, _, _, _, _, _, D, _, _, _, _, _, _)
 2520	;   nb_getval('$chr_store_global_list_flux____all_holds___3', D)
 2521	),
 2522	member(E, D),
 2523	E=suspension(_, active, _, _, _, _, H, I, F),
 2524	F==A,
 2525	member(K, G),
 2526	copy_fluent(H, I, J, L),
 2527	J=K,
 2528	\+ call(#\+(L)),
 2529	'chr debug_event'(try([M],
 2530			      [E],
 2531			      (member(O, G), copy_fluent(H, I, N, P), N=O, \+call(#\+(P))),
 2532			      true)), !,
 2533	'chr debug_event'(apply([M],
 2534				[E],
 2535				(member(O, G), copy_fluent(H, I, N, P), N=O, \+call(#\+(P))),
 2536				true)),
 2537	'chr debug_event'(remove(M)),
 2538	M=suspension(_, _, _, _, _, or_holds, Q, R),
 2539	setarg(2, M, removed),
 2540	term_variables(term(Q, R), U),
 2541	nb_getval('$chr_store_global_list_flux____or_holds___2', S),
 2542	'chr sbag_del_element'(S, M, T),
 2543	b_setval('$chr_store_global_list_flux____or_holds___2', T),
 2544	detach_or_holds___2(U, M).
 2545or_holds___2__0(G, A, M) :-
 2546	(   'chr newvia_1'(A, B)
 2547	->  get_attr(B, flux, C),
 2548	    C=v(_, _, _, _, _, _, _, _, D, _, _, _, _, _)
 2549	;   nb_getval('$chr_store_global_list_flux____all_not_holds___3',
 2550		      D)
 2551	),
 2552	member(E, D),
 2553	E=suspension(_, active, _, _, _, _, H, I, F),
 2554	F==A,
 2555	member(K, G, W),
 2556	copy_fluent(H, I, J, L),
 2557	J=K,
 2558	\+ call(#\+(L)),
 2559	'chr debug_event'(try([M],
 2560			      [E],
 2561			      (member(O, G, Q), copy_fluent(H, I, N, P), N=O, \+call(#\+(P))),
 2562			      or_holds(Q, A))), !,
 2563	'chr debug_event'(apply([M],
 2564				[E],
 2565				(member(O, G, Q), copy_fluent(H, I, N, P), N=O, \+call(#\+(P))),
 2566				or_holds(Q, A))),
 2567	'chr debug_event'(remove(M)),
 2568	M=suspension(_, _, _, _, _, or_holds, R, S),
 2569	setarg(2, M, removed),
 2570	term_variables(term(R, S), V),
 2571	nb_getval('$chr_store_global_list_flux____or_holds___2', T),
 2572	'chr sbag_del_element'(T, M, U),
 2573	b_setval('$chr_store_global_list_flux____or_holds___2', U),
 2574	detach_or_holds___2(V, M),
 2575	or_holds(W, A).
 2576or_holds___2__0(A, E, D) :-
 2577	nonvar(A),
 2578	A=[C|B],
 2579	B==[],
 2580	C\=eq(_, _),
 2581	C\=neq(_, _),
 2582	'chr debug_event'(try([D],
 2583			      [],
 2584			      (C\=eq(F, G), C\=neq(H, I)),
 2585			      holds(C, E))), !,
 2586	'chr debug_event'(apply([D],
 2587				[],
 2588				(C\=eq(F, G), C\=neq(H, I)),
 2589				holds(C, E))),
 2590	'chr debug_event'(remove(D)),
 2591	D=suspension(_, _, _, _, _, or_holds, J, K),
 2592	setarg(2, D, removed),
 2593	term_variables(term(J, K), N),
 2594	nb_getval('$chr_store_global_list_flux____or_holds___2', L),
 2595	'chr sbag_del_element'(L, D, M),
 2596	b_setval('$chr_store_global_list_flux____or_holds___2', M),
 2597	detach_or_holds___2(N, D),
 2598	holds(C, E).
 2599or_holds___2__0(A, _, C) :-
 2600	\+ ( member(B, A),
 2601	     B\=eq(_, _),
 2602	     B\=neq(_, _)
 2603	   ),
 2604	'chr debug_event'(try([C],
 2605			      [],
 2606			      \+ (member(D, A), D\=eq(F, G), D\=neq(H, I)),
 2607			      (or_and_eq(A, E), call(E)))), !,
 2608	'chr debug_event'(apply([C],
 2609				[],
 2610				\+ (member(D, A), D\=eq(F, G), D\=neq(H, I)),
 2611				(or_and_eq(A, E), call(E)))),
 2612	'chr debug_event'(remove(C)),
 2613	C=suspension(_, _, _, _, _, or_holds, J, K),
 2614	setarg(2, C, removed),
 2615	term_variables(term(J, K), N),
 2616	nb_getval('$chr_store_global_list_flux____or_holds___2', L),
 2617	'chr sbag_del_element'(L, C, M),
 2618	b_setval('$chr_store_global_list_flux____or_holds___2', M),
 2619	detach_or_holds___2(N, C),
 2620	or_and_eq(A, O),
 2621	call(O).
 2622or_holds___2__0(B, A, D) :-
 2623	A==[],
 2624	member(C, B, P),
 2625	C\=eq(_, _),
 2626	C\=neq(_, _),
 2627	'chr debug_event'(try([D],
 2628			      [],
 2629			      (member(E, B, F), E\=eq(G, H), E\=neq(I, J)),
 2630			      or_holds(F, []))), !,
 2631	'chr debug_event'(apply([D],
 2632				[],
 2633				(member(E, B, F), E\=eq(G, H), E\=neq(I, J)),
 2634				or_holds(F, []))),
 2635	'chr debug_event'(remove(D)),
 2636	D=suspension(_, _, _, _, _, or_holds, K, L),
 2637	setarg(2, D, removed),
 2638	term_variables(term(K, L), O),
 2639	nb_getval('$chr_store_global_list_flux____or_holds___2', M),
 2640	'chr sbag_del_element'(M, D, N),
 2641	b_setval('$chr_store_global_list_flux____or_holds___2', N),
 2642	detach_or_holds___2(O, D),
 2643	or_holds(P, []).
 2644or_holds___2__0(A, _, E) :-
 2645	member(eq(B, C), A),
 2646	or_neq(exists, B, C, D),
 2647	\+ call(D),
 2648	'chr debug_event'(try([E],
 2649			      [],
 2650			      (member(eq(F, G), A), or_neq(exists, F, G, H), \+call(H)),
 2651			      true)), !,
 2652	'chr debug_event'(apply([E],
 2653				[],
 2654				(member(eq(F, G), A), or_neq(exists, F, G, H), \+call(H)),
 2655				true)),
 2656	'chr debug_event'(remove(E)),
 2657	E=suspension(_, _, _, _, _, or_holds, I, J),
 2658	setarg(2, E, removed),
 2659	term_variables(term(I, J), M),
 2660	nb_getval('$chr_store_global_list_flux____or_holds___2', K),
 2661	'chr sbag_del_element'(K, E, L),
 2662	b_setval('$chr_store_global_list_flux____or_holds___2', L),
 2663	detach_or_holds___2(M, E).
 2664or_holds___2__0(A, _, E) :-
 2665	member(neq(B, C), A),
 2666	and_eq(B, C, D),
 2667	\+ call(D),
 2668	'chr debug_event'(try([E],
 2669			      [],
 2670			      (member(neq(F, G), A), and_eq(F, G, H), \+call(H)),
 2671			      true)), !,
 2672	'chr debug_event'(apply([E],
 2673				[],
 2674				(member(neq(F, G), A), and_eq(F, G, H), \+call(H)),
 2675				true)),
 2676	'chr debug_event'(remove(E)),
 2677	E=suspension(_, _, _, _, _, or_holds, I, J),
 2678	setarg(2, E, removed),
 2679	term_variables(term(I, J), M),
 2680	nb_getval('$chr_store_global_list_flux____or_holds___2', K),
 2681	'chr sbag_del_element'(K, E, L),
 2682	b_setval('$chr_store_global_list_flux____or_holds___2', L),
 2683	detach_or_holds___2(M, E).
 2684or_holds___2__0(A, J, E) :-
 2685	member(eq(B, C), A, P),
 2686	\+ ( and_eq(B, C, D),
 2687	     call(D)
 2688	   ),
 2689	'chr debug_event'(try([E],
 2690			      [],
 2691			      (member(eq(F, G), A, I), \+ (and_eq(F, G, H), call(H))),
 2692			      or_holds(I, J))), !,
 2693	'chr debug_event'(apply([E],
 2694				[],
 2695				(member(eq(F, G), A, I), \+ (and_eq(F, G, H), call(H))),
 2696				or_holds(I, J))),
 2697	'chr debug_event'(remove(E)),
 2698	E=suspension(_, _, _, _, _, or_holds, K, L),
 2699	setarg(2, E, removed),
 2700	term_variables(term(K, L), O),
 2701	nb_getval('$chr_store_global_list_flux____or_holds___2', M),
 2702	'chr sbag_del_element'(M, E, N),
 2703	b_setval('$chr_store_global_list_flux____or_holds___2', N),
 2704	detach_or_holds___2(O, E),
 2705	or_holds(P, J).
 2706or_holds___2__0(A, J, E) :-
 2707	member(neq(B, C), A, P),
 2708	\+ ( or_neq(exists, B, C, D),
 2709	     call(D)
 2710	   ),
 2711	'chr debug_event'(try([E],
 2712			      [],
 2713			      (member(neq(F, G), A, I), \+ (or_neq(exists, F, G, H), call(H))),
 2714			      or_holds(I, J))), !,
 2715	'chr debug_event'(apply([E],
 2716				[],
 2717				(member(neq(F, G), A, I), \+ (or_neq(exists, F, G, H), call(H))),
 2718				or_holds(I, J))),
 2719	'chr debug_event'(remove(E)),
 2720	E=suspension(_, _, _, _, _, or_holds, K, L),
 2721	setarg(2, E, removed),
 2722	term_variables(term(K, L), O),
 2723	nb_getval('$chr_store_global_list_flux____or_holds___2', M),
 2724	'chr sbag_del_element'(M, E, N),
 2725	b_setval('$chr_store_global_list_flux____or_holds___2', N),
 2726	detach_or_holds___2(O, E),
 2727	or_holds(P, J).
 2728or_holds___2__0(C, A, B) :-
 2729	nonvar(A),
 2730	A=[D|E],
 2731	'chr debug_event'(try([B],
 2732			      [],
 2733			      true,
 2734			      or_holds(C, [], [D|E]))), !,
 2735	'chr debug_event'(apply([B],
 2736				[],
 2737				true,
 2738				or_holds(C, [], [D|E]))),
 2739	'chr debug_event'(remove(B)),
 2740	B=suspension(_, _, _, _, _, or_holds, F, G),
 2741	setarg(2, B, removed),
 2742	term_variables(term(F, G), J),
 2743	nb_getval('$chr_store_global_list_flux____or_holds___2', H),
 2744	'chr sbag_del_element'(H, B, I),
 2745	b_setval('$chr_store_global_list_flux____or_holds___2', I),
 2746	detach_or_holds___2(J, B),
 2747	or_holds(C, [], [D|E]).
 2748or_holds___2__0(G, A, J) :-
 2749	(   'chr newvia_1'(A, B)
 2750	->  get_attr(B, flux, C),
 2751	    C=v(_, D, _, _, _, _, _, _, _, _, _, _, _, _)
 2752	;   nb_getval('$chr_store_global_list_flux____not_holds___2', D)
 2753	),
 2754	member(E, D),
 2755	E=suspension(_, active, _, _, _, _, H, F),
 2756	F==A,
 2757	member(I, G, R),
 2758	H==I,
 2759	'chr debug_event'(try([J],
 2760			      [E],
 2761			      (member(K, G, L), H==K),
 2762			      or_holds(L, A))), !,
 2763	'chr debug_event'(apply([J],
 2764				[E],
 2765				(member(K, G, L), H==K),
 2766				or_holds(L, A))),
 2767	'chr debug_event'(remove(J)),
 2768	J=suspension(_, _, _, _, _, or_holds, M, N),
 2769	setarg(2, J, removed),
 2770	term_variables(term(M, N), Q),
 2771	nb_getval('$chr_store_global_list_flux____or_holds___2', O),
 2772	'chr sbag_del_element'(O, J, P),
 2773	b_setval('$chr_store_global_list_flux____or_holds___2', P),
 2774	detach_or_holds___2(Q, J),
 2775	or_holds(R, A).
 2776or_holds___2__0(G, A, J) :-
 2777	(   'chr newvia_1'(A, B)
 2778	->  get_attr(B, flux, C),
 2779	    C=v(_, _, _, _, _, _, _, _, _, _, _, _, D, _)
 2780	;   nb_getval('$chr_store_global_list_flux____cancel___2', D)
 2781	),
 2782	member(E, D),
 2783	E=suspension(_, active, _, _, _, _, H, F),
 2784	F==A,
 2785	member(I, G),
 2786	\+ H\=I,
 2787	'chr debug_event'(try([J],
 2788			      [E],
 2789			      (member(K, G), \+H\=K),
 2790			      true)), !,
 2791	'chr debug_event'(apply([J],
 2792				[E],
 2793				(member(K, G), \+H\=K),
 2794				true)),
 2795	'chr debug_event'(remove(J)),
 2796	J=suspension(_, _, _, _, _, or_holds, L, M),
 2797	setarg(2, J, removed),
 2798	term_variables(term(L, M), P),
 2799	nb_getval('$chr_store_global_list_flux____or_holds___2', N),
 2800	'chr sbag_del_element'(N, J, O),
 2801	b_setval('$chr_store_global_list_flux____or_holds___2', O),
 2802	detach_or_holds___2(P, J).
 2803or_holds___2__0(_, _, A) :-
 2804	setarg(2, A, active).
 2805
 2806detach_not_holds_all___2([], _).
 2807detach_not_holds_all___2([A|T], E) :-
 2808	(   get_attr(A, flux, B)
 2809	->  B=v(C, H, D, I, J, K, L, M, N, O, P, Q, R, S),
 2810	    (   C/\2=:=2
 2811	    ->  'chr sbag_del_element'(D, E, F),
 2812		(   F==[]
 2813		->  G is C/\ -3,
 2814		    (   G==0
 2815		    ->  del_attr(A, flux)
 2816		    ;   put_attr(A,
 2817				 flux,
 2818				 v(G,
 2819				   H,
 2820				   [],
 2821				   I,
 2822				   J,
 2823				   K,
 2824				   L,
 2825				   M,
 2826				   N,
 2827				   O,
 2828				   P,
 2829				   Q,
 2830				   R,
 2831				   S))
 2832		    )
 2833		;   put_attr(A,
 2834			     flux,
 2835			     v(C,
 2836			       H,
 2837			       F,
 2838			       I,
 2839			       J,
 2840			       K,
 2841			       L,
 2842			       M,
 2843			       N,
 2844			       O,
 2845			       P,
 2846			       Q,
 2847			       R,
 2848			       S))
 2849		)
 2850	    ;   true
 2851	    )
 2852	;   true
 2853	),
 2854	detach_not_holds_all___2(T, E).
 2855
 2856all_not_holds___3__0(I, J, A, O) :-
 2857	(   'chr newvia_1'(A, B)
 2858	->  get_attr(B, flux, C),
 2859	    C=v(_, _, _, _, _, _, _, D, _, _, _, _, _, _)
 2860	;   nb_getval('$chr_store_global_list_flux____all_holds___3', D)
 2861	),
 2862	member(E, D),
 2863	E=suspension(_, active, _, _, _, _, G, H, F),
 2864	F==A,
 2865	copy_fluent(G, H, K, M),
 2866	copy_fluent(I, J, L, N),
 2867	K=L,
 2868	call(M#/\N),
 2869	'chr debug_event'(try([E, O],
 2870			      [],
 2871			      (copy_fluent(G, H, P, R), copy_fluent(I, J, Q, S), P=Q, call(R#/\S)),
 2872			      false)), !,
 2873	'chr debug_event'(apply([E, O],
 2874				[],
 2875				(copy_fluent(G, H, P, R), copy_fluent(I, J, Q, S), P=Q, call(R#/\S)),
 2876				false)),
 2877	'chr debug_event'(remove(E)),
 2878	E=suspension(_, _, _, _, _, all_holds, T, U, V),
 2879	setarg(2, E, removed),
 2880	term_variables(term(T, U, V), Y),
 2881	nb_getval('$chr_store_global_list_flux____all_holds___3', W),
 2882	'chr sbag_del_element'(W, E, X),
 2883	b_setval('$chr_store_global_list_flux____all_holds___3', X),
 2884	detach_all_holds___3(Y, E),
 2885	'chr debug_event'(remove(O)),
 2886	O=suspension(_, _, _, _, _, all_not_holds, Z, A1, B1),
 2887	setarg(2, O, removed),
 2888	term_variables(term(Z, A1, B1), E1),
 2889	nb_getval('$chr_store_global_list_flux____all_not_holds___3', C1),
 2890	'chr sbag_del_element'(C1, O, D1),
 2891	b_setval('$chr_store_global_list_flux____all_not_holds___3', D1),
 2892	detach_all_not_holds___3(E1, O),
 2893	false.
 2894all_not_holds___3__0(_, _, A, B) :-
 2895	A==[],
 2896	'chr debug_event'(try([B], [], true, true)), !,
 2897	'chr debug_event'(apply([B], [], true, true)),
 2898	'chr debug_event'(remove(B)),
 2899	B=suspension(_, _, _, _, _, all_not_holds, C, D, E),
 2900	setarg(2, B, removed),
 2901	term_variables(term(C, D, E), H),
 2902	nb_getval('$chr_store_global_list_flux____all_not_holds___3', F),
 2903	'chr sbag_del_element'(F, B, G),
 2904	b_setval('$chr_store_global_list_flux____all_not_holds___3', G),
 2905	detach_all_not_holds___3(H, B).
 2906all_not_holds___3__0(E, F, A, G) :-
 2907	(   'chr newvia_1'(A, B)
 2908	->  get_attr(B, flux, C),
 2909	    C=v(_, D, _, _, _, _, _, _, _, _, _, _, _, _)
 2910	;   nb_getval('$chr_store_global_list_flux____not_holds___2', D)
 2911	), !,
 2912	all_not_holds___3__0__0__3(D, E, F, A, G).
 2913all_not_holds___3__0(A, B, C, D) :-
 2914	all_not_holds___3__1(A, B, C, D).
 2915
 2916all_not_holds___3__1__0__4([], A, B, C, D) :-
 2917	all_not_holds___3__2(A, B, C, D).
 2918all_not_holds___3__1__0__4([A|V], E, F, C, J) :-
 2919	(   A=suspension(_, active, _, _, _, _, D, B),
 2920	    B==C,
 2921	    member(H, D, U),
 2922	    copy_fluent(E, F, G, I),
 2923	    G=H,
 2924	    \+ call(#\+(I)),
 2925	    'chr debug_event'(try([A],
 2926				  [J],
 2927				  (member(L, O, N), copy_fluent(E, F, K, M), K=L, \+call(#\+(M))),
 2928				  or_holds(N, C)))
 2929	->  'chr debug_event'(apply([A],
 2930				    [J],
 2931				    (member(L, O, N), copy_fluent(E, F, K, M), K=L, \+call(#\+(M))),
 2932				    or_holds(N, C))),
 2933	    'chr debug_event'(remove(A)),
 2934	    A=suspension(_, _, _, _, _, or_holds, P, Q),
 2935	    setarg(2, A, removed),
 2936	    term_variables(term(P, Q), T),
 2937	    nb_getval('$chr_store_global_list_flux____or_holds___2', R),
 2938	    'chr sbag_del_element'(R, A, S),
 2939	    b_setval('$chr_store_global_list_flux____or_holds___2', S),
 2940	    detach_or_holds___2(T, A),
 2941	    setarg(2, J, active),
 2942	    or_holds(U, C),
 2943	    (   J=suspension(_, active, _, _, _, _, _, _, _)
 2944	    ->  setarg(2, J, inactive),
 2945		all_not_holds___3__1__0__4(V,
 2946					   E,
 2947					   F,
 2948					   C,
 2949					   J)
 2950	    ;   true
 2951	    )
 2952	;   all_not_holds___3__1__0__4(V,
 2953				       E,
 2954				       F,
 2955				       C,
 2956				       J)
 2957	).
 2958
 2959or_holds(A, B, C) :-
 2960	D=suspension(F, active, _, 0, flux:or_holds___3__0(A, B, C, D), or_holds, A, B, C),
 2961	term_variables(A, H, E),
 2962	term_variables(C, E),
 2963	'chr gen_id'(F),
 2964	nb_getval('$chr_store_global_list_flux____or_holds___3', G),
 2965	b_setval('$chr_store_global_list_flux____or_holds___3',
 2966		 [D|G]),
 2967	attach_or_holds___3(H, D),
 2968	setarg(2, D, inactive),
 2969	'chr debug_event'(insert(or_holds(A, B, C)#D)),
 2970	(   'chr debugging'
 2971	->  (   'chr debug_event'(call(D)),
 2972		or_holds___3__0(A, B, C, D)
 2973	    ;   'chr debug_event'(fail(D)), !,
 2974		fail
 2975	    ),
 2976	    (   'chr debug_event'(exit(D))
 2977	    ;   'chr debug_event'(redo(D)),
 2978		fail
 2979	    )
 2980	;   or_holds___3__0(A, B, C, D)
 2981	).
 2982
 2983all_holds___3__3(E, F, A, G) :-
 2984	(   'chr newvia_1'(A, B)
 2985	->  get_attr(B, flux, C),
 2986	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
 2987	;   nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 2988		      D)
 2989	), !,
 2990	all_holds___3__3__0__6(D, E, F, A, G).
 2991all_holds___3__3(A, B, C, D) :-
 2992	all_holds___3__4(A, B, C, D).
 2993
 2994or_neq(_, [], [], 0#\=0).
 2995or_neq(A, [D|B], [F|C], E) :-
 2996	or_neq(A, B, C, H),
 2997	(   A=forall,
 2998	    var(D),
 2999	    \+ is_domain(D)
 3000	->  (   binding(D, B, C, G)
 3001	    ->  E=(F#\=G#\/H)
 3002	    ;   E=H
 3003	    )
 3004	;   E=(D#\=F#\/H)
 3005	).
 3006
 3007and_eq([], [], 0#=0).
 3008and_eq([D|A], [E|B], C) :-
 3009	and_eq(A, B, F),
 3010	C=(D#=E#/\F).
 3011
 3012copy_fluent(A, D, E, F) :-
 3013	term_variables(A, B),
 3014	bound_free(B, [], _, C),
 3015	copy_term_vars(C, [A, D], [E, F]).
 3016
 3017all_not_holds___3__0__0__3([], A, B, C, D) :-
 3018	all_not_holds___3__1(A, B, C, D).
 3019all_not_holds___3__0__0__3([A|R], D, E, C, I) :-
 3020	(   A=suspension(_, active, _, _, _, _, G, B),
 3021	    B==C,
 3022	    copy_fluent(D, E, F, H),
 3023	    F=G,
 3024	    \+ call(#\+(H)),
 3025	    'chr debug_event'(try([A],
 3026				  [I],
 3027				  (copy_fluent(D, E, J, K), J=L, \+call(#\+(K))),
 3028				  true))
 3029	->  'chr debug_event'(apply([A],
 3030				    [I],
 3031				    (copy_fluent(D, E, J, K), J=L, \+call(#\+(K))),
 3032				    true)),
 3033	    'chr debug_event'(remove(A)),
 3034	    A=suspension(_, _, _, _, _, not_holds, M, N),
 3035	    setarg(2, A, removed),
 3036	    term_variables(term(M, N), Q),
 3037	    nb_getval('$chr_store_global_list_flux____not_holds___2', O),
 3038	    'chr sbag_del_element'(O, A, P),
 3039	    b_setval('$chr_store_global_list_flux____not_holds___2', P),
 3040	    detach_not_holds___2(Q, A),
 3041	    setarg(2, I, active),
 3042	    (   I=suspension(_, active, _, _, _, _, _, _, _)
 3043	    ->  setarg(2, I, inactive),
 3044		all_not_holds___3__0__0__3(R,
 3045					   D,
 3046					   E,
 3047					   C,
 3048					   I)
 3049	    ;   true
 3050	    )
 3051	;   all_not_holds___3__0__0__3(R,
 3052				       D,
 3053				       E,
 3054				       C,
 3055				       I)
 3056	).
 3057
 3058attach_if_then_holds___3([], _).
 3059attach_if_then_holds___3([A|T], L) :-
 3060	(   get_attr(A, flux, B)
 3061	->  B=v(C, D, E, F, G, H, I, J, K, M, N, O, P, Q),
 3062	    (   C/\256=:=256
 3063	    ->  R=v(C, D, E, F, G, H, I, J, K, [L|M], N, O, P, Q)
 3064	    ;   S is C\/256,
 3065		R=v(S, D, E, F, G, H, I, J, K, [L], N, O, P, Q)
 3066	    ),
 3067	    put_attr(A, flux, R)
 3068	;   put_attr(A,
 3069		     flux,
 3070		     v(256, [], [], [], [], [], [], [], [], [L], [], [], [], []))
 3071	),
 3072	attach_if_then_holds___3(T, L).
 3073
 3074detach_duplicate_free___1([], _).
 3075detach_duplicate_free___1([A|T], E) :-
 3076	(   get_attr(A, flux, B)
 3077	->  B=v(C, H, I, D, J, K, L, M, N, O, P, Q, R, S),
 3078	    (   C/\4=:=4
 3079	    ->  'chr sbag_del_element'(D, E, F),
 3080		(   F==[]
 3081		->  G is C/\ -5,
 3082		    (   G==0
 3083		    ->  del_attr(A, flux)
 3084		    ;   put_attr(A,
 3085				 flux,
 3086				 v(G,
 3087				   H,
 3088				   I,
 3089				   [],
 3090				   J,
 3091				   K,
 3092				   L,
 3093				   M,
 3094				   N,
 3095				   O,
 3096				   P,
 3097				   Q,
 3098				   R,
 3099				   S))
 3100		    )
 3101		;   put_attr(A,
 3102			     flux,
 3103			     v(C,
 3104			       H,
 3105			       I,
 3106			       F,
 3107			       J,
 3108			       K,
 3109			       L,
 3110			       M,
 3111			       N,
 3112			       O,
 3113			       P,
 3114			       Q,
 3115			       R,
 3116			       S))
 3117		)
 3118	    ;   true
 3119	    )
 3120	;   true
 3121	),
 3122	detach_duplicate_free___1(T, E).
 3123
 3124or_and_eq([], 0#\=0).
 3125or_and_eq([A|E], D#\/F) :-
 3126	(   A=eq(B, C)
 3127	->  and_eq(B, C, D)
 3128	;   A=neq(B, C),
 3129	    or_neq(exists, B, C, D)
 3130	),
 3131	or_and_eq(E, F).
 3132
 3133eq(A, B, I) :-
 3134	functor(A, C, E),
 3135	functor(B, D, F),
 3136	(   C=D,
 3137	    E=F
 3138	->  A=..[_|G],
 3139	    B=..[_|H],
 3140	    and_eq(G, H, I)
 3141	;   I=(0#\=0)
 3142	).
 3143
 3144all_not_holds___3__1(E, F, A, G) :-
 3145	(   'chr newvia_1'(A, B)
 3146	->  get_attr(B, flux, C),
 3147	    C=v(_, _, _, _, D, _, _, _, _, _, _, _, _, _)
 3148	;   nb_getval('$chr_store_global_list_flux____or_holds___2', D)
 3149	), !,
 3150	all_not_holds___3__1__0__4(D, E, F, A, G).
 3151all_not_holds___3__1(A, B, C, D) :-
 3152	all_not_holds___3__2(A, B, C, D).
 3153
 3154member(A, [A|B], B).
 3155member(B, [A|C], [A|D]) :-
 3156	member(B, C, D).
 3157
 3158not_holds___2__2__0__6([], A, B, C) :-
 3159	not_holds___2__3(A, B, C).
 3160not_holds___2__2__0__6([A|N], D, C, F) :-
 3161	(   A=suspension(_, active, _, _, _, _, E, _, B),
 3162	    B==C,
 3163	    D==E,
 3164	    'chr debug_event'(try([A], [F], D==G, true))
 3165	->  'chr debug_event'(apply([A], [F], D==G, true)),
 3166	    'chr debug_event'(remove(A)),
 3167	    A=suspension(_, _, _, _, _, if_then_or_holds, H, I, J),
 3168	    setarg(2, A, removed),
 3169	    term_variables(term(H, I, J), M),
 3170	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 3171		      K),
 3172	    'chr sbag_del_element'(K, A, L),
 3173	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
 3174		     L),
 3175	    detach_if_then_or_holds___3(M, A),
 3176	    setarg(2, F, active),
 3177	    (   F=suspension(_, active, _, _, _, _, _, _)
 3178	    ->  setarg(2, F, inactive),
 3179		not_holds___2__2__0__6(N, D, C, F)
 3180	    ;   true
 3181	    )
 3182	;   not_holds___2__2__0__6(N, D, C, F)
 3183	).
 3184
 3185duplicate_free___1__0(A, B) :-
 3186	nonvar(A),
 3187	A=[C|D],
 3188	'chr debug_event'(try([B],
 3189			      [],
 3190			      true,
 3191			      (not_holds(C, D), duplicate_free(D)))), !,
 3192	'chr debug_event'(apply([B],
 3193				[],
 3194				true,
 3195				(not_holds(C, D), duplicate_free(D)))),
 3196	'chr debug_event'(remove(B)),
 3197	B=suspension(_, _, _, _, _, duplicate_free, E),
 3198	setarg(2, B, removed),
 3199	term_variables(E, H),
 3200	nb_getval('$chr_store_global_list_flux____duplicate_free___1', F),
 3201	'chr sbag_del_element'(F, B, G),
 3202	b_setval('$chr_store_global_list_flux____duplicate_free___1', G),
 3203	detach_duplicate_free___1(H, B),
 3204	not_holds(C, D),
 3205	duplicate_free(D).
 3206duplicate_free___1__0(A, B) :-
 3207	A==[],
 3208	'chr debug_event'(try([B], [], true, true)), !,
 3209	'chr debug_event'(apply([B], [], true, true)),
 3210	'chr debug_event'(remove(B)),
 3211	B=suspension(_, _, _, _, _, duplicate_free, C),
 3212	setarg(2, B, removed),
 3213	term_variables(C, F),
 3214	nb_getval('$chr_store_global_list_flux____duplicate_free___1', D),
 3215	'chr sbag_del_element'(D, B, E),
 3216	b_setval('$chr_store_global_list_flux____duplicate_free___1', E),
 3217	detach_duplicate_free___1(F, B).
 3218duplicate_free___1__0(_, A) :-
 3219	setarg(2, A, active).
 3220
 3221not_holds___2__4(H, A, I) :-
 3222	(   'chr newvia_1'(A, B)
 3223	->  get_attr(B, flux, C),
 3224	    C=v(_, _, _, _, _, _, _, _, _, _, _, _, D, _)
 3225	;   nb_getval('$chr_store_global_list_flux____cancel___2', D)
 3226	),
 3227	member(E, D),
 3228	E=suspension(_, active, _, _, _, _, G, F),
 3229	F==A,
 3230	\+ G\=H,
 3231	'chr debug_event'(try([I], [E], \+G\=H, true)), !,
 3232	'chr debug_event'(apply([I], [E], \+G\=H, true)),
 3233	'chr debug_event'(remove(I)),
 3234	I=suspension(_, _, _, _, _, not_holds, J, K),
 3235	setarg(2, I, removed),
 3236	term_variables(term(J, K), N),
 3237	nb_getval('$chr_store_global_list_flux____not_holds___2', L),
 3238	'chr sbag_del_element'(L, I, M),
 3239	b_setval('$chr_store_global_list_flux____not_holds___2', M),
 3240	detach_not_holds___2(N, I).
 3241not_holds___2__4(_, _, A) :-
 3242	setarg(2, A, active).
 3243
 3244not_holds___2__3__0__7([], A, B, C) :-
 3245	not_holds___2__4(A, B, C).
 3246not_holds___2__3__0__7([A|T], E, C, G) :-
 3247	(   A=suspension(_, active, _, _, _, _, R, D, B),
 3248	    B==C,
 3249	    member(F, D, S),
 3250	    E==F,
 3251	    'chr debug_event'(try([A],
 3252				  [G],
 3253				  (member(H, J, I), E==H),
 3254				  if_then_or_holds(K, I, C)))
 3255	->  'chr debug_event'(apply([A],
 3256				    [G],
 3257				    (member(H, J, I), E==H),
 3258				    if_then_or_holds(K, I, C))),
 3259	    'chr debug_event'(remove(A)),
 3260	    A=suspension(_, _, _, _, _, if_then_or_holds, L, M, N),
 3261	    setarg(2, A, removed),
 3262	    term_variables(term(L, M, N), Q),
 3263	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 3264		      O),
 3265	    'chr sbag_del_element'(O, A, P),
 3266	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
 3267		     P),
 3268	    detach_if_then_or_holds___3(Q, A),
 3269	    setarg(2, G, active),
 3270	    if_then_or_holds(R, S, C),
 3271	    (   G=suspension(_, active, _, _, _, _, _, _)
 3272	    ->  setarg(2, G, inactive),
 3273		not_holds___2__3__0__7(T, E, C, G)
 3274	    ;   true
 3275	    )
 3276	;   not_holds___2__3__0__7(T, E, C, G)
 3277	).
 3278
 3279attach_duplicate_free___1([], _).
 3280attach_duplicate_free___1([A|T], F) :-
 3281	(   get_attr(A, flux, B)
 3282	->  B=v(C, D, E, G, H, I, J, K, L, M, N, O, P, Q),
 3283	    (   C/\4=:=4
 3284	    ->  R=v(C, D, E, [F|G], H, I, J, K, L, M, N, O, P, Q)
 3285	    ;   S is C\/4,
 3286		R=v(S, D, E, [F], H, I, J, K, L, M, N, O, P, Q)
 3287	    ),
 3288	    put_attr(A, flux, R)
 3289	;   put_attr(A,
 3290		     flux,
 3291		     v(4, [], [], [F], [], [], [], [], [], [], [], [], [], []))
 3292	),
 3293	attach_duplicate_free___1(T, F).
 3294
 3295neq_all(A, B, C) :-
 3296	or_neq_c(forall, A, B, C).
 3297
 3298not_holds_all___2__0(B, C, A) :-
 3299	'chr debug_event'(try([A],
 3300			      [],
 3301			      true,
 3302			      all_not_holds(B, 0#=0, C))), !,
 3303	'chr debug_event'(apply([A],
 3304				[],
 3305				true,
 3306				all_not_holds(B, 0#=0, C))),
 3307	'chr debug_event'(remove(A)),
 3308	A=suspension(_, _, _, _, _, not_holds_all, D, E),
 3309	setarg(2, A, removed),
 3310	term_variables(term(D, E), H),
 3311	nb_getval('$chr_store_global_list_flux____not_holds_all___2', F),
 3312	'chr sbag_del_element'(F, A, G),
 3313	b_setval('$chr_store_global_list_flux____not_holds_all___2', G),
 3314	detach_not_holds_all___2(H, A),
 3315	all_not_holds(B, 0#=0, C).
 3316not_holds_all___2__0(H, A, I) :-
 3317	(   'chr newvia_1'(A, B)
 3318	->  get_attr(B, flux, C),
 3319	    C=v(_, _, _, _, _, _, _, _, _, _, _, _, D, _)
 3320	;   nb_getval('$chr_store_global_list_flux____cancel___2', D)
 3321	),
 3322	member(E, D),
 3323	E=suspension(_, active, _, _, _, _, G, F),
 3324	F==A,
 3325	\+ G\=H,
 3326	'chr debug_event'(try([I], [E], \+G\=H, true)), !,
 3327	'chr debug_event'(apply([I], [E], \+G\=H, true)),
 3328	'chr debug_event'(remove(I)),
 3329	I=suspension(_, _, _, _, _, not_holds_all, J, K),
 3330	setarg(2, I, removed),
 3331	term_variables(term(J, K), N),
 3332	nb_getval('$chr_store_global_list_flux____not_holds_all___2', L),
 3333	'chr sbag_del_element'(L, I, M),
 3334	b_setval('$chr_store_global_list_flux____not_holds_all___2', M),
 3335	detach_not_holds_all___2(N, I).
 3336not_holds_all___2__0(_, _, A) :-
 3337	setarg(2, A, active).
 3338
 3339all_holds___3__3__0__6([], A, B, C, D) :-
 3340	all_holds___3__4(A, B, C, D).
 3341all_holds___3__3__0__6([A|U], E, F, C, J) :-
 3342	(   A=suspension(_, active, _, _, _, _, _, D, B),
 3343	    B==C,
 3344	    member(H, D),
 3345	    copy_fluent(E, F, G, I),
 3346	    G=H,
 3347	    \+ call(#\+(I)),
 3348	    'chr debug_event'(try([A],
 3349				  [J],
 3350				  (member(L, N), copy_fluent(E, F, K, M), K=L, \+call(#\+(M))),
 3351				  true))
 3352	->  'chr debug_event'(apply([A],
 3353				    [J],
 3354				    (member(L, N), copy_fluent(E, F, K, M), K=L, \+call(#\+(M))),
 3355				    true)),
 3356	    'chr debug_event'(remove(A)),
 3357	    A=suspension(_, _, _, _, _, if_then_or_holds, O, P, Q),
 3358	    setarg(2, A, removed),
 3359	    term_variables(term(O, P, Q), T),
 3360	    nb_getval('$chr_store_global_list_flux____if_then_or_holds___3',
 3361		      R),
 3362	    'chr sbag_del_element'(R, A, S),
 3363	    b_setval('$chr_store_global_list_flux____if_then_or_holds___3',
 3364		     S),
 3365	    detach_if_then_or_holds___3(T, A),
 3366	    setarg(2, J, active),
 3367	    (   J=suspension(_, active, _, _, _, _, _, _, _)
 3368	    ->  setarg(2, J, inactive),
 3369		all_holds___3__3__0__6(U,
 3370				       E,
 3371				       F,
 3372				       C,
 3373				       J)
 3374	    ;   true
 3375	    )
 3376	;   all_holds___3__3__0__6(U, E, F, C, J)
 3377	)