2:-[flux2].    3
    4
    5not_holds___2__3__0__7([], A, B, C) :-
    6	not_holds___2__4(A, B, C).
    7not_holds___2__3__0__7([A|T], E, C, G) :-
    8	(   A=suspension(_, active, _, _, _, _, R, D, B),
    9	    B==C,
   10	    member(F, D, S),
   11	    E==F,
   12	    'chr debug_event'(try([A],
   13				  [G],
   14				  (member(H, J, I), E==H),
   15				  if_then_or_holds(K, I, C)))
   16	->  'chr debug_event'(apply([A],
   17				    [G],
   18				    (member(H, J, I), E==H),
   19				    if_then_or_holds(K, I, C))),
   20	    'chr debug_event'(remove(A)),
   21	    A=suspension(_, _, _, _, _, if_then_or_holds, L, M, N),
   22	    setarg(2, A, removed),
   23	    term_variables(term(L, M, N), Q),
   24	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
   25		      O),
   26	    'chr sbag_del_element'(O, A, P),
   27	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
   28		     P),
   29	    detach_if_then_or_holds___3(Q, A),
   30	    setarg(2, G, active),
   31	    if_then_or_holds(R, S, C),
   32	    (   G=suspension(_, active, _, _, _, _, _, _)
   33	    ->  setarg(2, G, inactive),
   34		not_holds___2__3__0__7(T, E, C, G)
   35	    ;   true
   36	    )
   37	;   not_holds___2__3__0__7(T, E, C, G)
   38	).
   39
   40:- dynamic library_directory/1.   41:- multifile library_directory/1.   42
   43library_directory(B) :-
   44    '$parms':
   45    (   cached_library_directory(local, A=lib, A),
   46	B=A
   47    ).
   48library_directory(B) :-
   49    '$parms':
   50    (   cached_library_directory(user,
   51				 expand_file_name('~/lib/prolog', [A]),
   52				 A),
   53	B=A
   54    ).
   55library_directory(B) :-
   56    '$parms':
   57    (   cached_library_directory(system,
   58				 absolute_file_name(swi(library), A),
   59				 A),
   60	B=A
   61    ).
   62library_directory(B) :-
   63    '$parms':
   64    (   cached_library_directory(clp,
   65				 absolute_file_name(swi('library/clp'), A),
   66				 A),
   67	B=A
   68    ).
   69
   70all_not_holds___3__2(E, F, A, G) :-
   71	(   'chr newvia_1'(A, B)
   72	->  get_attr(B, user, C),
   73	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
   74	;   nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
   75		      D)
   76	), !,
   77	all_not_holds___3__2__0__5(D, E, F, A, G).
   78all_not_holds___3__2(A, B, C, D) :-
   79	all_not_holds___3__3(A, B, C, D).
   80
   81:- dynamic portray/1.   82:- multifile portray/1.   83
   84
   85all_not_holds___3__3__0__6([], A, B, C, D) :-
   86	all_not_holds___3__4(A, B, C, D).
   87all_not_holds___3__3__0__6([A|Y], E, F, C, J) :-
   88	(   A=suspension(_, active, _, _, _, _, W, D, B),
   89	    B==C,
   90	    member(H, D, X),
   91	    copy_fluent(E, F, G, I),
   92	    G=H,
   93	    \+ call(#\+I),
   94	    'chr debug_event'(try([A],
   95				  [J],
   96				  (member(L, O, N), copy_fluent(E, F, K, M), K=L, \+call(#\+M)),
   97				  if_then_or_holds(P, N, C)))
   98	->  'chr debug_event'(apply([A],
   99				    [J],
  100				    (member(L, O, N), copy_fluent(E, F, K, M), K=L, \+call(#\+M)),
  101				    if_then_or_holds(P,
  102						     N,
  103						     C))),
  104	    'chr debug_event'(remove(A)),
  105	    A=suspension(_, _, _, _, _, if_then_or_holds, Q, R, S),
  106	    setarg(2, A, removed),
  107	    term_variables(term(Q, R, S), V),
  108	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
  109		      T),
  110	    'chr sbag_del_element'(T, A, U),
  111	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
  112		     U),
  113	    detach_if_then_or_holds___3(V, A),
  114	    setarg(2, J, active),
  115	    if_then_or_holds(W, X, C),
  116	    (   J=suspension(_, active, _, _, _, _, _, _, _)
  117	    ->  setarg(2, J, inactive),
  118		all_not_holds___3__3__0__6(Y,
  119					   E,
  120					   F,
  121					   C,
  122					   J)
  123	    ;   true
  124	    )
  125	;   all_not_holds___3__3__0__6(Y,
  126				       E,
  127				       F,
  128				       C,
  129				       J)
  130	).
  131
  132not_holds___2__0__0__3([], A, B, C) :-
  133	not_holds___2__1(A, B, C).
  134not_holds___2__0__0__3([A|M], I, C, D) :-
  135	(   A=suspension(_, active, _, _, _, _, F, G, B),
  136	    B==C,
  137	    E=t(7, A, D),
  138	    '$novel_production'(A, E),
  139	    '$novel_production'(D, E),
  140	    copy_fluent(F, G, K, L),
  141	    'chr debug_event'(try([],
  142				  [A, D],
  143				  copy_fluent(F, G, H, J),
  144				  (H=I, call(#\+J))))
  145	->  'chr debug_event'(apply([],
  146				    [A, D],
  147				    copy_fluent(F,
  148						G,
  149						H,
  150						J),
  151				    (H=I, call(#\+J)))),
  152	    '$extend_history'(D, E),
  153	    setarg(2, D, active),
  154	    K=I,
  155	    call(#\+L),
  156	    (   D=suspension(_, active, _, _, _, _, _, _)
  157	    ->  setarg(2, D, inactive),
  158		not_holds___2__0__0__3(M, I, C, D)
  159	    ;   true
  160	    )
  161	;   not_holds___2__0__0__3(M, I, C, D)
  162	).
  163
  164all_not_holds(A, B, C) :-
  165	D=suspension(E, active, _, 0, user:all_not_holds___3__0(A, B, C, D), all_not_holds, A, B, C),
  166	term_variables(term(A, B, C), G),
  167	'chr gen_id'(E),
  168	nb_getval('$chr_store_global_list_user____all_not_holds___3', F),
  169	b_setval('$chr_store_global_list_user____all_not_holds___3',
  170		 [D|F]),
  171	attach_all_not_holds___3(G, D),
  172	setarg(2, D, inactive),
  173	'chr debug_event'(insert(all_not_holds(A, B, C)#D)),
  174	(   'chr debug_event'(call(D)),
  175	    all_not_holds___3__0(A, B, C, D)
  176	;   'chr debug_event'(fail(D)), !,
  177	    fail
  178	),
  179	(   'chr debug_event'(exit(D))
  180	;   'chr debug_event'(redo(D)),
  181	    fail
  182	).
  183
  184all_holds___3__3(E, F, A, G) :-
  185	(   'chr newvia_1'(A, B)
  186	->  get_attr(B, user, C),
  187	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
  188	;   nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
  189		      D)
  190	), !,
  191	all_holds___3__3__0__6(D, E, F, A, G).
  192all_holds___3__3(A, B, C, D) :-
  193	all_holds___3__4(A, B, C, D).
  194
  195turn_to(A, B, C) :-
  196	(   knows(facing(A), B)
  197	->  C=B
  198	;   execute(turn, B, D),
  199	    turn_to(A, D, C)
  200	).
  201
  202detach_cancelled___2([], _).
  203detach_cancelled___2([A|T], E) :-
  204	(   get_attr(A, user, B)
  205	->  B=v(C, H, I, J, K, L, M, N, O, P, Q, R, S, D),
  206	    (   C/\4096=:=4096
  207	    ->  'chr sbag_del_element'(D, E, F),
  208		(   F==[]
  209		->  G is C/\ -4097,
  210		    (   G==0
  211		    ->  del_attr(A, user)
  212		    ;   put_attr(A,
  213				 user,
  214				 v(G,
  215				   H,
  216				   I,
  217				   J,
  218				   K,
  219				   L,
  220				   M,
  221				   N,
  222				   O,
  223				   P,
  224				   Q,
  225				   R,
  226				   S,
  227				   []))
  228		    )
  229		;   put_attr(A,
  230			     user,
  231			     v(C,
  232			       H,
  233			       I,
  234			       J,
  235			       K,
  236			       L,
  237			       M,
  238			       N,
  239			       O,
  240			       P,
  241			       Q,
  242			       R,
  243			       S,
  244			       F))
  245		)
  246	    ;   true
  247	    )
  248	;   true
  249	),
  250	detach_cancelled___2(T, E).
  251
  252all_holds(A, B) :-
  253	C=suspension(D, active, _, 0, user:all_holds___2__0(A, B, C), all_holds, A, B),
  254	'chr gen_id'(D),
  255	nb_getval('$chr_store_global_list_user____all_holds___2', E),
  256	b_setval('$chr_store_global_list_user____all_holds___2',
  257		 [C|E]),
  258	attach_all_holds___2([], C),
  259	setarg(2, C, inactive),
  260	'chr debug_event'(insert(all_holds(A, B)#C)),
  261	(   'chr debug_event'(call(C)),
  262	    all_holds___2__0(A, B, C)
  263	;   'chr debug_event'(fail(C)), !,
  264	    fail
  265	),
  266	(   'chr debug_event'(exit(C))
  267	;   'chr debug_event'(redo(C)),
  268	    fail
  269	).
  270
  271main :-
  272	init_simulator,
  273	init(A),
  274	execute(enter, A, E),
  275	B=[1, 1, [1, 2]],
  276	C=[[1, 1]],
  277	D=[],
  278	main_loop(B, C, D, E).
  279
  280cancel___2__3(E, A, F) :-
  281	(   'chr newvia_1'(A, B)
  282	->  get_attr(B, user, C),
  283	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
  284	;   nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
  285		      D)
  286	), !,
  287	cancel___2__3__0__4(D, E, A, F).
  288cancel___2__3(A, B, C) :-
  289	cancel___2__4(A, B, C).
  290
  291all_holds___3__0(C, E, A, B) :-
  292	nonvar(A),
  293	A=[D|F],
  294	'chr debug_event'(try([B],
  295			      [],
  296			      true,
  297			      (\+ (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)))), !,
  298	'chr debug_event'(apply([B],
  299				[],
  300				true,
  301				(\+ (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)))),
  302	'chr debug_event'(remove(B)),
  303	B=suspension(_, _, _, _, _, all_holds, L, M, N),
  304	setarg(2, B, removed),
  305	term_variables(term(L, M, N), Q),
  306	nb_getval('$chr_store_global_list_user____all_holds___3', O),
  307	'chr sbag_del_element'(O, B, P),
  308	b_setval('$chr_store_global_list_user____all_holds___3', P),
  309	detach_all_holds___3(Q, B),
  310	(   \+ ( C=D,
  311		 call(E)
  312	       )
  313	->  all_holds(C, E, F)
  314	;   C=..[_|R],
  315	    D=..[_|S],
  316	    or_neq(exists, R, S, T),
  317	    all_holds(C, E#/\T, F)
  318	).
  319all_holds___3__0(E, F, A, G) :-
  320	(   'chr newvia_1'(A, B)
  321	->  get_attr(B, user, C),
  322	    C=v(_, D, _, _, _, _, _, _, _, _, _, _, _, _)
  323	;   nb_getval('$chr_store_global_list_user____not_holds___2', D)
  324	), !,
  325	all_holds___3__0__0__2(D, E, F, A, G).
  326all_holds___3__0(A, B, C, D) :-
  327	all_holds___3__1(A, B, C, D).
  328
  329binding(A, [B|E], [D|F], C) :-
  330	(   A==B
  331	->  C=D
  332	;   binding(A, E, F, C)
  333	).
  334
  335:- dynamic resource/3.  336:- multifile resource/3.  337
  338
  339or_neq(G, A, B) :-
  340	functor(A, C, E),
  341	functor(B, D, F),
  342	(   C=D,
  343	    E=F
  344	->  A=..[_|H],
  345	    B=..[_|I],
  346	    or_neq(G, H, I, J),
  347	    call(J)
  348	;   true
  349	).
  350
  351if_then_or_holds___3__0(J, O, A, L) :-
  352	(   'chr newvia_1'(A, B)
  353	->  get_attr(B, user, C),
  354	    C=v(_, _, _, _, _, _, _, D, _, _, _, _, _, _)
  355	;   nb_getval('$chr_store_global_list_user____all_holds___3', D)
  356	),
  357	'chr sbag_member'(E, D),
  358	E=suspension(_, active, _, _, _, _, G, H, F),
  359	F==A,
  360	(   copy_fluent(G, H, I, K),
  361	    I=J,
  362	    \+ call(#\+K),
  363	    'chr debug_event'(try([L],
  364				  [E],
  365				  (copy_fluent(G, H, M, N), M=J, \+call(#\+N)),
  366				  or_holds(O, A))), !,
  367	    'chr debug_event'(apply([L],
  368				    [E],
  369				    (copy_fluent(G, H, M, N), M=J, \+call(#\+N)),
  370				    or_holds(O, A))),
  371	    'chr debug_event'(remove(L)),
  372	    L=suspension(_, _, _, _, _, if_then_or_holds, P, Q, R),
  373	    setarg(2, L, removed),
  374	    term_variables(term(P, Q, R), U),
  375	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
  376		      S),
  377	    'chr sbag_del_element'(S, L, T),
  378	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
  379		     T),
  380	    detach_if_then_or_holds___3(U, L),
  381	    or_holds(O, A)
  382	;   member(W, O),
  383	    copy_fluent(G, H, V, X),
  384	    V=W,
  385	    \+ call(#\+X),
  386	    'chr debug_event'(try([L],
  387				  [E],
  388				  (member(Z, O), copy_fluent(G, H, Y, A1), Y=Z, \+call(#\+A1)),
  389				  true)), !,
  390	    'chr debug_event'(apply([L],
  391				    [E],
  392				    (member(Z, O), copy_fluent(G, H, Y, A1), Y=Z, \+call(#\+A1)),
  393				    true)),
  394	    'chr debug_event'(remove(L)),
  395	    L=suspension(_, _, _, _, _, if_then_or_holds, B1, C1, D1),
  396	    setarg(2, L, removed),
  397	    term_variables(term(B1, C1, D1), G1),
  398	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
  399		      E1),
  400	    'chr sbag_del_element'(E1, L, F1),
  401	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
  402		     F1),
  403	    detach_if_then_or_holds___3(G1, L)
  404	).
  405if_then_or_holds___3__0(J, U, A, L) :-
  406	(   'chr newvia_1'(A, B)
  407	->  get_attr(B, user, C),
  408	    C=v(_, _, _, _, _, _, _, _, D, _, _, _, _, _)
  409	;   nb_getval('$chr_store_global_list_user____all_not_holds___3',
  410		      D)
  411	),
  412	'chr sbag_member'(E, D),
  413	E=suspension(_, active, _, _, _, _, G, H, F),
  414	F==A,
  415	(   copy_fluent(G, H, I, K),
  416	    I=J,
  417	    \+ call(#\+K),
  418	    'chr debug_event'(try([L],
  419				  [E],
  420				  (copy_fluent(G, H, M, N), M=J, \+call(#\+N)),
  421				  true)), !,
  422	    'chr debug_event'(apply([L],
  423				    [E],
  424				    (copy_fluent(G, H, M, N), M=J, \+call(#\+N)),
  425				    true)),
  426	    'chr debug_event'(remove(L)),
  427	    L=suspension(_, _, _, _, _, if_then_or_holds, O, P, Q),
  428	    setarg(2, L, removed),
  429	    term_variables(term(O, P, Q), T),
  430	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
  431		      R),
  432	    'chr sbag_del_element'(R, L, S),
  433	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
  434		     S),
  435	    detach_if_then_or_holds___3(T, L)
  436	;   member(W, U, I1),
  437	    copy_fluent(G, H, V, X),
  438	    V=W,
  439	    \+ call(#\+X),
  440	    'chr debug_event'(try([L],
  441				  [E],
  442				  (member(Z, U, B1), copy_fluent(G, H, Y, A1), Y=Z, \+call(#\+A1)),
  443				  if_then_or_holds(J, B1, A))), !,
  444	    'chr debug_event'(apply([L],
  445				    [E],
  446				    (member(Z, U, B1), copy_fluent(G, H, Y, A1), Y=Z, \+call(#\+A1)),
  447				    if_then_or_holds(J, B1, A))),
  448	    'chr debug_event'(remove(L)),
  449	    L=suspension(_, _, _, _, _, if_then_or_holds, C1, D1, E1),
  450	    setarg(2, L, removed),
  451	    term_variables(term(C1, D1, E1), H1),
  452	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
  453		      F1),
  454	    'chr sbag_del_element'(F1, L, G1),
  455	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
  456		     G1),
  457	    detach_if_then_or_holds___3(H1, L),
  458	    if_then_or_holds(J, I1, A)
  459	).
  460if_then_or_holds___3__0(C, A, D, B) :-
  461	A==[],
  462	'chr debug_event'(try([B], [], true, not_holds(C, D))), !,
  463	'chr debug_event'(apply([B], [], true, not_holds(C, D))),
  464	'chr debug_event'(remove(B)),
  465	B=suspension(_, _, _, _, _, if_then_or_holds, E, F, G),
  466	setarg(2, B, removed),
  467	term_variables(term(E, F, G), J),
  468	nb_getval('$chr_store_global_list_user____if_then_or_holds___3', H),
  469	'chr sbag_del_element'(H, B, I),
  470	b_setval('$chr_store_global_list_user____if_then_or_holds___3', I),
  471	detach_if_then_or_holds___3(J, B),
  472	not_holds(C, D).
  473if_then_or_holds___3__0(_, _, A, B) :-
  474	A==[],
  475	'chr debug_event'(try([B], [], true, true)), !,
  476	'chr debug_event'(apply([B], [], true, true)),
  477	'chr debug_event'(remove(B)),
  478	B=suspension(_, _, _, _, _, if_then_or_holds, C, D, E),
  479	setarg(2, B, removed),
  480	term_variables(term(C, D, E), H),
  481	nb_getval('$chr_store_global_list_user____if_then_or_holds___3', F),
  482	'chr sbag_del_element'(F, B, G),
  483	b_setval('$chr_store_global_list_user____if_then_or_holds___3', G),
  484	detach_if_then_or_holds___3(H, B).
  485if_then_or_holds___3__0(_, A, _, E) :-
  486	member(eq(B, C), A),
  487	or_neq(exists, B, C, D),
  488	\+ call(D),
  489	'chr debug_event'(try([E],
  490			      [],
  491			      (member(eq(F, G), A), or_neq(exists, F, G, H), \+call(H)),
  492			      true)), !,
  493	'chr debug_event'(apply([E],
  494				[],
  495				(member(eq(F, G), A), or_neq(exists, F, G, H), \+call(H)),
  496				true)),
  497	'chr debug_event'(remove(E)),
  498	E=suspension(_, _, _, _, _, if_then_or_holds, I, J, K),
  499	setarg(2, E, removed),
  500	term_variables(term(I, J, K), N),
  501	nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
  502		  L),
  503	'chr sbag_del_element'(L, E, M),
  504	b_setval('$chr_store_global_list_user____if_then_or_holds___3', M),
  505	detach_if_then_or_holds___3(N, E).
  506if_then_or_holds___3__0(I, A, K, E) :-
  507	member(eq(B, C), A, R),
  508	\+ ( and_eq(B, C, D),
  509	     call(D)
  510	   ),
  511	'chr debug_event'(try([E],
  512			      [],
  513			      (member(eq(F, G), A, J), \+ (and_eq(F, G, H), call(H))),
  514			      if_then_or_holds(I, J, K))), !,
  515	'chr debug_event'(apply([E],
  516				[],
  517				(member(eq(F, G), A, J), \+ (and_eq(F, G, H), call(H))),
  518				if_then_or_holds(I, J, K))),
  519	'chr debug_event'(remove(E)),
  520	E=suspension(_, _, _, _, _, if_then_or_holds, L, M, N),
  521	setarg(2, E, removed),
  522	term_variables(term(L, M, N), Q),
  523	nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
  524		  O),
  525	'chr sbag_del_element'(O, E, P),
  526	b_setval('$chr_store_global_list_user____if_then_or_holds___3', P),
  527	detach_if_then_or_holds___3(Q, E),
  528	if_then_or_holds(I, R, K).
  529if_then_or_holds___3__0(C, E, A, B) :-
  530	nonvar(A),
  531	A=[D|F],
  532	'chr debug_event'(try([B],
  533			      [],
  534			      true,
  535			      (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])))), !,
  536	'chr debug_event'(apply([B],
  537				[],
  538				true,
  539				(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])))),
  540	'chr debug_event'(remove(B)),
  541	B=suspension(_, _, _, _, _, if_then_or_holds, K, L, M),
  542	setarg(2, B, removed),
  543	term_variables(term(K, L, M), P),
  544	nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
  545		  N),
  546	'chr sbag_del_element'(N, B, O),
  547	b_setval('$chr_store_global_list_user____if_then_or_holds___3', O),
  548	detach_if_then_or_holds___3(P, B),
  549	(   C==D
  550	->  or_holds(E, [D|F])
  551	;   C\=D
  552	->  if_then_or_holds(C, E, [], [D|F])
  553	;   C=..[_|Q],
  554	    D=..[_|R],
  555	    or_holds([neq(Q, R)|E], [D|F]),
  556	    if_then_or_holds(C, E, [], [D|F])
  557	).
  558if_then_or_holds___3__0(H, P, A, I) :-
  559	(   'chr newvia_1'(A, B)
  560	->  get_attr(B, user, C),
  561	    C=v(_, D, _, _, _, _, _, _, _, _, _, _, _, _)
  562	;   nb_getval('$chr_store_global_list_user____not_holds___2', D)
  563	),
  564	'chr sbag_member'(E, D),
  565	E=suspension(_, active, _, _, _, _, G, F),
  566	F==A,
  567	(   G==H,
  568	    'chr debug_event'(try([I], [E], G==H, true)), !,
  569	    'chr debug_event'(apply([I], [E], G==H, true)),
  570	    'chr debug_event'(remove(I)),
  571	    I=suspension(_, _, _, _, _, if_then_or_holds, J, K, L),
  572	    setarg(2, I, removed),
  573	    term_variables(term(J, K, L), O),
  574	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
  575		      M),
  576	    'chr sbag_del_element'(M, I, N),
  577	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
  578		     N),
  579	    detach_if_then_or_holds___3(O, I)
  580	;   member(Q, P, Z),
  581	    G==Q,
  582	    'chr debug_event'(try([I],
  583				  [E],
  584				  (member(R, P, S), G==R),
  585				  if_then_or_holds(H, S, A))), !,
  586	    'chr debug_event'(apply([I],
  587				    [E],
  588				    (member(R, P, S), G==R),
  589				    if_then_or_holds(H, S, A))),
  590	    'chr debug_event'(remove(I)),
  591	    I=suspension(_, _, _, _, _, if_then_or_holds, T, U, V),
  592	    setarg(2, I, removed),
  593	    term_variables(term(T, U, V), Y),
  594	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
  595		      W),
  596	    'chr sbag_del_element'(W, I, X),
  597	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
  598		     X),
  599	    detach_if_then_or_holds___3(Y, I),
  600	    if_then_or_holds(H, Z, A)
  601	).
  602if_then_or_holds___3__0(H, P, A, I) :-
  603	(   'chr newvia_1'(A, B)
  604	->  get_attr(B, user, C),
  605	    C=v(_, _, _, _, _, _, _, _, _, _, _, _, D, _)
  606	;   nb_getval('$chr_store_global_list_user____cancel___2', D)
  607	),
  608	'chr sbag_member'(E, D),
  609	E=suspension(_, active, _, _, _, _, G, F),
  610	F==A,
  611	(   \+ G\=H,
  612	    'chr debug_event'(try([I],
  613				  [E],
  614				  \+G\=H,
  615				  true)), !,
  616	    'chr debug_event'(apply([I],
  617				    [E],
  618				    \+G\=H,
  619				    true)),
  620	    'chr debug_event'(remove(I)),
  621	    I=suspension(_, _, _, _, _, if_then_or_holds, J, K, L),
  622	    setarg(2, I, removed),
  623	    term_variables(term(J, K, L), O),
  624	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
  625		      M),
  626	    'chr sbag_del_element'(M, I, N),
  627	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
  628		     N),
  629	    detach_if_then_or_holds___3(O, I)
  630	;   member(Q, P),
  631	    \+ G\=Q,
  632	    'chr debug_event'(try([I],
  633				  [E],
  634				  (member(R, P), \+G\=R),
  635				  true)), !,
  636	    'chr debug_event'(apply([I],
  637				    [E],
  638				    (member(R, P), \+G\=R),
  639				    true)),
  640	    'chr debug_event'(remove(I)),
  641	    I=suspension(_, _, _, _, _, if_then_or_holds, S, T, U),
  642	    setarg(2, I, removed),
  643	    term_variables(term(S, T, U), X),
  644	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
  645		      V),
  646	    'chr sbag_del_element'(V, I, W),
  647	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
  648		     W),
  649	    detach_if_then_or_holds___3(X, I)
  650	).
  651if_then_or_holds___3__0(_, _, _, A) :-
  652	setarg(2, A, active).
  653
  654detach_if_then_or_holds___3([], _).
  655detach_if_then_or_holds___3([A|T], E) :-
  656	(   get_attr(A, user, B)
  657	->  B=v(C, H, I, J, K, L, M, N, O, P, D, Q, R, S),
  658	    (   C/\512=:=512
  659	    ->  'chr sbag_del_element'(D, E, F),
  660		(   F==[]
  661		->  G is C/\ -513,
  662		    (   G==0
  663		    ->  del_attr(A, user)
  664		    ;   put_attr(A,
  665				 user,
  666				 v(G,
  667				   H,
  668				   I,
  669				   J,
  670				   K,
  671				   L,
  672				   M,
  673				   N,
  674				   O,
  675				   P,
  676				   [],
  677				   Q,
  678				   R,
  679				   S))
  680		    )
  681		;   put_attr(A,
  682			     user,
  683			     v(C,
  684			       H,
  685			       I,
  686			       J,
  687			       K,
  688			       L,
  689			       M,
  690			       N,
  691			       O,
  692			       P,
  693			       F,
  694			       Q,
  695			       R,
  696			       S))
  697		)
  698	    ;   true
  699	    )
  700	;   true
  701	),
  702	detach_if_then_or_holds___3(T, E).
  703
  704not_holds___2__2(E, A, F) :-
  705	(   'chr newvia_1'(A, B)
  706	->  get_attr(B, user, C),
  707	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
  708	;   nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
  709		      D)
  710	), !,
  711	not_holds___2__2__0__6(D, E, A, F).
  712not_holds___2__2(A, B, C) :-
  713	not_holds___2__3(A, B, C).
  714
  715a_star_do(D, A, H, I) :-
  716	(   A=do(go_to(B, C), _)
  717	->  true
  718	;   knows_val([B, C], at(B, C), D)
  719	),
  720	(   E=4
  721	;   E=3
  722	;   E=2
  723	;   E=1
  724	),
  725	adjacent(B, C, E, F, G),
  726	\+ visited(F, G),
  727	knows_not(pit(F, G), D),
  728	(   \+ knows(dead, D)
  729	->  knows_not(wumpus(F, G), D)
  730	;   true
  731	),
  732	H=go_to(F, G),
  733	assertz(visited(F, G)),
  734	I is F+G-2.
  735
  736all_not_holds___3__0__0__3([], A, B, C, D) :-
  737	all_not_holds___3__1(A, B, C, D).
  738all_not_holds___3__0__0__3([A|R], D, E, C, I) :-
  739	(   A=suspension(_, active, _, _, _, _, G, B),
  740	    B==C,
  741	    copy_fluent(D, E, F, H),
  742	    F=G,
  743	    \+ call(#\+H),
  744	    'chr debug_event'(try([A],
  745				  [I],
  746				  (copy_fluent(D, E, J, K), J=L, \+call(#\+K)),
  747				  true))
  748	->  'chr debug_event'(apply([A],
  749				    [I],
  750				    (copy_fluent(D, E, J, K), J=L, \+call(#\+K)),
  751				    true)),
  752	    'chr debug_event'(remove(A)),
  753	    A=suspension(_, _, _, _, _, not_holds, M, N),
  754	    setarg(2, A, removed),
  755	    term_variables(term(M, N), Q),
  756	    nb_getval('$chr_store_global_list_user____not_holds___2', O),
  757	    'chr sbag_del_element'(O, A, P),
  758	    b_setval('$chr_store_global_list_user____not_holds___2', P),
  759	    detach_not_holds___2(Q, A),
  760	    setarg(2, I, active),
  761	    (   I=suspension(_, active, _, _, _, _, _, _, _)
  762	    ->  setarg(2, I, inactive),
  763		all_not_holds___3__0__0__3(R,
  764					   D,
  765					   E,
  766					   C,
  767					   I)
  768	    ;   true
  769	    )
  770	;   all_not_holds___3__0__0__3(R,
  771				       D,
  772				       E,
  773				       C,
  774				       I)
  775	).
  776
  777attr_unify_hook(v(C2, A, B, C, D, E, F, G, H, I, J, K, L, M), N) :-
  778	sort(A, Q),
  779	sort(B, T),
  780	sort(C, W),
  781	sort(D, Z),
  782	sort(E, C1),
  783	sort(F, F1),
  784	sort(G, I1),
  785	sort(H, L1),
  786	sort(I, O1),
  787	sort(J, R1),
  788	sort(K, U1),
  789	sort(L, X1),
  790	sort(M, A2),
  791	(   var(N)
  792	->  (   get_attr(N, user, O)
  793	    ->  O=v(D2, P, S, V, Y, B1, E1, H1, K1, N1, Q1, T1, W1, Z1),
  794		sort(P, R),
  795		'chr merge_attributes'(Q, R, F2),
  796		sort(S, U),
  797		'chr merge_attributes'(T, U, G2),
  798		sort(V, X),
  799		'chr merge_attributes'(W, X, H2),
  800		sort(Y, A1),
  801		'chr merge_attributes'(Z, A1, I2),
  802		sort(B1, D1),
  803		'chr merge_attributes'(C1, D1, J2),
  804		sort(E1, G1),
  805		'chr merge_attributes'(F1, G1, K2),
  806		sort(H1, J1),
  807		'chr merge_attributes'(I1, J1, L2),
  808		sort(K1, M1),
  809		'chr merge_attributes'(L1, M1, M2),
  810		sort(N1, P1),
  811		'chr merge_attributes'(O1, P1, N2),
  812		sort(Q1, S1),
  813		'chr merge_attributes'(R1, S1, O2),
  814		sort(T1, V1),
  815		'chr merge_attributes'(U1, V1, P2),
  816		sort(W1, Y1),
  817		'chr merge_attributes'(X1, Y1, Q2),
  818		sort(Z1, B2),
  819		'chr merge_attributes'(A2, B2, R2),
  820		E2 is C2\/D2,
  821		put_attr(N,
  822			 user,
  823			 v(E2,
  824			   F2,
  825			   G2,
  826			   H2,
  827			   I2,
  828			   J2,
  829			   K2,
  830			   L2,
  831			   M2,
  832			   N2,
  833			   O2,
  834			   P2,
  835			   Q2,
  836			   R2)),
  837		'$run_suspensions_not_holds___2'(F2),
  838		'$run_suspensions_not_holds_all___2'(G2),
  839		'$run_suspensions_duplicate_free___1'(H2),
  840		'$run_suspensions_or_holds___2'(I2),
  841		'$run_suspensions_or_holds___3'(J2),
  842		'$run_suspensions_all_holds___2'(F1),
  843		'$run_suspensions_all_holds___3'(L2),
  844		'$run_suspensions_all_not_holds___3'(M2),
  845		'$run_suspensions_if_then_holds___3'(O1),
  846		'$run_suspensions_if_then_or_holds___3'(O2),
  847		'$run_suspensions_if_then_or_holds___4'(P2),
  848		'$run_suspensions_cancel___2'(Q2),
  849		'$run_suspensions_cancelled___2'(A2)
  850	    ;   put_attr(N,
  851			 user,
  852			 v(C2,
  853			   Q,
  854			   T,
  855			   W,
  856			   Z,
  857			   C1,
  858			   F1,
  859			   I1,
  860			   L1,
  861			   O1,
  862			   R1,
  863			   U1,
  864			   X1,
  865			   A2)),
  866		'$run_suspensions_not_holds___2'(Q),
  867		'$run_suspensions_not_holds_all___2'(T),
  868		'$run_suspensions_duplicate_free___1'(W),
  869		'$run_suspensions_or_holds___2'(Z),
  870		'$run_suspensions_or_holds___3'(C1),
  871		'$run_suspensions_all_holds___2'(F1),
  872		'$run_suspensions_all_holds___3'(I1),
  873		'$run_suspensions_all_not_holds___3'(L1),
  874		'$run_suspensions_if_then_holds___3'(O1),
  875		'$run_suspensions_if_then_or_holds___3'(R1),
  876		'$run_suspensions_if_then_or_holds___4'(U1),
  877		'$run_suspensions_cancel___2'(X1),
  878		'$run_suspensions_cancelled___2'(A2)
  879	    )
  880	;   (   compound(N)
  881	    ->  term_variables(N, S2),
  882		attach_increment(S2,
  883				 v(C2,
  884				   Q,
  885				   T,
  886				   W,
  887				   Z,
  888				   C1,
  889				   F1,
  890				   I1,
  891				   L1,
  892				   O1,
  893				   R1,
  894				   U1,
  895				   X1,
  896				   A2))
  897	    ;   true
  898	    ),
  899	    '$run_suspensions_not_holds___2'(Q),
  900	    '$run_suspensions_not_holds_all___2'(T),
  901	    '$run_suspensions_duplicate_free___1'(W),
  902	    '$run_suspensions_or_holds___2'(Z),
  903	    '$run_suspensions_or_holds___3'(C1),
  904	    '$run_suspensions_all_holds___2'(F1),
  905	    '$run_suspensions_all_holds___3'(I1),
  906	    '$run_suspensions_all_not_holds___3'(L1),
  907	    '$run_suspensions_if_then_holds___3'(O1),
  908	    '$run_suspensions_if_then_or_holds___3'(R1),
  909	    '$run_suspensions_if_then_or_holds___4'(U1),
  910	    '$run_suspensions_cancel___2'(X1),
  911	    '$run_suspensions_cancelled___2'(A2)
  912	).
  913
  914not_holds(A, B) :-
  915	C=suspension(D, active, t, 0, user:not_holds___2__0(A, B, C), not_holds, A, B),
  916	term_variables(term(A, B), F),
  917	'chr gen_id'(D),
  918	nb_getval('$chr_store_global_list_user____not_holds___2', E),
  919	b_setval('$chr_store_global_list_user____not_holds___2',
  920		 [C|E]),
  921	attach_not_holds___2(F, C),
  922	setarg(2, C, inactive),
  923	'chr debug_event'(insert(not_holds(A, B)#C)),
  924	(   'chr debug_event'(call(C)),
  925	    not_holds___2__0(A, B, C)
  926	;   'chr debug_event'(fail(C)), !,
  927	    fail
  928	),
  929	(   'chr debug_event'(exit(C))
  930	;   'chr debug_event'(redo(C)),
  931	    fail
  932	).
  933
  934cancel___2__1__0__2([], A, B, C) :-
  935	cancel___2__2(A, B, C).
  936cancel___2__1__0__2([A|M], D, C, F) :-
  937	(   A=suspension(_, active, _, _, _, _, E, B),
  938	    B==C,
  939	    \+ D\=E,
  940	    'chr debug_event'(try([A],
  941				  [F],
  942				  \+D\=G,
  943				  true))
  944	->  'chr debug_event'(apply([A],
  945				    [F],
  946				    \+D\=G,
  947				    true)),
  948	    'chr debug_event'(remove(A)),
  949	    A=suspension(_, _, _, _, _, not_holds_all, H, I),
  950	    setarg(2, A, removed),
  951	    term_variables(term(H, I), L),
  952	    nb_getval('$chr_store_global_list_user____not_holds_all___2',
  953		      J),
  954	    'chr sbag_del_element'(J, A, K),
  955	    b_setval('$chr_store_global_list_user____not_holds_all___2',
  956		     K),
  957	    detach_not_holds_all___2(L, A),
  958	    setarg(2, F, active),
  959	    (   F=suspension(_, active, _, _, _, _, _, _)
  960	    ->  setarg(2, F, inactive),
  961		cancel___2__1__0__2(M, D, C, F)
  962	    ;   true
  963	    )
  964	;   cancel___2__1__0__2(M, D, C, F)
  965	).
  966
  967not_holds___2__0(C, A, B) :-
  968	nonvar(A),
  969	A=[D|E],
  970	'chr debug_event'(try([B],
  971			      [],
  972			      true,
  973			      (neq(C, D), not_holds(C, E)))), !,
  974	'chr debug_event'(apply([B],
  975				[],
  976				true,
  977				(neq(C, D), not_holds(C, E)))),
  978	'chr debug_event'(remove(B)),
  979	B=suspension(_, _, _, _, _, not_holds, F, G),
  980	setarg(2, B, removed),
  981	term_variables(term(F, G), J),
  982	nb_getval('$chr_store_global_list_user____not_holds___2', H),
  983	'chr sbag_del_element'(H, B, I),
  984	b_setval('$chr_store_global_list_user____not_holds___2', I),
  985	detach_not_holds___2(J, B),
  986	neq(C, D),
  987	not_holds(C, E).
  988not_holds___2__0(_, A, B) :-
  989	A==[],
  990	'chr debug_event'(try([B], [], true, true)), !,
  991	'chr debug_event'(apply([B], [], true, true)),
  992	'chr debug_event'(remove(B)),
  993	B=suspension(_, _, _, _, _, not_holds, C, D),
  994	setarg(2, B, removed),
  995	term_variables(term(C, D), G),
  996	nb_getval('$chr_store_global_list_user____not_holds___2', E),
  997	'chr sbag_del_element'(E, B, F),
  998	b_setval('$chr_store_global_list_user____not_holds___2', F),
  999	detach_not_holds___2(G, B).
 1000not_holds___2__0(E, A, F) :-
 1001	(   'chr newvia_1'(A, B)
 1002	->  get_attr(B, user, C),
 1003	    C=v(_, _, _, _, _, _, _, D, _, _, _, _, _, _)
 1004	;   nb_getval('$chr_store_global_list_user____all_holds___3', D)
 1005	), !,
 1006	not_holds___2__0__0__3(D, E, A, F).
 1007not_holds___2__0(A, B, C) :-
 1008	not_holds___2__1(A, B, C).
 1009
 1010all_holds___3__0__0__2([], A, B, C, D) :-
 1011	all_holds___3__1(A, B, C, D).
 1012all_holds___3__0__0__2([A|M], F, G, C, D) :-
 1013	(   A=suspension(_, active, _, _, _, _, I, B),
 1014	    B==C,
 1015	    E=t(7, D, A),
 1016	    '$novel_production'(D, E),
 1017	    '$novel_production'(A, E),
 1018	    copy_fluent(F, G, K, L),
 1019	    'chr debug_event'(try([],
 1020				  [D, A],
 1021				  copy_fluent(F, G, H, J),
 1022				  (H=I, call(#\+J))))
 1023	->  'chr debug_event'(apply([],
 1024				    [D, A],
 1025				    copy_fluent(F,
 1026						G,
 1027						H,
 1028						J),
 1029				    (H=I, call(#\+J)))),
 1030	    '$extend_history'(D, E),
 1031	    setarg(2, D, active),
 1032	    K=I,
 1033	    call(#\+L),
 1034	    (   D=suspension(_, active, _, _, _, _, _, _, _)
 1035	    ->  setarg(2, D, inactive),
 1036		all_holds___3__0__0__2(M,
 1037				       F,
 1038				       G,
 1039				       C,
 1040				       D)
 1041	    ;   true
 1042	    )
 1043	;   all_holds___3__0__0__2(M, F, G, C, D)
 1044	).
 1045
 1046main_loop([B, C, A|M], E, N, F) :-
 1047	(   A=[D|L]
 1048	->  (   explore(B, C, D, E, F, I)
 1049	    ->  knows_val([G, H], at(G, H), I),
 1050		hunt_wumpus(G, H, I, J),
 1051		(   knows(gold(G, H), J)
 1052		->  execute(grab, J, K),
 1053		    go_home(K)
 1054		;   O=[G, H, [1, 2, 3, 4], B, C, L|M],
 1055		    P=[[G, H]|E],
 1056		    Q=[B, C|N],
 1057		    main_loop(O, P, Q, J)
 1058		)
 1059	    ;   main_loop([B, C, L|M],
 1060			  E,
 1061			  N,
 1062			  F)
 1063	    )
 1064	;   backtrack(M, E, N, F)
 1065	).
 1066
 1067inst(A, B) :-
 1068	\+ ( term_variables(A, D),
 1069	     term_variables(B, C),
 1070	     bound_free(C, D, G, E),
 1071	     copy_term_vars(E, B, F),
 1072	     \+ no_global_bindings(A=F, G)
 1073	   ).
 1074
 1075neq(A, B) :-
 1076	or_neq(exists, A, B).
 1077
 1078attach_all_holds___2([], _).
 1079attach_all_holds___2([A|T], I) :-
 1080	(   get_attr(A, user, B)
 1081	->  B=v(C, D, E, F, G, H, J, K, L, M, N, O, P, Q),
 1082	    (   C/\32=:=32
 1083	    ->  R=v(C, D, E, F, G, H, [I|J], K, L, M, N, O, P, Q)
 1084	    ;   S is C\/32,
 1085		R=v(S, D, E, F, G, H, [I], K, L, M, N, O, P, Q)
 1086	    ),
 1087	    put_attr(A, user, R)
 1088	;   put_attr(A,
 1089		     user,
 1090		     v(32, [], [], [], [], [], [I], [], [], [], [], [], [], []))
 1091	),
 1092	attach_all_holds___2(T, I).
 1093
 1094if_then_or_holds(A, B, C, D) :-
 1095	E=suspension(G, active, _, 0, user:if_then_or_holds___4__0(A, B, C, D, E), if_then_or_holds, A, B, C, D),
 1096	term_variables(B, I, F),
 1097	term_variables(D, F),
 1098	'chr gen_id'(G),
 1099	nb_getval('$chr_store_global_list_user____if_then_or_holds___4', H),
 1100	b_setval('$chr_store_global_list_user____if_then_or_holds___4',
 1101		 [E|H]),
 1102	attach_if_then_or_holds___4(I, E),
 1103	setarg(2, E, inactive),
 1104	'chr debug_event'(insert(if_then_or_holds(A, B, C, D)#E)),
 1105	(   'chr debug_event'(call(E)),
 1106	    if_then_or_holds___4__0(A, B, C, D, E)
 1107	;   'chr debug_event'(fail(E)), !,
 1108	    fail
 1109	),
 1110	(   'chr debug_event'(exit(E))
 1111	;   'chr debug_event'(redo(E)),
 1112	    fail
 1113	).
 1114
 1115cancel___2__0(E, A, F) :-
 1116	(   'chr newvia_1'(A, B)
 1117	->  get_attr(B, user, C),
 1118	    C=v(_, D, _, _, _, _, _, _, _, _, _, _, _, _)
 1119	;   nb_getval('$chr_store_global_list_user____not_holds___2', D)
 1120	), !,
 1121	cancel___2__0__0__1(D, E, A, F).
 1122cancel___2__0(A, B, C) :-
 1123	cancel___2__1(A, B, C).
 1124
 1125neq(A, B, C) :-
 1126	or_neq_c(exists, A, B, C).
 1127
 1128attach_if_then_or_holds___3([], _).
 1129attach_if_then_or_holds___3([A|T], M) :-
 1130	(   get_attr(A, user, B)
 1131	->  B=v(C, D, E, F, G, H, I, J, K, L, N, O, P, Q),
 1132	    (   C/\512=:=512
 1133	    ->  R=v(C, D, E, F, G, H, I, J, K, L, [M|N], O, P, Q)
 1134	    ;   S is C\/512,
 1135		R=v(S, D, E, F, G, H, I, J, K, L, [M], O, P, Q)
 1136	    ),
 1137	    put_attr(A, user, R)
 1138	;   put_attr(A,
 1139		     user,
 1140		     v(512, [], [], [], [], [], [], [], [], [], [M], [], [], []))
 1141	),
 1142	attach_if_then_or_holds___3(T, M).
 1143
 1144detach_duplicate_free___1([], _).
 1145detach_duplicate_free___1([A|T], E) :-
 1146	(   get_attr(A, user, B)
 1147	->  B=v(C, H, I, D, J, K, L, M, N, O, P, Q, R, S),
 1148	    (   C/\4=:=4
 1149	    ->  'chr sbag_del_element'(D, E, F),
 1150		(   F==[]
 1151		->  G is C/\ -5,
 1152		    (   G==0
 1153		    ->  del_attr(A, user)
 1154		    ;   put_attr(A,
 1155				 user,
 1156				 v(G,
 1157				   H,
 1158				   I,
 1159				   [],
 1160				   J,
 1161				   K,
 1162				   L,
 1163				   M,
 1164				   N,
 1165				   O,
 1166				   P,
 1167				   Q,
 1168				   R,
 1169				   S))
 1170		    )
 1171		;   put_attr(A,
 1172			     user,
 1173			     v(C,
 1174			       H,
 1175			       I,
 1176			       F,
 1177			       J,
 1178			       K,
 1179			       L,
 1180			       M,
 1181			       N,
 1182			       O,
 1183			       P,
 1184			       Q,
 1185			       R,
 1186			       S))
 1187		)
 1188	    ;   true
 1189	    )
 1190	;   true
 1191	),
 1192	detach_duplicate_free___1(T, E).
 1193
 1194insert_all([], _, _, A, A).
 1195insert_all([[G, F]|A], B, C, D, J) :-
 1196	insert_all(A, B, C, D, I),
 1197	E is C+1,
 1198	H is E+F,
 1199	ins(do(G, B), E, H, I, J).
 1200
 1201and_eq([], [], 0#=0).
 1202and_eq([D|A], [E|B], C) :-
 1203	and_eq(A, B, F),
 1204	C= (D#=E#/\F).
 1205
 1206all_not_holds___3__1(E, F, A, G) :-
 1207	(   'chr newvia_1'(A, B)
 1208	->  get_attr(B, user, C),
 1209	    C=v(_, _, _, _, D, _, _, _, _, _, _, _, _, _)
 1210	;   nb_getval('$chr_store_global_list_user____or_holds___2', D)
 1211	), !,
 1212	all_not_holds___3__1__0__4(D, E, F, A, G).
 1213all_not_holds___3__1(A, B, C, D) :-
 1214	all_not_holds___3__2(A, B, C, D).
 1215
 1216init_scenario :-
 1217	retractall(wumpus(_, _)),
 1218	retractall(pit(_, _)),
 1219	retractall(gold(_, _)),
 1220	xdim(B),
 1221	ydim(D),
 1222	random(0, 4294967296, A),
 1223	random(0, 4294967296, C),
 1224	E is A mod B+1,
 1225	F is C mod D+1,
 1226	(   E=1,
 1227	    F=1
 1228	->  true
 1229	;   assertz(wumpus(E, F)),
 1230	    write(wumpus(E, F))
 1231	),
 1232	random(0, 4294967296, G),
 1233	random(0, 4294967296, H),
 1234	I is G mod B+1,
 1235	J is H mod D+1,
 1236	assertz(gold(I, J)),
 1237	write(gold(I, J)),
 1238	no_of_random_pits(K),
 1239	create_pits(K).
 1240
 1241cancel___2__4__0__5([], A, B, C) :-
 1242	cancel___2__5(A, B, C).
 1243cancel___2__4__0__5([A|P], E, C, G) :-
 1244	(   A=suspension(_, active, _, _, _, _, _, D, B),
 1245	    B==C,
 1246	    member(F, D),
 1247	    \+ E\=F,
 1248	    'chr debug_event'(try([A],
 1249				  [G],
 1250				  (member(H, I), \+E\=H),
 1251				  true))
 1252	->  'chr debug_event'(apply([A],
 1253				    [G],
 1254				    (member(H, I), \+E\=H),
 1255				    true)),
 1256	    'chr debug_event'(remove(A)),
 1257	    A=suspension(_, _, _, _, _, if_then_or_holds, J, K, L),
 1258	    setarg(2, A, removed),
 1259	    term_variables(term(J, K, L), O),
 1260	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
 1261		      M),
 1262	    'chr sbag_del_element'(M, A, N),
 1263	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
 1264		     N),
 1265	    detach_if_then_or_holds___3(O, A),
 1266	    setarg(2, G, active),
 1267	    (   G=suspension(_, active, _, _, _, _, _, _)
 1268	    ->  setarg(2, G, inactive),
 1269		cancel___2__4__0__5(P, E, C, G)
 1270	    ;   true
 1271	    )
 1272	;   cancel___2__4__0__5(P, E, C, G)
 1273	).
 1274
 1275if_then_or_holds(A, B, C) :-
 1276	D=suspension(E, active, _, 0, user:if_then_or_holds___3__0(A, B, C, D), if_then_or_holds, A, B, C),
 1277	term_variables(term(A, B, C), G),
 1278	'chr gen_id'(E),
 1279	nb_getval('$chr_store_global_list_user____if_then_or_holds___3', F),
 1280	b_setval('$chr_store_global_list_user____if_then_or_holds___3',
 1281		 [D|F]),
 1282	attach_if_then_or_holds___3(G, D),
 1283	setarg(2, D, inactive),
 1284	'chr debug_event'(insert(if_then_or_holds(A, B, C)#D)),
 1285	(   'chr debug_event'(call(D)),
 1286	    if_then_or_holds___3__0(A, B, C, D)
 1287	;   'chr debug_event'(fail(D)), !,
 1288	    fail
 1289	),
 1290	(   'chr debug_event'(exit(D))
 1291	;   'chr debug_event'(redo(D)),
 1292	    fail
 1293	).
 1294
 1295all_holds___3__2(E, F, A, G) :-
 1296	(   'chr newvia_1'(A, B)
 1297	->  get_attr(B, user, C),
 1298	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
 1299	;   nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
 1300		      D)
 1301	), !,
 1302	all_holds___3__2__0__5(D, E, F, A, G).
 1303all_holds___3__2(A, B, C, D) :-
 1304	all_holds___3__3(A, B, C, D).
 1305
 1306not_holds___2__3(E, A, F) :-
 1307	(   'chr newvia_1'(A, B)
 1308	->  get_attr(B, user, C),
 1309	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
 1310	;   nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
 1311		      D)
 1312	), !,
 1313	not_holds___2__3__0__7(D, E, A, F).
 1314not_holds___2__3(A, B, C) :-
 1315	not_holds___2__4(A, B, C).
 1316
 1317not_holds___2__1__0__5([], A, B, C) :-
 1318	not_holds___2__2(A, B, C).
 1319not_holds___2__1__0__5([A|Q], E, C, G) :-
 1320	(   A=suspension(_, active, _, _, _, _, D, B),
 1321	    B==C,
 1322	    member(F, D, P),
 1323	    E==F,
 1324	    'chr debug_event'(try([A],
 1325				  [G],
 1326				  (member(H, J, I), E==H),
 1327				  or_holds(I, C)))
 1328	->  'chr debug_event'(apply([A],
 1329				    [G],
 1330				    (member(H, J, I), E==H),
 1331				    or_holds(I, C))),
 1332	    'chr debug_event'(remove(A)),
 1333	    A=suspension(_, _, _, _, _, or_holds, K, L),
 1334	    setarg(2, A, removed),
 1335	    term_variables(term(K, L), O),
 1336	    nb_getval('$chr_store_global_list_user____or_holds___2', M),
 1337	    'chr sbag_del_element'(M, A, N),
 1338	    b_setval('$chr_store_global_list_user____or_holds___2', N),
 1339	    detach_or_holds___2(O, A),
 1340	    setarg(2, G, active),
 1341	    or_holds(P, C),
 1342	    (   G=suspension(_, active, _, _, _, _, _, _)
 1343	    ->  setarg(2, G, inactive),
 1344		not_holds___2__1__0__5(Q, E, C, G)
 1345	    ;   true
 1346	    )
 1347	;   not_holds___2__1__0__5(Q, E, C, G)
 1348	).
 1349
 1350a_star_plan(C, D) :-
 1351	retractall(visited(_, _)),
 1352	knows_val([A, B], at(A, B), C),
 1353	assertz(visited(A, B)),
 1354	a_star(C, [[], 0, 100000], D).
 1355
 1356cancelled___2__0(A, B, I) :-
 1357	(   'chr newvia_2'(A, B, C)
 1358	->  get_attr(C, user, D),
 1359	    D=v(_, _, _, _, _, _, _, _, _, _, _, _, E, _)
 1360	;   nb_getval('$chr_store_global_list_user____cancel___2', E)
 1361	),
 1362	'chr sbag_member'(F, E),
 1363	F=suspension(_, active, _, _, _, _, G, H),
 1364	G==A,
 1365	H==B,
 1366	'chr debug_event'(try([F, I], [], true, true)), !,
 1367	'chr debug_event'(apply([F, I], [], true, true)),
 1368	'chr debug_event'(remove(F)),
 1369	F=suspension(_, _, _, _, _, cancel, J, K),
 1370	setarg(2, F, removed),
 1371	term_variables(term(J, K), N),
 1372	nb_getval('$chr_store_global_list_user____cancel___2', L),
 1373	'chr sbag_del_element'(L, F, M),
 1374	b_setval('$chr_store_global_list_user____cancel___2', M),
 1375	detach_cancel___2(N, F),
 1376	'chr debug_event'(remove(I)),
 1377	I=suspension(_, _, _, _, _, cancelled, O, P),
 1378	setarg(2, I, removed),
 1379	term_variables(term(O, P), S),
 1380	nb_getval('$chr_store_global_list_user____cancelled___2', Q),
 1381	'chr sbag_del_element'(Q, I, R),
 1382	b_setval('$chr_store_global_list_user____cancelled___2', R),
 1383	detach_cancelled___2(S, I).
 1384cancelled___2__0(_, _, A) :-
 1385	setarg(2, A, active).
 1386
 1387is_domain(A) :-
 1388	clpfd:fd_get(A, B, _), !,
 1389	A in B.
 1390
 1391or_neq(_, [], [], 0#\=0).
 1392or_neq(A, [D|B], [F|C], E) :-
 1393	or_neq(A, B, C, H),
 1394	(   A=forall,
 1395	    var(D),
 1396	    \+ is_domain(D)
 1397	->  (   binding(D, B, C, G)
 1398	    ->  E= (F#\=G#\/H)
 1399	    ;   E=H
 1400	    )
 1401	;   E= (D#\=F#\/H)
 1402	).
 1403
 1404go_home(A) :-
 1405	write('Planning...'),
 1406	a_star_plan(A, B),
 1407	execute(B, A, C),
 1408	execute(exit, C, _).
 1409
 1410attach_increment([], _).
 1411attach_increment([A|G2], B) :-
 1412	(   get_attr(A, user, C)
 1413	->  B=v(Q1, E, H, K, N, Q, T, W, Z, C1, F1, I1, L1, O1),
 1414	    C=v(R1, D, G, J, M, P, S, V, Y, B1, E1, H1, K1, N1),
 1415	    sort(D, F),
 1416	    'chr merge_attributes'(E, F, T1),
 1417	    sort(G, I),
 1418	    'chr merge_attributes'(H, I, U1),
 1419	    sort(J, L),
 1420	    'chr merge_attributes'(K, L, V1),
 1421	    sort(M, O),
 1422	    'chr merge_attributes'(N, O, W1),
 1423	    sort(P, R),
 1424	    'chr merge_attributes'(Q, R, X1),
 1425	    sort(S, U),
 1426	    'chr merge_attributes'(T, U, Y1),
 1427	    sort(V, X),
 1428	    'chr merge_attributes'(W, X, Z1),
 1429	    sort(Y, A1),
 1430	    'chr merge_attributes'(Z, A1, A2),
 1431	    sort(B1, D1),
 1432	    'chr merge_attributes'(C1, D1, B2),
 1433	    sort(E1, G1),
 1434	    'chr merge_attributes'(F1, G1, C2),
 1435	    sort(H1, J1),
 1436	    'chr merge_attributes'(I1, J1, D2),
 1437	    sort(K1, M1),
 1438	    'chr merge_attributes'(L1, M1, E2),
 1439	    sort(N1, P1),
 1440	    'chr merge_attributes'(O1, P1, F2),
 1441	    S1 is Q1\/R1,
 1442	    put_attr(A,
 1443		     user,
 1444		     v(S1,
 1445		       T1,
 1446		       U1,
 1447		       V1,
 1448		       W1,
 1449		       X1,
 1450		       Y1,
 1451		       Z1,
 1452		       A2,
 1453		       B2,
 1454		       C2,
 1455		       D2,
 1456		       E2,
 1457		       F2))
 1458	;   put_attr(A, user, B)
 1459	),
 1460	attach_increment(G2, B).
 1461
 1462ydim(12).
 1463
 1464cancel___2__2(E, A, F) :-
 1465	(   'chr newvia_1'(A, B)
 1466	->  get_attr(B, user, C),
 1467	    C=v(_, _, _, _, D, _, _, _, _, _, _, _, _, _)
 1468	;   nb_getval('$chr_store_global_list_user____or_holds___2', D)
 1469	), !,
 1470	cancel___2__2__0__3(D, E, A, F).
 1471cancel___2__2(A, B, C) :-
 1472	cancel___2__3(A, B, C).
 1473
 1474adjacent(A, D, G, C, F) :-
 1475	xdim(B),
 1476	ydim(E),
 1477	A in 1..B,
 1478	C in 1..B,
 1479	D in 1..E,
 1480	F in 1..E,
 1481	G in 1..4,
 1482	G#=1#/\C#=A#/\F#=D+1#\/G#=3#/\C#=A#/\F#=D-1#\/G#=2#/\C#=A+1#/\F#=D#\/G#=4#/\C#=A-1#/\F#=D.
 1483
 1484bound_free([], A, A, []).
 1485bound_free([C|A], B, D, F) :-
 1486	bound_free(A, B, E, G),
 1487	(   is_domain(C)
 1488	->  D=[C|E],
 1489	    F=G
 1490	;   D=E,
 1491	    F=[C|G]
 1492	).
 1493
 1494:- dynamic expand_query/4. 1495:- multifile expand_query/4. 1496
 1497expand_query(A, B, C, D) :-
 1498	toplevel_variables:expand_query(A, B, C, D).
 1499
 1500detach_all_holds___3([], _).
 1501detach_all_holds___3([A|T], E) :-
 1502	(   get_attr(A, user, B)
 1503	->  B=v(C, H, I, J, K, L, M, D, N, O, P, Q, R, S),
 1504	    (   C/\64=:=64
 1505	    ->  'chr sbag_del_element'(D, E, F),
 1506		(   F==[]
 1507		->  G is C/\ -65,
 1508		    (   G==0
 1509		    ->  del_attr(A, user)
 1510		    ;   put_attr(A,
 1511				 user,
 1512				 v(G,
 1513				   H,
 1514				   I,
 1515				   J,
 1516				   K,
 1517				   L,
 1518				   M,
 1519				   [],
 1520				   N,
 1521				   O,
 1522				   P,
 1523				   Q,
 1524				   R,
 1525				   S))
 1526		    )
 1527		;   put_attr(A,
 1528			     user,
 1529			     v(C,
 1530			       H,
 1531			       I,
 1532			       J,
 1533			       K,
 1534			       L,
 1535			       M,
 1536			       F,
 1537			       N,
 1538			       O,
 1539			       P,
 1540			       Q,
 1541			       R,
 1542			       S))
 1543		)
 1544	    ;   true
 1545	    )
 1546	;   true
 1547	),
 1548	detach_all_holds___3(T, E).
 1549
 1550hunt_wumpus(D, E, A, H) :-
 1551	(   \+ knows(dead, A),
 1552	    knows_val([B, C], wumpus(B, C), A),
 1553	    in_direction(D, E, F, B, C)
 1554	->  turn_to(F, A, G),
 1555	    execute(shoot, G, H)
 1556	;   H=A
 1557	).
 1558
 1559all_holds___3__1__0__4([], A, B, C, D) :-
 1560	all_holds___3__2(A, B, C, D).
 1561all_holds___3__1__0__4([A|T], E, F, C, J) :-
 1562	(   A=suspension(_, active, _, _, _, _, D, B),
 1563	    B==C,
 1564	    member(H, D),
 1565	    copy_fluent(E, F, G, I),
 1566	    G=H,
 1567	    \+ call(#\+I),
 1568	    'chr debug_event'(try([A],
 1569				  [J],
 1570				  (member(L, N), copy_fluent(E, F, K, M), K=L, \+call(#\+M)),
 1571				  true))
 1572	->  'chr debug_event'(apply([A],
 1573				    [J],
 1574				    (member(L, N), copy_fluent(E, F, K, M), K=L, \+call(#\+M)),
 1575				    true)),
 1576	    'chr debug_event'(remove(A)),
 1577	    A=suspension(_, _, _, _, _, or_holds, O, P),
 1578	    setarg(2, A, removed),
 1579	    term_variables(term(O, P), S),
 1580	    nb_getval('$chr_store_global_list_user____or_holds___2', Q),
 1581	    'chr sbag_del_element'(Q, A, R),
 1582	    b_setval('$chr_store_global_list_user____or_holds___2', R),
 1583	    detach_or_holds___2(S, A),
 1584	    setarg(2, J, active),
 1585	    (   J=suspension(_, active, _, _, _, _, _, _, _)
 1586	    ->  setarg(2, J, inactive),
 1587		all_holds___3__1__0__4(T,
 1588				       E,
 1589				       F,
 1590				       C,
 1591				       J)
 1592	    ;   true
 1593	    )
 1594	;   all_holds___3__1__0__4(T, E, F, C, J)
 1595	).
 1596
 1597attach_cancel___2([], _).
 1598attach_cancel___2([A|T], O) :-
 1599	(   get_attr(A, user, B)
 1600	->  B=v(C, D, E, F, G, H, I, J, K, L, M, N, P, Q),
 1601	    (   C/\2048=:=2048
 1602	    ->  R=v(C, D, E, F, G, H, I, J, K, L, M, N, [O|P], Q)
 1603	    ;   S is C\/2048,
 1604		R=v(S, D, E, F, G, H, I, J, K, L, M, N, [O], Q)
 1605	    ),
 1606	    put_attr(A, user, R)
 1607	;   put_attr(A,
 1608		     user,
 1609		     v(2048, [], [], [], [], [], [], [], [], [], [], [], [O], []))
 1610	),
 1611	attach_cancel___2(T, O).
 1612
 1613if_then_holds___3__0(B, C, D, A) :-
 1614	'chr debug_event'(try([A],
 1615			      [],
 1616			      true,
 1617			      if_then_or_holds(B, [C], D))), !,
 1618	'chr debug_event'(apply([A],
 1619				[],
 1620				true,
 1621				if_then_or_holds(B, [C], D))),
 1622	'chr debug_event'(remove(A)),
 1623	A=suspension(_, _, _, _, _, if_then_holds, _, _, _),
 1624	setarg(2, A, removed),
 1625	nb_getval('$chr_store_global_list_user____if_then_holds___3', E),
 1626	'chr sbag_del_element'(E, A, F),
 1627	b_setval('$chr_store_global_list_user____if_then_holds___3', F),
 1628	if_then_or_holds(B, [C], D).
 1629if_then_holds___3__0(_, _, _, A) :-
 1630	setarg(2, A, active).
 1631
 1632all_holds___2__0(B, C, A) :-
 1633	'chr debug_event'(try([A],
 1634			      [],
 1635			      true,
 1636			      all_holds(B, 0#=0, C))), !,
 1637	'chr debug_event'(apply([A],
 1638				[],
 1639				true,
 1640				all_holds(B, 0#=0, C))),
 1641	'chr debug_event'(remove(A)),
 1642	A=suspension(_, _, _, _, _, all_holds, _, _),
 1643	setarg(2, A, removed),
 1644	nb_getval('$chr_store_global_list_user____all_holds___2', D),
 1645	'chr sbag_del_element'(D, A, E),
 1646	b_setval('$chr_store_global_list_user____all_holds___2', E),
 1647	all_holds(B, 0#=0, C).
 1648all_holds___2__0(_, _, A) :-
 1649	setarg(2, A, active).
 1650
 1651if_then_or_holds___4__0(F, A, H, B, C) :-
 1652	nonvar(A),
 1653	A=[D|G],
 1654	nonvar(B),
 1655	B=[E|I],
 1656	'chr debug_event'(try([C],
 1657			      [],
 1658			      true,
 1659			      (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])))), !,
 1660	'chr debug_event'(apply([C],
 1661				[],
 1662				true,
 1663				(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])))),
 1664	'chr debug_event'(remove(C)),
 1665	C=suspension(_, _, _, _, _, if_then_or_holds, _, N, _, O),
 1666	setarg(2, C, removed),
 1667	term_variables(N, S, P),
 1668	term_variables(O, P),
 1669	nb_getval('$chr_store_global_list_user____if_then_or_holds___4',
 1670		  Q),
 1671	'chr sbag_del_element'(Q, C, R),
 1672	b_setval('$chr_store_global_list_user____if_then_or_holds___4', R),
 1673	detach_if_then_or_holds___4(S, C),
 1674	(   D==E
 1675	->  true
 1676	;   D\=E
 1677	->  if_then_or_holds(F,
 1678			     G,
 1679			     [D|H],
 1680			     [E|I])
 1681	;   D=..[_|T],
 1682	    E=..[_|U],
 1683	    if_then_or_holds(F,
 1684			     G,
 1685			     [eq(T, U), D|H],
 1686			     [E|I])
 1687	).
 1688if_then_or_holds___4__0(D, A, E, B, C) :-
 1689	A==[],
 1690	nonvar(B),
 1691	B=[_|F],
 1692	'chr debug_event'(try([C],
 1693			      [],
 1694			      true,
 1695			      if_then_or_holds(D, E, F))), !,
 1696	'chr debug_event'(apply([C],
 1697				[],
 1698				true,
 1699				if_then_or_holds(D, E, F))),
 1700	'chr debug_event'(remove(C)),
 1701	C=suspension(_, _, _, _, _, if_then_or_holds, _, G, _, H),
 1702	setarg(2, C, removed),
 1703	term_variables(G, L, I),
 1704	term_variables(H, I),
 1705	nb_getval('$chr_store_global_list_user____if_then_or_holds___4', J),
 1706	'chr sbag_del_element'(J, C, K),
 1707	b_setval('$chr_store_global_list_user____if_then_or_holds___4', K),
 1708	detach_if_then_or_holds___4(L, C),
 1709	if_then_or_holds(D, E, F).
 1710if_then_or_holds___4__0(_, _, _, _, A) :-
 1711	setarg(2, A, active).
 1712
 1713cancel(A, B) :-
 1714	C=suspension(D, active, _, 0, user:cancel___2__0(A, B, C), cancel, A, B),
 1715	term_variables(term(A, B), F),
 1716	'chr gen_id'(D),
 1717	nb_getval('$chr_store_global_list_user____cancel___2', E),
 1718	b_setval('$chr_store_global_list_user____cancel___2', [C|E]),
 1719	attach_cancel___2(F, C),
 1720	setarg(2, C, inactive),
 1721	'chr debug_event'(insert(cancel(A, B)#C)),
 1722	(   'chr debug_event'(call(C)),
 1723	    cancel___2__0(A, B, C)
 1724	;   'chr debug_event'(fail(C)), !,
 1725	    fail
 1726	),
 1727	(   'chr debug_event'(exit(C))
 1728	;   'chr debug_event'(redo(C)),
 1729	    fail
 1730	).
 1731
 1732breeze_perception(A, F, K, L) :-
 1733	(   integer(B)
 1734	->  (   var(A+1)
 1735	    ->  A+1 is B
 1736	    ;   integer(A)
 1737	    ->  B=:=A+1
 1738	    ;   C is B,
 1739		clpfd:clpfd_equal(C, A+1)
 1740	    )
 1741	;   integer(A)
 1742	->  (   var(B)
 1743	    ->  B is A+1
 1744	    ;   C is A+1,
 1745		clpfd:clpfd_equal(B, C)
 1746	    )
 1747	;   clpfd:clpfd_equal(B, A+1)
 1748	),
 1749	(   integer(D)
 1750	->  (   var(A-1)
 1751	    ->  A-1 is D
 1752	    ;   integer(A)
 1753	    ->  D=:=A-1
 1754	    ;   E is D,
 1755		clpfd:clpfd_equal(E, A-1)
 1756	    )
 1757	;   integer(A)
 1758	->  (   var(D)
 1759	    ->  D is A-1
 1760	    ;   E is A+ -1,
 1761		clpfd:clpfd_equal(D, E)
 1762	    )
 1763	;   clpfd:clpfd_equal(D, A-1)
 1764	),
 1765	(   integer(G)
 1766	->  (   var(F+1)
 1767	    ->  F+1 is G
 1768	    ;   integer(F)
 1769	    ->  G=:=F+1
 1770	    ;   H is G,
 1771		clpfd:clpfd_equal(H, F+1)
 1772	    )
 1773	;   integer(F)
 1774	->  (   var(G)
 1775	    ->  G is F+1
 1776	    ;   H is F+1,
 1777		clpfd:clpfd_equal(G, H)
 1778	    )
 1779	;   clpfd:clpfd_equal(G, F+1)
 1780	),
 1781	(   integer(I)
 1782	->  (   var(F-1)
 1783	    ->  F-1 is I
 1784	    ;   integer(F)
 1785	    ->  I=:=F-1
 1786	    ;   J is I,
 1787		clpfd:clpfd_equal(J, F-1)
 1788	    )
 1789	;   integer(F)
 1790	->  (   var(I)
 1791	    ->  I is F-1
 1792	    ;   J is F+ -1,
 1793		clpfd:clpfd_equal(I, J)
 1794	    )
 1795	;   clpfd:clpfd_equal(I, F-1)
 1796	),
 1797	(   K=false,
 1798	    not_holds(pit(B, F), L),
 1799	    not_holds(pit(D, F), L),
 1800	    not_holds(pit(A, G), L),
 1801	    not_holds(pit(A, I), L)
 1802	;   K=true,
 1803	    or_holds(
 1804		     [ pit(B, F),
 1805		       pit(A, G),
 1806		       pit(D, F),
 1807		       pit(A, I)
 1808		     ],
 1809		     L)
 1810	).
 1811
 1812create_pits(0) :- !.
 1813create_pits(G) :-
 1814	xdim(B),
 1815	ydim(D),
 1816	random(0, 4294967296, A),
 1817	random(0, 4294967296, C),
 1818	E is A mod B+1,
 1819	F is C mod D+1,
 1820	(   E+F<4
 1821	->  create_pits(G)
 1822	;   assertz(pit(E, F)),
 1823	    write(pit(E, F))
 1824	),
 1825	H is G+ -1,
 1826	create_pits(H).
 1827
 1828ins(C, D, A, [G, H, B|E], F) :-
 1829	(   A>B
 1830	->  ins(C, D, A, E, I),
 1831	    F=[G, H, B|I]
 1832	;   F=[C, D, A, G, H, B|E]
 1833	).
 1834ins(A, B, C, [], [A, B, C]).
 1835
 1836or_holds(A, B, C) :-
 1837	D=suspension(F, active, _, 0, user:or_holds___3__0(A, B, C, D), or_holds, A, B, C),
 1838	term_variables(A, H, E),
 1839	term_variables(C, E),
 1840	'chr gen_id'(F),
 1841	nb_getval('$chr_store_global_list_user____or_holds___3', G),
 1842	b_setval('$chr_store_global_list_user____or_holds___3',
 1843		 [D|G]),
 1844	attach_or_holds___3(H, D),
 1845	setarg(2, D, inactive),
 1846	'chr debug_event'(insert(or_holds(A, B, C)#D)),
 1847	(   'chr debug_event'(call(D)),
 1848	    or_holds___3__0(A, B, C, D)
 1849	;   'chr debug_event'(fail(D)), !,
 1850	    fail
 1851	),
 1852	(   'chr debug_event'(exit(D))
 1853	;   'chr debug_event'(redo(D)),
 1854	    fail
 1855	).
 1856
 1857init_simulator :-
 1858	init_scenario,
 1859	retractall(current_state(_)),
 1860	assertz(current_state([])).
 1861
 1862detach_if_then_holds___3([], _).
 1863detach_if_then_holds___3([A|T], E) :-
 1864	(   get_attr(A, user, B)
 1865	->  B=v(C, H, I, J, K, L, M, N, O, D, P, Q, R, S),
 1866	    (   C/\256=:=256
 1867	    ->  'chr sbag_del_element'(D, E, F),
 1868		(   F==[]
 1869		->  G is C/\ -257,
 1870		    (   G==0
 1871		    ->  del_attr(A, user)
 1872		    ;   put_attr(A,
 1873				 user,
 1874				 v(G,
 1875				   H,
 1876				   I,
 1877				   J,
 1878				   K,
 1879				   L,
 1880				   M,
 1881				   N,
 1882				   O,
 1883				   [],
 1884				   P,
 1885				   Q,
 1886				   R,
 1887				   S))
 1888		    )
 1889		;   put_attr(A,
 1890			     user,
 1891			     v(C,
 1892			       H,
 1893			       I,
 1894			       J,
 1895			       K,
 1896			       L,
 1897			       M,
 1898			       N,
 1899			       O,
 1900			       F,
 1901			       P,
 1902			       Q,
 1903			       R,
 1904			       S))
 1905		)
 1906	    ;   true
 1907	    )
 1908	;   true
 1909	),
 1910	detach_if_then_holds___3(T, E).
 1911
 1912perform(turn, []) :-
 1913	write(turn),
 1914	nl,
 1915	current_state([at(A, B), facing(C)]),
 1916	retract(current_state([at(A, B), facing(C)])),
 1917	(   C<4
 1918	->  D is C+1
 1919	;   D is 1
 1920	),
 1921	assertz(current_state([at(A, B), facing(D)])).
 1922perform(enter, [D, C, B]) :-
 1923	write(enter),
 1924	nl,
 1925	current_state(A),
 1926	retract(current_state(A)),
 1927	assertz(current_state([at(1, 1), facing(1)])),
 1928	(   gold(1, 1)
 1929	->  B=true
 1930	;   B=false
 1931	),
 1932	(   (   wumpus(1, 2)
 1933	    ;   wumpus(2, 1)
 1934	    )
 1935	->  C=true
 1936	;   C=false
 1937	),
 1938	(   (   pit(2, 1)
 1939	    ;   pit(1, 2)
 1940	    )
 1941	->  D=true
 1942	;   D=false
 1943	).
 1944perform(exit, []) :-
 1945	write(exit),
 1946	nl,
 1947	current_state([at(A, B), facing(C)]),
 1948	retract(current_state([at(A, B), facing(C)])),
 1949	assertz(current_state([])).
 1950perform(grab, []) :-
 1951	write(grab),
 1952	nl.
 1953perform(shoot, [F]) :-
 1954	write(shoot),
 1955	nl,
 1956	current_state([at(A, B), facing(C)]),
 1957	wumpus(D, E),
 1958	(   in_direction(A, B, C, D, E),
 1959	    F=true
 1960	;   F=false
 1961	).
 1962perform(go, [L, K, F]) :-
 1963	write(go),
 1964	nl,
 1965	current_state([at(A, B), facing(C)]),
 1966	retract(current_state([at(A, B), facing(C)])),
 1967	(   C=1
 1968	->  D is A,
 1969	    E is B+1
 1970	;   C=3
 1971	->  D is A,
 1972	    E is B+ -1
 1973	;   C=2
 1974	->  D is A+1,
 1975	    E is B
 1976	;   C=4
 1977	->  D is A+ -1,
 1978	    E is B
 1979	),
 1980	assertz(current_state([at(D, E), facing(C)])),
 1981	(   gold(D, E)
 1982	->  F=true
 1983	;   F=false
 1984	),
 1985	G is D+1,
 1986	I is D+ -1,
 1987	H is E+1,
 1988	J is E+ -1,
 1989	(   (   wumpus(G, E)
 1990	    ;   wumpus(D, H)
 1991	    ;   wumpus(I, E)
 1992	    ;   wumpus(D, J)
 1993	    )
 1994	->  K=true
 1995	;   K=false
 1996	),
 1997	(   (   pit(G, E)
 1998	    ;   pit(D, H)
 1999	    ;   pit(I, E)
 2000	    ;   pit(D, J)
 2001	    )
 2002	->  L=true
 2003	;   L=false
 2004	).
 2005
 2006:- dynamic visited/2. 2007
 2008
 2009copy_fluent(A, D, E, F) :-
 2010	term_variables(A, B),
 2011	bound_free(B, [], _, C),
 2012	copy_term_vars(C, [A, D], [E, F]).
 2013
 2014xdim(10).
 2015
 2016cancel___2__0__0__1([], A, B, C) :-
 2017	cancel___2__1(A, B, C).
 2018cancel___2__0__0__1([A|M], D, C, F) :-
 2019	(   A=suspension(_, active, _, _, _, _, E, B),
 2020	    B==C,
 2021	    \+ D\=E,
 2022	    'chr debug_event'(try([A],
 2023				  [F],
 2024				  \+D\=G,
 2025				  true))
 2026	->  'chr debug_event'(apply([A],
 2027				    [F],
 2028				    \+D\=G,
 2029				    true)),
 2030	    'chr debug_event'(remove(A)),
 2031	    A=suspension(_, _, _, _, _, not_holds, H, I),
 2032	    setarg(2, A, removed),
 2033	    term_variables(term(H, I), L),
 2034	    nb_getval('$chr_store_global_list_user____not_holds___2', J),
 2035	    'chr sbag_del_element'(J, A, K),
 2036	    b_setval('$chr_store_global_list_user____not_holds___2', K),
 2037	    detach_not_holds___2(L, A),
 2038	    setarg(2, F, active),
 2039	    (   F=suspension(_, active, _, _, _, _, _, _)
 2040	    ->  setarg(2, F, inactive),
 2041		cancel___2__0__0__1(M, D, C, F)
 2042	    ;   true
 2043	    )
 2044	;   cancel___2__0__0__1(M, D, C, F)
 2045	).
 2046
 2047variable(A) :-
 2048	nb_setval(A, []).
 2049
 2050:- dynamic expand_answer/2. 2051:- multifile expand_answer/2. 2052
 2053expand_answer(A, B) :-
 2054	toplevel_variables:expand_answer(A, B).
 2055
 2056explore(A, B, C, F, G, I) :-
 2057	adjacent(A, B, C, D, E),
 2058	\+ member([D, E], F),
 2059	knows_not(pit(D, E), G),
 2060	(   knows_not(wumpus(D, E), G)
 2061	;   knows(dead, G)
 2062	),
 2063	turn_to(C, G, H),
 2064	execute(go, H, I).
 2065
 2066attach_all_holds___3([], _).
 2067attach_all_holds___3([A|T], J) :-
 2068	(   get_attr(A, user, B)
 2069	->  B=v(C, D, E, F, G, H, I, K, L, M, N, O, P, Q),
 2070	    (   C/\64=:=64
 2071	    ->  R=v(C, D, E, F, G, H, I, [J|K], L, M, N, O, P, Q)
 2072	    ;   S is C\/64,
 2073		R=v(S, D, E, F, G, H, I, [J], L, M, N, O, P, Q)
 2074	    ),
 2075	    put_attr(A, user, R)
 2076	;   put_attr(A,
 2077		     user,
 2078		     v(64, [], [], [], [], [], [], [J], [], [], [], [], [], []))
 2079	),
 2080	attach_all_holds___3(T, J).
 2081
 2082:- dynamic prolog_event_hook/1. 2083:- multifile prolog_event_hook/1. 2084
 2085
 2086cancelled(A, B) :-
 2087	C=suspension(D, active, _, 0, user:cancelled___2__0(A, B, C), cancelled, A, B),
 2088	term_variables(term(A, B), F),
 2089	'chr gen_id'(D),
 2090	nb_getval('$chr_store_global_list_user____cancelled___2', E),
 2091	b_setval('$chr_store_global_list_user____cancelled___2',
 2092		 [C|E]),
 2093	attach_cancelled___2(F, C),
 2094	setarg(2, C, inactive),
 2095	'chr debug_event'(insert(cancelled(A, B)#C)),
 2096	(   'chr debug_event'(call(C)),
 2097	    cancelled___2__0(A, B, C)
 2098	;   'chr debug_event'(fail(C)), !,
 2099	    fail
 2100	),
 2101	(   'chr debug_event'(exit(C))
 2102	;   'chr debug_event'(redo(C)),
 2103	    fail
 2104	).
 2105
 2106attach_or_holds___2([], _).
 2107attach_or_holds___2([A|T], G) :-
 2108	(   get_attr(A, user, B)
 2109	->  B=v(C, D, E, F, H, I, J, K, L, M, N, O, P, Q),
 2110	    (   C/\8=:=8
 2111	    ->  R=v(C, D, E, F, [G|H], I, J, K, L, M, N, O, P, Q)
 2112	    ;   S is C\/8,
 2113		R=v(S, D, E, F, [G], I, J, K, L, M, N, O, P, Q)
 2114	    ),
 2115	    put_attr(A, user, R)
 2116	;   put_attr(A,
 2117		     user,
 2118		     v(8, [], [], [], [G], [], [], [], [], [], [], [], [], []))
 2119	),
 2120	attach_or_holds___2(T, G).
 2121
 2122attach_if_then_holds___3([], _).
 2123attach_if_then_holds___3([A|T], L) :-
 2124	(   get_attr(A, user, B)
 2125	->  B=v(C, D, E, F, G, H, I, J, K, M, N, O, P, Q),
 2126	    (   C/\256=:=256
 2127	    ->  R=v(C, D, E, F, G, H, I, J, K, [L|M], N, O, P, Q)
 2128	    ;   S is C\/256,
 2129		R=v(S, D, E, F, G, H, I, J, K, [L], N, O, P, Q)
 2130	    ),
 2131	    put_attr(A, user, R)
 2132	;   put_attr(A,
 2133		     user,
 2134		     v(256, [], [], [], [], [], [], [], [], [L], [], [], [], []))
 2135	),
 2136	attach_if_then_holds___3(T, L).
 2137
 2138:- dynamic current_state/1. 2139
 2140current_state([]).
 2141
 2142detach_not_holds_all___2([], _).
 2143detach_not_holds_all___2([A|T], E) :-
 2144	(   get_attr(A, user, B)
 2145	->  B=v(C, H, D, I, J, K, L, M, N, O, P, Q, R, S),
 2146	    (   C/\2=:=2
 2147	    ->  'chr sbag_del_element'(D, E, F),
 2148		(   F==[]
 2149		->  G is C/\ -3,
 2150		    (   G==0
 2151		    ->  del_attr(A, user)
 2152		    ;   put_attr(A,
 2153				 user,
 2154				 v(G,
 2155				   H,
 2156				   [],
 2157				   I,
 2158				   J,
 2159				   K,
 2160				   L,
 2161				   M,
 2162				   N,
 2163				   O,
 2164				   P,
 2165				   Q,
 2166				   R,
 2167				   S))
 2168		    )
 2169		;   put_attr(A,
 2170			     user,
 2171			     v(C,
 2172			       H,
 2173			       F,
 2174			       I,
 2175			       J,
 2176			       K,
 2177			       L,
 2178			       M,
 2179			       N,
 2180			       O,
 2181			       P,
 2182			       Q,
 2183			       R,
 2184			       S))
 2185		)
 2186	    ;   true
 2187	    )
 2188	;   true
 2189	),
 2190	detach_not_holds_all___2(T, E).
 2191
 2192member(A, [A|B], B).
 2193member(B, [A|C], [A|D]) :-
 2194	member(B, C, D).
 2195
 2196a_star(A, [B, H, _|I], F) :-
 2197	findall([C, D],
 2198		a_star_do(A, B, C, D),
 2199		E),
 2200	(   member([G, 0], E)
 2201	->  F=do(G, B)
 2202	;   insert_all(E, B, H, I, J),
 2203	    a_star(A, J, F)
 2204	).
 2205
 2206detach_all_holds___2([], _).
 2207detach_all_holds___2([A|T], E) :-
 2208	(   get_attr(A, user, B)
 2209	->  B=v(C, H, I, J, K, L, D, M, N, O, P, Q, R, S),
 2210	    (   C/\32=:=32
 2211	    ->  'chr sbag_del_element'(D, E, F),
 2212		(   F==[]
 2213		->  G is C/\ -33,
 2214		    (   G==0
 2215		    ->  del_attr(A, user)
 2216		    ;   put_attr(A,
 2217				 user,
 2218				 v(G,
 2219				   H,
 2220				   I,
 2221				   J,
 2222				   K,
 2223				   L,
 2224				   [],
 2225				   M,
 2226				   N,
 2227				   O,
 2228				   P,
 2229				   Q,
 2230				   R,
 2231				   S))
 2232		    )
 2233		;   put_attr(A,
 2234			     user,
 2235			     v(C,
 2236			       H,
 2237			       I,
 2238			       J,
 2239			       K,
 2240			       L,
 2241			       F,
 2242			       M,
 2243			       N,
 2244			       O,
 2245			       P,
 2246			       Q,
 2247			       R,
 2248			       S))
 2249		)
 2250	    ;   true
 2251	    )
 2252	;   true
 2253	),
 2254	detach_all_holds___2(T, E).
 2255
 2256attach_all_not_holds___3([], _).
 2257attach_all_not_holds___3([A|T], K) :-
 2258	(   get_attr(A, user, B)
 2259	->  B=v(C, D, E, F, G, H, I, J, L, M, N, O, P, Q),
 2260	    (   C/\128=:=128
 2261	    ->  R=v(C, D, E, F, G, H, I, J, [K|L], M, N, O, P, Q)
 2262	    ;   S is C\/128,
 2263		R=v(S, D, E, F, G, H, I, J, [K], M, N, O, P, Q)
 2264	    ),
 2265	    put_attr(A, user, R)
 2266	;   put_attr(A,
 2267		     user,
 2268		     v(128, [], [], [], [], [], [], [], [K], [], [], [], [], []))
 2269	),
 2270	attach_all_not_holds___3(T, K).
 2271
 2272detach_or_holds___2([], _).
 2273detach_or_holds___2([A|T], E) :-
 2274	(   get_attr(A, user, B)
 2275	->  B=v(C, H, I, J, D, K, L, M, N, O, P, Q, R, S),
 2276	    (   C/\8=:=8
 2277	    ->  'chr sbag_del_element'(D, E, F),
 2278		(   F==[]
 2279		->  G is C/\ -9,
 2280		    (   G==0
 2281		    ->  del_attr(A, user)
 2282		    ;   put_attr(A,
 2283				 user,
 2284				 v(G,
 2285				   H,
 2286				   I,
 2287				   J,
 2288				   [],
 2289				   K,
 2290				   L,
 2291				   M,
 2292				   N,
 2293				   O,
 2294				   P,
 2295				   Q,
 2296				   R,
 2297				   S))
 2298		    )
 2299		;   put_attr(A,
 2300			     user,
 2301			     v(C,
 2302			       H,
 2303			       I,
 2304			       J,
 2305			       F,
 2306			       K,
 2307			       L,
 2308			       M,
 2309			       N,
 2310			       O,
 2311			       P,
 2312			       Q,
 2313			       R,
 2314			       S))
 2315		)
 2316	    ;   true
 2317	    )
 2318	;   true
 2319	),
 2320	detach_or_holds___2(T, E).
 2321
 2322:- thread_local thread_message_hook/3. 2323:- dynamic thread_message_hook/3. 2324:- volatile thread_message_hook/3. 2325
 2326
 2327glitter_perception(B, C, A, D) :-
 2328	(   A=false,
 2329	    not_holds(gold(B, C), D)
 2330	;   A=true,
 2331	    holds(gold(B, C), D)
 2332	).
 2333
 2334duplicate_free(A) :-
 2335	B=suspension(C, active, _, 0, user:duplicate_free___1__0(A, B), duplicate_free, A),
 2336	term_variables(A, E),
 2337	'chr gen_id'(C),
 2338	nb_getval('$chr_store_global_list_user____duplicate_free___1', D),
 2339	b_setval('$chr_store_global_list_user____duplicate_free___1',
 2340		 [B|D]),
 2341	attach_duplicate_free___1(E, B),
 2342	setarg(2, B, inactive),
 2343	'chr debug_event'(insert(duplicate_free(A)#B)),
 2344	(   'chr debug_event'(call(B)),
 2345	    duplicate_free___1__0(A, B)
 2346	;   'chr debug_event'(fail(B)), !,
 2347	    fail
 2348	),
 2349	(   'chr debug_event'(exit(B))
 2350	;   'chr debug_event'(redo(B)),
 2351	    fail
 2352	).
 2353
 2354attribute_goals(_, A, A).
 2355
 2356cancel___2__1(E, A, F) :-
 2357	(   'chr newvia_1'(A, B)
 2358	->  get_attr(B, user, C),
 2359	    C=v(_, _, D, _, _, _, _, _, _, _, _, _, _, _)
 2360	;   nb_getval('$chr_store_global_list_user____not_holds_all___2',
 2361		      D)
 2362	), !,
 2363	cancel___2__1__0__2(D, E, A, F).
 2364cancel___2__1(A, B, C) :-
 2365	cancel___2__2(A, B, C).
 2366
 2367all_holds___3__1(G, H, A, O) :-
 2368	(   'chr newvia_1'(A, B)
 2369	->  get_attr(B, user, C),
 2370	    C=v(_, _, _, _, _, _, _, _, D, _, _, _, _, _)
 2371	;   nb_getval('$chr_store_global_list_user____all_not_holds___3',
 2372		      D)
 2373	),
 2374	'chr sbag_member'(E, D),
 2375	E=suspension(_, active, _, _, _, _, I, J, F),
 2376	F==A,
 2377	copy_fluent(G, H, K, M),
 2378	copy_fluent(I, J, L, N),
 2379	K=L,
 2380	call(M#/\N),
 2381	'chr debug_event'(try([O, E],
 2382			      [],
 2383			      (copy_fluent(G, H, P, R), copy_fluent(I, J, Q, S), P=Q, call(R#/\S)),
 2384			      false)), !,
 2385	'chr debug_event'(apply([O, E],
 2386				[],
 2387				(copy_fluent(G, H, P, R), copy_fluent(I, J, Q, S), P=Q, call(R#/\S)),
 2388				false)),
 2389	'chr debug_event'(remove(E)),
 2390	E=suspension(_, _, _, _, _, all_not_holds, T, U, V),
 2391	setarg(2, E, removed),
 2392	term_variables(term(T, U, V), Y),
 2393	nb_getval('$chr_store_global_list_user____all_not_holds___3', W),
 2394	'chr sbag_del_element'(W, E, X),
 2395	b_setval('$chr_store_global_list_user____all_not_holds___3', X),
 2396	detach_all_not_holds___3(Y, E),
 2397	'chr debug_event'(remove(O)),
 2398	O=suspension(_, _, _, _, _, all_holds, Z, A1, B1),
 2399	setarg(2, O, removed),
 2400	term_variables(term(Z, A1, B1), E1),
 2401	nb_getval('$chr_store_global_list_user____all_holds___3', C1),
 2402	'chr sbag_del_element'(C1, O, D1),
 2403	b_setval('$chr_store_global_list_user____all_holds___3', D1),
 2404	detach_all_holds___3(E1, O),
 2405	false.
 2406all_holds___3__1(E, F, A, G) :-
 2407	(   'chr newvia_1'(A, B)
 2408	->  get_attr(B, user, C),
 2409	    C=v(_, _, _, _, D, _, _, _, _, _, _, _, _, _)
 2410	;   nb_getval('$chr_store_global_list_user____or_holds___2', D)
 2411	), !,
 2412	all_holds___3__1__0__4(D, E, F, A, G).
 2413all_holds___3__1(A, B, C, D) :-
 2414	all_holds___3__2(A, B, C, D).
 2415
 2416getval(A, B) :-
 2417	nb_getval(A, B).
 2418
 2419:- multifile prolog_clause_name/2. 2420
 2421
 2422setval(A) :-
 2423	trace,
 2424	nb_setval(A, []).
 2425
 2426detach_if_then_or_holds___4([], _).
 2427detach_if_then_or_holds___4([A|T], E) :-
 2428	(   get_attr(A, user, B)
 2429	->  B=v(C, H, I, J, K, L, M, N, O, P, Q, D, R, S),
 2430	    (   C/\1024=:=1024
 2431	    ->  'chr sbag_del_element'(D, E, F),
 2432		(   F==[]
 2433		->  G is C/\ -1025,
 2434		    (   G==0
 2435		    ->  del_attr(A, user)
 2436		    ;   put_attr(A,
 2437				 user,
 2438				 v(G,
 2439				   H,
 2440				   I,
 2441				   J,
 2442				   K,
 2443				   L,
 2444				   M,
 2445				   N,
 2446				   O,
 2447				   P,
 2448				   Q,
 2449				   [],
 2450				   R,
 2451				   S))
 2452		    )
 2453		;   put_attr(A,
 2454			     user,
 2455			     v(C,
 2456			       H,
 2457			       I,
 2458			       J,
 2459			       K,
 2460			       L,
 2461			       M,
 2462			       N,
 2463			       O,
 2464			       P,
 2465			       Q,
 2466			       F,
 2467			       R,
 2468			       S))
 2469		)
 2470	    ;   true
 2471	    )
 2472	;   true
 2473	),
 2474	detach_if_then_or_holds___4(T, E).
 2475
 2476attach_or_holds___3([], _).
 2477attach_or_holds___3([A|T], H) :-
 2478	(   get_attr(A, user, B)
 2479	->  B=v(C, D, E, F, G, I, J, K, L, M, N, O, P, Q),
 2480	    (   C/\16=:=16
 2481	    ->  R=v(C, D, E, F, G, [H|I], J, K, L, M, N, O, P, Q)
 2482	    ;   S is C\/16,
 2483		R=v(S, D, E, F, G, [H], J, K, L, M, N, O, P, Q)
 2484	    ),
 2485	    put_attr(A, user, R)
 2486	;   put_attr(A,
 2487		     user,
 2488		     v(16, [], [], [], [], [H], [], [], [], [], [], [], [], []))
 2489	),
 2490	attach_or_holds___3(T, H).
 2491
 2492:- meta_predicate local (:).
 2493
 2494local _:A :-
 2495	call(A).
 2496
 2497:- dynamic pit/2. 2498
 2499pit(6, 4).
 2500pit(4, 10).
 2501pit(6, 8).
 2502pit(10, 5).
 2503pit(2, 12).
 2504pit(6, 4).
 2505pit(1, 6).
 2506pit(6, 10).
 2507pit(10, 5).
 2508pit(6, 1).
 2509pit(8, 8).
 2510pit(3, 6).
 2511
 2512if_then_holds(A, B, C) :-
 2513	D=suspension(E, active, _, 0, user:if_then_holds___3__0(A, B, C, D), if_then_holds, A, B, C),
 2514	'chr gen_id'(E),
 2515	nb_getval('$chr_store_global_list_user____if_then_holds___3', F),
 2516	b_setval('$chr_store_global_list_user____if_then_holds___3',
 2517		 [D|F]),
 2518	attach_if_then_holds___3([], D),
 2519	setarg(2, D, inactive),
 2520	'chr debug_event'(insert(if_then_holds(A, B, C)#D)),
 2521	(   'chr debug_event'(call(D)),
 2522	    if_then_holds___3__0(A, B, C, D)
 2523	;   'chr debug_event'(fail(D)), !,
 2524	    fail
 2525	),
 2526	(   'chr debug_event'(exit(D))
 2527	;   'chr debug_event'(redo(D)),
 2528	    fail
 2529	).
 2530
 2531or_holds___2__0(G, A, M) :-
 2532	(   'chr newvia_1'(A, B)
 2533	->  get_attr(B, user, C),
 2534	    C=v(_, _, _, _, _, _, _, D, _, _, _, _, _, _)
 2535	;   nb_getval('$chr_store_global_list_user____all_holds___3', D)
 2536	),
 2537	'chr sbag_member'(E, D),
 2538	E=suspension(_, active, _, _, _, _, H, I, F),
 2539	F==A,
 2540	member(K, G),
 2541	copy_fluent(H, I, J, L),
 2542	J=K,
 2543	\+ call(#\+L),
 2544	'chr debug_event'(try([M],
 2545			      [E],
 2546			      (member(O, G), copy_fluent(H, I, N, P), N=O, \+call(#\+P)),
 2547			      true)), !,
 2548	'chr debug_event'(apply([M],
 2549				[E],
 2550				(member(O, G), copy_fluent(H, I, N, P), N=O, \+call(#\+P)),
 2551				true)),
 2552	'chr debug_event'(remove(M)),
 2553	M=suspension(_, _, _, _, _, or_holds, Q, R),
 2554	setarg(2, M, removed),
 2555	term_variables(term(Q, R), U),
 2556	nb_getval('$chr_store_global_list_user____or_holds___2', S),
 2557	'chr sbag_del_element'(S, M, T),
 2558	b_setval('$chr_store_global_list_user____or_holds___2', T),
 2559	detach_or_holds___2(U, M).
 2560or_holds___2__0(G, A, M) :-
 2561	(   'chr newvia_1'(A, B)
 2562	->  get_attr(B, user, C),
 2563	    C=v(_, _, _, _, _, _, _, _, D, _, _, _, _, _)
 2564	;   nb_getval('$chr_store_global_list_user____all_not_holds___3',
 2565		      D)
 2566	),
 2567	'chr sbag_member'(E, D),
 2568	E=suspension(_, active, _, _, _, _, H, I, F),
 2569	F==A,
 2570	member(K, G, W),
 2571	copy_fluent(H, I, J, L),
 2572	J=K,
 2573	\+ call(#\+L),
 2574	'chr debug_event'(try([M],
 2575			      [E],
 2576			      (member(O, G, Q), copy_fluent(H, I, N, P), N=O, \+call(#\+P)),
 2577			      or_holds(Q, A))), !,
 2578	'chr debug_event'(apply([M],
 2579				[E],
 2580				(member(O, G, Q), copy_fluent(H, I, N, P), N=O, \+call(#\+P)),
 2581				or_holds(Q, A))),
 2582	'chr debug_event'(remove(M)),
 2583	M=suspension(_, _, _, _, _, or_holds, R, S),
 2584	setarg(2, M, removed),
 2585	term_variables(term(R, S), V),
 2586	nb_getval('$chr_store_global_list_user____or_holds___2', T),
 2587	'chr sbag_del_element'(T, M, U),
 2588	b_setval('$chr_store_global_list_user____or_holds___2', U),
 2589	detach_or_holds___2(V, M),
 2590	or_holds(W, A).
 2591or_holds___2__0(A, E, D) :-
 2592	nonvar(A),
 2593	A=[C|B],
 2594	B==[],
 2595	C\=eq(_, _),
 2596	C\=neq(_, _),
 2597	'chr debug_event'(try([D],
 2598			      [],
 2599			      (C\=eq(F, G), C\=neq(H, I)),
 2600			      holds(C, E))), !,
 2601	'chr debug_event'(apply([D],
 2602				[],
 2603				(C\=eq(F, G), C\=neq(H, I)),
 2604				holds(C, E))),
 2605	'chr debug_event'(remove(D)),
 2606	D=suspension(_, _, _, _, _, or_holds, J, K),
 2607	setarg(2, D, removed),
 2608	term_variables(term(J, K), N),
 2609	nb_getval('$chr_store_global_list_user____or_holds___2', L),
 2610	'chr sbag_del_element'(L, D, M),
 2611	b_setval('$chr_store_global_list_user____or_holds___2', M),
 2612	detach_or_holds___2(N, D),
 2613	holds(C, E).
 2614or_holds___2__0(A, _, C) :-
 2615	\+ ( member(B, A),
 2616	     B\=eq(_, _),
 2617	     B\=neq(_, _)
 2618	   ),
 2619	'chr debug_event'(try([C],
 2620			      [],
 2621			      \+ (member(D, A), D\=eq(F, G), D\=neq(H, I)),
 2622			      (or_and_eq(A, E), call(E)))), !,
 2623	'chr debug_event'(apply([C],
 2624				[],
 2625				\+ (member(D, A), D\=eq(F, G), D\=neq(H, I)),
 2626				(or_and_eq(A, E), call(E)))),
 2627	'chr debug_event'(remove(C)),
 2628	C=suspension(_, _, _, _, _, or_holds, J, K),
 2629	setarg(2, C, removed),
 2630	term_variables(term(J, K), N),
 2631	nb_getval('$chr_store_global_list_user____or_holds___2', L),
 2632	'chr sbag_del_element'(L, C, M),
 2633	b_setval('$chr_store_global_list_user____or_holds___2', M),
 2634	detach_or_holds___2(N, C),
 2635	or_and_eq(A, O),
 2636	call(O).
 2637or_holds___2__0(B, A, D) :-
 2638	A==[],
 2639	member(C, B, P),
 2640	C\=eq(_, _),
 2641	C\=neq(_, _),
 2642	'chr debug_event'(try([D],
 2643			      [],
 2644			      (member(E, B, F), E\=eq(G, H), E\=neq(I, J)),
 2645			      or_holds(F, []))), !,
 2646	'chr debug_event'(apply([D],
 2647				[],
 2648				(member(E, B, F), E\=eq(G, H), E\=neq(I, J)),
 2649				or_holds(F, []))),
 2650	'chr debug_event'(remove(D)),
 2651	D=suspension(_, _, _, _, _, or_holds, K, L),
 2652	setarg(2, D, removed),
 2653	term_variables(term(K, L), O),
 2654	nb_getval('$chr_store_global_list_user____or_holds___2', M),
 2655	'chr sbag_del_element'(M, D, N),
 2656	b_setval('$chr_store_global_list_user____or_holds___2', N),
 2657	detach_or_holds___2(O, D),
 2658	or_holds(P, []).
 2659or_holds___2__0(A, _, E) :-
 2660	member(eq(B, C), A),
 2661	or_neq(exists, B, C, D),
 2662	\+ call(D),
 2663	'chr debug_event'(try([E],
 2664			      [],
 2665			      (member(eq(F, G), A), or_neq(exists, F, G, H), \+call(H)),
 2666			      true)), !,
 2667	'chr debug_event'(apply([E],
 2668				[],
 2669				(member(eq(F, G), A), or_neq(exists, F, G, H), \+call(H)),
 2670				true)),
 2671	'chr debug_event'(remove(E)),
 2672	E=suspension(_, _, _, _, _, or_holds, I, J),
 2673	setarg(2, E, removed),
 2674	term_variables(term(I, J), M),
 2675	nb_getval('$chr_store_global_list_user____or_holds___2', K),
 2676	'chr sbag_del_element'(K, E, L),
 2677	b_setval('$chr_store_global_list_user____or_holds___2', L),
 2678	detach_or_holds___2(M, E).
 2679or_holds___2__0(A, _, E) :-
 2680	member(neq(B, C), A),
 2681	and_eq(B, C, D),
 2682	\+ call(D),
 2683	'chr debug_event'(try([E],
 2684			      [],
 2685			      (member(neq(F, G), A), and_eq(F, G, H), \+call(H)),
 2686			      true)), !,
 2687	'chr debug_event'(apply([E],
 2688				[],
 2689				(member(neq(F, G), A), and_eq(F, G, H), \+call(H)),
 2690				true)),
 2691	'chr debug_event'(remove(E)),
 2692	E=suspension(_, _, _, _, _, or_holds, I, J),
 2693	setarg(2, E, removed),
 2694	term_variables(term(I, J), M),
 2695	nb_getval('$chr_store_global_list_user____or_holds___2', K),
 2696	'chr sbag_del_element'(K, E, L),
 2697	b_setval('$chr_store_global_list_user____or_holds___2', L),
 2698	detach_or_holds___2(M, E).
 2699or_holds___2__0(A, J, E) :-
 2700	member(eq(B, C), A, P),
 2701	\+ ( and_eq(B, C, D),
 2702	     call(D)
 2703	   ),
 2704	'chr debug_event'(try([E],
 2705			      [],
 2706			      (member(eq(F, G), A, I), \+ (and_eq(F, G, H), call(H))),
 2707			      or_holds(I, J))), !,
 2708	'chr debug_event'(apply([E],
 2709				[],
 2710				(member(eq(F, G), A, I), \+ (and_eq(F, G, H), call(H))),
 2711				or_holds(I, J))),
 2712	'chr debug_event'(remove(E)),
 2713	E=suspension(_, _, _, _, _, or_holds, K, L),
 2714	setarg(2, E, removed),
 2715	term_variables(term(K, L), O),
 2716	nb_getval('$chr_store_global_list_user____or_holds___2', M),
 2717	'chr sbag_del_element'(M, E, N),
 2718	b_setval('$chr_store_global_list_user____or_holds___2', N),
 2719	detach_or_holds___2(O, E),
 2720	or_holds(P, J).
 2721or_holds___2__0(A, J, E) :-
 2722	member(neq(B, C), A, P),
 2723	\+ ( or_neq(exists, B, C, D),
 2724	     call(D)
 2725	   ),
 2726	'chr debug_event'(try([E],
 2727			      [],
 2728			      (member(neq(F, G), A, I), \+ (or_neq(exists, F, G, H), call(H))),
 2729			      or_holds(I, J))), !,
 2730	'chr debug_event'(apply([E],
 2731				[],
 2732				(member(neq(F, G), A, I), \+ (or_neq(exists, F, G, H), call(H))),
 2733				or_holds(I, J))),
 2734	'chr debug_event'(remove(E)),
 2735	E=suspension(_, _, _, _, _, or_holds, K, L),
 2736	setarg(2, E, removed),
 2737	term_variables(term(K, L), O),
 2738	nb_getval('$chr_store_global_list_user____or_holds___2', M),
 2739	'chr sbag_del_element'(M, E, N),
 2740	b_setval('$chr_store_global_list_user____or_holds___2', N),
 2741	detach_or_holds___2(O, E),
 2742	or_holds(P, J).
 2743or_holds___2__0(C, A, B) :-
 2744	nonvar(A),
 2745	A=[D|E],
 2746	'chr debug_event'(try([B],
 2747			      [],
 2748			      true,
 2749			      or_holds(C, [], [D|E]))), !,
 2750	'chr debug_event'(apply([B],
 2751				[],
 2752				true,
 2753				or_holds(C, [], [D|E]))),
 2754	'chr debug_event'(remove(B)),
 2755	B=suspension(_, _, _, _, _, or_holds, F, G),
 2756	setarg(2, B, removed),
 2757	term_variables(term(F, G), J),
 2758	nb_getval('$chr_store_global_list_user____or_holds___2', H),
 2759	'chr sbag_del_element'(H, B, I),
 2760	b_setval('$chr_store_global_list_user____or_holds___2', I),
 2761	detach_or_holds___2(J, B),
 2762	or_holds(C, [], [D|E]).
 2763or_holds___2__0(G, A, J) :-
 2764	(   'chr newvia_1'(A, B)
 2765	->  get_attr(B, user, C),
 2766	    C=v(_, D, _, _, _, _, _, _, _, _, _, _, _, _)
 2767	;   nb_getval('$chr_store_global_list_user____not_holds___2', D)
 2768	),
 2769	'chr sbag_member'(E, D),
 2770	E=suspension(_, active, _, _, _, _, H, F),
 2771	F==A,
 2772	member(I, G, R),
 2773	H==I,
 2774	'chr debug_event'(try([J],
 2775			      [E],
 2776			      (member(K, G, L), H==K),
 2777			      or_holds(L, A))), !,
 2778	'chr debug_event'(apply([J],
 2779				[E],
 2780				(member(K, G, L), H==K),
 2781				or_holds(L, A))),
 2782	'chr debug_event'(remove(J)),
 2783	J=suspension(_, _, _, _, _, or_holds, M, N),
 2784	setarg(2, J, removed),
 2785	term_variables(term(M, N), Q),
 2786	nb_getval('$chr_store_global_list_user____or_holds___2', O),
 2787	'chr sbag_del_element'(O, J, P),
 2788	b_setval('$chr_store_global_list_user____or_holds___2', P),
 2789	detach_or_holds___2(Q, J),
 2790	or_holds(R, A).
 2791or_holds___2__0(G, A, J) :-
 2792	(   'chr newvia_1'(A, B)
 2793	->  get_attr(B, user, C),
 2794	    C=v(_, _, _, _, _, _, _, _, _, _, _, _, D, _)
 2795	;   nb_getval('$chr_store_global_list_user____cancel___2', D)
 2796	),
 2797	'chr sbag_member'(E, D),
 2798	E=suspension(_, active, _, _, _, _, H, F),
 2799	F==A,
 2800	member(I, G),
 2801	\+ H\=I,
 2802	'chr debug_event'(try([J],
 2803			      [E],
 2804			      (member(K, G), \+H\=K),
 2805			      true)), !,
 2806	'chr debug_event'(apply([J],
 2807				[E],
 2808				(member(K, G), \+H\=K),
 2809				true)),
 2810	'chr debug_event'(remove(J)),
 2811	J=suspension(_, _, _, _, _, or_holds, L, M),
 2812	setarg(2, J, removed),
 2813	term_variables(term(L, M), P),
 2814	nb_getval('$chr_store_global_list_user____or_holds___2', N),
 2815	'chr sbag_del_element'(N, J, O),
 2816	b_setval('$chr_store_global_list_user____or_holds___2', O),
 2817	detach_or_holds___2(P, J).
 2818or_holds___2__0(_, _, A) :-
 2819	setarg(2, A, active).
 2820
 2821state_update(A, enter, B, [C, D, E]) :-
 2822	update(A, [at(1, 1), facing(1)], [], B),
 2823	breeze_perception(1, 1, C, B),
 2824	stench_perception(1, 1, D, B),
 2825	glitter_perception(1, 1, E, B).
 2826state_update(A, exit, C, []) :-
 2827	holds(facing(B), A),
 2828	update(A, [], [at(1, 1), facing(B)], C).
 2829state_update(A, turn, D, []) :-
 2830	holds(facing(B), A),
 2831	B#<4#/\C#=B+1#\/B#=4#/\C#=1,
 2832	update(A, [facing(C)], [facing(B)], D).
 2833state_update(A, grab, D, []) :-
 2834	holds(at(B, C), A),
 2835	update(A, [has(1)], [gold(B, C)], D).
 2836state_update(B, shoot, C, [A]) :-
 2837	(   A=true,
 2838	    update(B, [dead], [has(2)], C)
 2839	;   A=false,
 2840	    update(B, [], [has(2)], C)
 2841	).
 2842state_update(A, go, G, [H, I, J]) :-
 2843	holds(at(B, C), A),
 2844	holds(facing(D), A),
 2845	adjacent(B, C, D, E, F),
 2846	update(A, [at(E, F)], [at(B, C)], G),
 2847	breeze_perception(E, F, H, G),
 2848	stench_perception(E, F, I, G),
 2849	glitter_perception(E, F, J, G).
 2850
 2851:- dynamic prolog_file_type/2. 2852:- multifile prolog_file_type/2. 2853
 2854prolog_file_type(pl, prolog).
 2855prolog_file_type(prolog, prolog).
 2856prolog_file_type(qlf, prolog).
 2857prolog_file_type(qlf, qlf).
 2858prolog_file_type(A, executable) :-
 2859	system:current_prolog_flag(shared_object_extension, A).
 2860
 2861or_and_eq([], 0#\=0).
 2862or_and_eq([A|E], D#\/F) :-
 2863	(   A=eq(B, C)
 2864	->  and_eq(B, C, D)
 2865	;   A=neq(B, C),
 2866	    or_neq(exists, B, C, D)
 2867	),
 2868	or_and_eq(E, F).
 2869
 2870all_not_holds___3__2__0__5([], A, B, C, D) :-
 2871	all_not_holds___3__3(A, B, C, D).
 2872all_not_holds___3__2__0__5([A|S], D, E, C, I) :-
 2873	(   A=suspension(_, active, _, _, _, _, G, _, B),
 2874	    B==C,
 2875	    copy_fluent(D, E, F, H),
 2876	    F=G,
 2877	    \+ call(#\+H),
 2878	    'chr debug_event'(try([A],
 2879				  [I],
 2880				  (copy_fluent(D, E, J, K), J=L, \+call(#\+K)),
 2881				  true))
 2882	->  'chr debug_event'(apply([A],
 2883				    [I],
 2884				    (copy_fluent(D, E, J, K), J=L, \+call(#\+K)),
 2885				    true)),
 2886	    'chr debug_event'(remove(A)),
 2887	    A=suspension(_, _, _, _, _, if_then_or_holds, M, N, O),
 2888	    setarg(2, A, removed),
 2889	    term_variables(term(M, N, O), R),
 2890	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
 2891		      P),
 2892	    'chr sbag_del_element'(P, A, Q),
 2893	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
 2894		     Q),
 2895	    detach_if_then_or_holds___3(R, A),
 2896	    setarg(2, I, active),
 2897	    (   I=suspension(_, active, _, _, _, _, _, _, _)
 2898	    ->  setarg(2, I, inactive),
 2899		all_not_holds___3__2__0__5(S,
 2900					   D,
 2901					   E,
 2902					   C,
 2903					   I)
 2904	    ;   true
 2905	    )
 2906	;   all_not_holds___3__2__0__5(S,
 2907				       D,
 2908				       E,
 2909				       C,
 2910				       I)
 2911	).
 2912
 2913attach_not_holds_all___2([], _).
 2914attach_not_holds_all___2([A|T], E) :-
 2915	(   get_attr(A, user, B)
 2916	->  B=v(C, D, F, G, H, I, J, K, L, M, N, O, P, Q),
 2917	    (   C/\2=:=2
 2918	    ->  R=v(C, D, [E|F], G, H, I, J, K, L, M, N, O, P, Q)
 2919	    ;   S is C\/2,
 2920		R=v(S, D, [E], G, H, I, J, K, L, M, N, O, P, Q)
 2921	    ),
 2922	    put_attr(A, user, R)
 2923	;   put_attr(A,
 2924		     user,
 2925		     v(2, [], [E], [], [], [], [], [], [], [], [], [], [], []))
 2926	),
 2927	attach_not_holds_all___2(T, E).
 2928
 2929:- dynamic file_search_path/2. 2930:- multifile file_search_path/2. 2931
 2932file_search_path(library, 'c:/pf/swipl/library/dialect/hprolog') :-
 2933	hprolog:prolog_load_context(dialect, hprolog).
 2934file_search_path(library, A) :-
 2935	library_directory(A).
 2936file_search_path(swi, A) :-
 2937	system:current_prolog_flag(home, A).
 2938file_search_path(foreign, swi(B)) :-
 2939    system:
 2940    (   current_prolog_flag(arch, A),
 2941	atom_concat('lib/', A, B)
 2942    ).
 2943file_search_path(foreign, swi(A)) :-
 2944    system:
 2945    (   (   current_prolog_flag(windows, true)
 2946	->  A=bin
 2947	;   A=lib
 2948	)
 2949    ).
 2950file_search_path(path, C) :-
 2951    system:
 2952    (   getenv('PATH', A),
 2953	(   current_prolog_flag(windows, true)
 2954	->  atomic_list_concat(B, ;, A)
 2955	;   atomic_list_concat(B, :, A)
 2956	),
 2957	'$member'(C, B)
 2958    ).
 2959file_search_path(user_profile, app_preferences('.')).
 2960file_search_path(app_preferences, app_data('.')).
 2961file_search_path(app_data, B) :-
 2962    '$toplevel':
 2963    (   current_prolog_flag(windows, true),
 2964	catch(win_folder(appdata, A), _, fail),
 2965	atom_concat(A, '/SWI-Prolog', B),
 2966	(   exists_directory(B)
 2967	->  true
 2968	;   catch(make_directory(B), _, fail)
 2969	)
 2970    ).
 2971file_search_path(app_preferences, A) :-
 2972	'$toplevel':catch(expand_file_name(~, [A]), _, fail).
 2973file_search_path(autoload, library('.')).
 2974file_search_path(pack, app_data(pack)).
 2975file_search_path(pack, swi(pack)).
 2976file_search_path(library, A) :-
 2977	'$pack':pack_dir(_, prolog, A).
 2978file_search_path(foreign, A) :-
 2979	'$pack':pack_dir(_, foreign, A).
 2980file_search_path(pce, A) :-
 2981	link_xpce:pcehome_(A).
 2982file_search_path(library, pce('prolog/lib')).
 2983file_search_path(foreign, pce(B)) :-
 2984    link_xpce:
 2985    (   current_prolog_flag(arch, A),
 2986	atom_concat('lib/', A, B)
 2987    ).
 2988file_search_path(chr, library(chr)).
 2989
 2990all_not_holds___3__4(C, E, A, B) :-
 2991	nonvar(A),
 2992	A=[D|K],
 2993	'chr debug_event'(try([B],
 2994			      [],
 2995			      true,
 2996			      ((\+ (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)))), !,
 2997	'chr debug_event'(apply([B],
 2998				[],
 2999				true,
 3000				((\+ (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)))),
 3001	'chr debug_event'(remove(B)),
 3002	B=suspension(_, _, _, _, _, all_not_holds, L, M, N),
 3003	setarg(2, B, removed),
 3004	term_variables(term(L, M, N), Q),
 3005	nb_getval('$chr_store_global_list_user____all_not_holds___3', O),
 3006	'chr sbag_del_element'(O, B, P),
 3007	b_setval('$chr_store_global_list_user____all_not_holds___3', P),
 3008	detach_all_not_holds___3(Q, B),
 3009	(   \+ ( C=D,
 3010		 call(E)
 3011	       )
 3012	->  true
 3013	;   copy_fluent(C=D, E, R=S, U),
 3014	    R=S,
 3015	    eq(D, S, T),
 3016	    neq_all(C, D, V),
 3017	    call(T#/\ #\+U#\/V)
 3018	),
 3019	all_not_holds(C, E, K).
 3020all_not_holds___3__4(_, _, _, A) :-
 3021	setarg(2, A, active).
 3022
 3023eq(A, B, I) :-
 3024	functor(A, C, E),
 3025	functor(B, D, F),
 3026	(   C=D,
 3027	    E=F
 3028	->  A=..[_|G],
 3029	    B=..[_|H],
 3030	    and_eq(G, H, I)
 3031	;   I= (0#\=0)
 3032	).
 3033
 3034:- multifile prolog_list_goal/1. 3035
 3036
 3037no_of_random_pits(12).
 3038
 3039attach_cancelled___2([], _).
 3040attach_cancelled___2([A|T], P) :-
 3041	(   get_attr(A, user, B)
 3042	->  B=v(C, D, E, F, G, H, I, J, K, L, M, N, O, Q),
 3043	    (   C/\4096=:=4096
 3044	    ->  R=v(C, D, E, F, G, H, I, J, K, L, M, N, O, [P|Q])
 3045	    ;   S is C\/4096,
 3046		R=v(S, D, E, F, G, H, I, J, K, L, M, N, O, [P])
 3047	    ),
 3048	    put_attr(A, user, R)
 3049	;   put_attr(A,
 3050		     user,
 3051		     v(4096, [], [], [], [], [], [], [], [], [], [], [], [], [P]))
 3052	),
 3053	attach_cancelled___2(T, P).
 3054
 3055go_back(D, E, A, H) :-
 3056	holds(at(B, C), A),
 3057	adjacent(B, C, F, D, E),
 3058	turn_to(F, A, G),
 3059	execute(go, G, H).
 3060
 3061or_holds(A, B) :-
 3062	C=suspension(D, active, _, 0, user:or_holds___2__0(A, B, C), or_holds, A, B),
 3063	term_variables(term(A, B), F),
 3064	'chr gen_id'(D),
 3065	nb_getval('$chr_store_global_list_user____or_holds___2', E),
 3066	b_setval('$chr_store_global_list_user____or_holds___2',
 3067		 [C|E]),
 3068	attach_or_holds___2(F, C),
 3069	setarg(2, C, inactive),
 3070	'chr debug_event'(insert(or_holds(A, B)#C)),
 3071	(   'chr debug_event'(call(C)),
 3072	    or_holds___2__0(A, B, C)
 3073	;   'chr debug_event'(fail(C)), !,
 3074	    fail
 3075	),
 3076	(   'chr debug_event'(exit(C))
 3077	;   'chr debug_event'(redo(C)),
 3078	    fail
 3079	).
 3080
 3081:- dynamic message_hook/3. 3082:- multifile message_hook/3. 3083
 3084message_hook(trace_mode(A), _, _) :-
 3085    chr:
 3086    (   (   A==on
 3087	->  chr_trace
 3088	;   chr_notrace
 3089	),
 3090	fail
 3091    ).
 3092
 3093all_holds___3__3__0__6([], A, B, C, D) :-
 3094	all_holds___3__4(A, B, C, D).
 3095all_holds___3__3__0__6([A|U], E, F, C, J) :-
 3096	(   A=suspension(_, active, _, _, _, _, _, D, B),
 3097	    B==C,
 3098	    member(H, D),
 3099	    copy_fluent(E, F, G, I),
 3100	    G=H,
 3101	    \+ call(#\+I),
 3102	    'chr debug_event'(try([A],
 3103				  [J],
 3104				  (member(L, N), copy_fluent(E, F, K, M), K=L, \+call(#\+M)),
 3105				  true))
 3106	->  'chr debug_event'(apply([A],
 3107				    [J],
 3108				    (member(L, N), copy_fluent(E, F, K, M), K=L, \+call(#\+M)),
 3109				    true)),
 3110	    'chr debug_event'(remove(A)),
 3111	    A=suspension(_, _, _, _, _, if_then_or_holds, O, P, Q),
 3112	    setarg(2, A, removed),
 3113	    term_variables(term(O, P, Q), T),
 3114	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
 3115		      R),
 3116	    'chr sbag_del_element'(R, A, S),
 3117	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
 3118		     S),
 3119	    detach_if_then_or_holds___3(T, A),
 3120	    setarg(2, J, active),
 3121	    (   J=suspension(_, active, _, _, _, _, _, _, _)
 3122	    ->  setarg(2, J, inactive),
 3123		all_holds___3__3__0__6(U,
 3124				       E,
 3125				       F,
 3126				       C,
 3127				       J)
 3128	    ;   true
 3129	    )
 3130	;   all_holds___3__3__0__6(U, E, F, C, J)
 3131	).
 3132
 3133cancel___2__5(A, B, I) :-
 3134	(   'chr newvia_2'(A, B, C)
 3135	->  get_attr(C, user, D),
 3136	    D=v(_, _, _, _, _, _, _, _, _, _, _, _, _, E)
 3137	;   nb_getval('$chr_store_global_list_user____cancelled___2', E)
 3138	),
 3139	'chr sbag_member'(F, E),
 3140	F=suspension(_, active, _, _, _, _, G, H),
 3141	G==A,
 3142	H==B,
 3143	'chr debug_event'(try([I, F], [], true, true)), !,
 3144	'chr debug_event'(apply([I, F], [], true, true)),
 3145	'chr debug_event'(remove(F)),
 3146	F=suspension(_, _, _, _, _, cancelled, J, K),
 3147	setarg(2, F, removed),
 3148	term_variables(term(J, K), N),
 3149	nb_getval('$chr_store_global_list_user____cancelled___2', L),
 3150	'chr sbag_del_element'(L, F, M),
 3151	b_setval('$chr_store_global_list_user____cancelled___2', M),
 3152	detach_cancelled___2(N, F),
 3153	'chr debug_event'(remove(I)),
 3154	I=suspension(_, _, _, _, _, cancel, O, P),
 3155	setarg(2, I, removed),
 3156	term_variables(term(O, P), S),
 3157	nb_getval('$chr_store_global_list_user____cancel___2', Q),
 3158	'chr sbag_del_element'(Q, I, R),
 3159	b_setval('$chr_store_global_list_user____cancel___2', R),
 3160	detach_cancel___2(S, I).
 3161cancel___2__5(_, _, A) :-
 3162	setarg(2, A, active).
 3163
 3164all_holds(A, B, C) :-
 3165	D=suspension(E, active, t, 0, user:all_holds___3__0(A, B, C, D), all_holds, A, B, C),
 3166	term_variables(term(A, B, C), G),
 3167	'chr gen_id'(E),
 3168	nb_getval('$chr_store_global_list_user____all_holds___3', F),
 3169	b_setval('$chr_store_global_list_user____all_holds___3',
 3170		 [D|F]),
 3171	attach_all_holds___3(G, D),
 3172	setarg(2, D, inactive),
 3173	'chr debug_event'(insert(all_holds(A, B, C)#D)),
 3174	(   'chr debug_event'(call(D)),
 3175	    all_holds___3__0(A, B, C, D)
 3176	;   'chr debug_event'(fail(D)), !,
 3177	    fail
 3178	),
 3179	(   'chr debug_event'(exit(D))
 3180	;   'chr debug_event'(redo(D)),
 3181	    fail
 3182	).
 3183
 3184stench_perception(A, F, K, L) :-
 3185	(   integer(B)
 3186	->  (   var(A+1)
 3187	    ->  A+1 is B
 3188	    ;   integer(A)
 3189	    ->  B=:=A+1
 3190	    ;   C is B,
 3191		clpfd:clpfd_equal(C, A+1)
 3192	    )
 3193	;   integer(A)
 3194	->  (   var(B)
 3195	    ->  B is A+1
 3196	    ;   C is A+1,
 3197		clpfd:clpfd_equal(B, C)
 3198	    )
 3199	;   clpfd:clpfd_equal(B, A+1)
 3200	),
 3201	(   integer(D)
 3202	->  (   var(A-1)
 3203	    ->  A-1 is D
 3204	    ;   integer(A)
 3205	    ->  D=:=A-1
 3206	    ;   E is D,
 3207		clpfd:clpfd_equal(E, A-1)
 3208	    )
 3209	;   integer(A)
 3210	->  (   var(D)
 3211	    ->  D is A-1
 3212	    ;   E is A+ -1,
 3213		clpfd:clpfd_equal(D, E)
 3214	    )
 3215	;   clpfd:clpfd_equal(D, A-1)
 3216	),
 3217	(   integer(G)
 3218	->  (   var(F+1)
 3219	    ->  F+1 is G
 3220	    ;   integer(F)
 3221	    ->  G=:=F+1
 3222	    ;   H is G,
 3223		clpfd:clpfd_equal(H, F+1)
 3224	    )
 3225	;   integer(F)
 3226	->  (   var(G)
 3227	    ->  G is F+1
 3228	    ;   H is F+1,
 3229		clpfd:clpfd_equal(G, H)
 3230	    )
 3231	;   clpfd:clpfd_equal(G, F+1)
 3232	),
 3233	(   integer(I)
 3234	->  (   var(F-1)
 3235	    ->  F-1 is I
 3236	    ;   integer(F)
 3237	    ->  I=:=F-1
 3238	    ;   J is I,
 3239		clpfd:clpfd_equal(J, F-1)
 3240	    )
 3241	;   integer(F)
 3242	->  (   var(I)
 3243	    ->  I is F-1
 3244	    ;   J is F+ -1,
 3245		clpfd:clpfd_equal(I, J)
 3246	    )
 3247	;   clpfd:clpfd_equal(I, F-1)
 3248	),
 3249	(   K=false,
 3250	    not_holds(wumpus(B, F), L),
 3251	    not_holds(wumpus(D, F), L),
 3252	    not_holds(wumpus(A, G), L),
 3253	    not_holds(wumpus(A, I), L)
 3254	;   K=true,
 3255	    or_holds(
 3256		     [ wumpus(B, F),
 3257		       wumpus(A, G),
 3258		       wumpus(D, F),
 3259		       wumpus(A, I)
 3260		     ],
 3261		     L)
 3262	).
 3263
 3264setval(A, B) :-
 3265	nb_setval(A, B).
 3266
 3267cancel___2__3__0__4([], A, B, C) :-
 3268	cancel___2__4(A, B, C).
 3269cancel___2__3__0__4([A|N], D, C, F) :-
 3270	(   A=suspension(_, active, _, _, _, _, E, _, B),
 3271	    B==C,
 3272	    \+ D\=E,
 3273	    'chr debug_event'(try([A],
 3274				  [F],
 3275				  \+D\=G,
 3276				  true))
 3277	->  'chr debug_event'(apply([A],
 3278				    [F],
 3279				    \+D\=G,
 3280				    true)),
 3281	    'chr debug_event'(remove(A)),
 3282	    A=suspension(_, _, _, _, _, if_then_or_holds, H, I, J),
 3283	    setarg(2, A, removed),
 3284	    term_variables(term(H, I, J), M),
 3285	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
 3286		      K),
 3287	    'chr sbag_del_element'(K, A, L),
 3288	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
 3289		     L),
 3290	    detach_if_then_or_holds___3(M, A),
 3291	    setarg(2, F, active),
 3292	    (   F=suspension(_, active, _, _, _, _, _, _)
 3293	    ->  setarg(2, F, inactive),
 3294		cancel___2__3__0__4(N, D, C, F)
 3295	    ;   true
 3296	    )
 3297	;   cancel___2__3__0__4(N, D, C, F)
 3298	).
 3299
 3300:- multifile prolog_predicate_name/2. 3301
 3302
 3303type_prolog(swi).
 3304
 3305or_holds___3__0(A, G, B, C) :-
 3306	nonvar(A),
 3307	A=[D|F],
 3308	nonvar(B),
 3309	B=[E|H],
 3310	'chr debug_event'(try([C],
 3311			      [],
 3312			      true,
 3313			      (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])))), !,
 3314	'chr debug_event'(apply([C],
 3315				[],
 3316				true,
 3317				(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])))),
 3318	'chr debug_event'(remove(C)),
 3319	C=suspension(_, _, _, _, _, or_holds, M, _, N),
 3320	setarg(2, C, removed),
 3321	term_variables(M, R, O),
 3322	term_variables(N, O),
 3323	nb_getval('$chr_store_global_list_user____or_holds___3', P),
 3324	'chr sbag_del_element'(P, C, Q),
 3325	b_setval('$chr_store_global_list_user____or_holds___3', Q),
 3326	detach_or_holds___3(R, C),
 3327	(   D==E
 3328	->  true
 3329	;   D\=E
 3330	->  or_holds(F, [D|G], [E|H])
 3331	;   D=..[_|S],
 3332	    E=..[_|T],
 3333	    or_holds(F,
 3334		     [eq(S, T), D|G],
 3335		     [E|H])
 3336	).
 3337or_holds___3__0(A, D, B, C) :-
 3338	A==[],
 3339	nonvar(B),
 3340	B=[_|E],
 3341	'chr debug_event'(try([C], [], true, or_holds(D, E))), !,
 3342	'chr debug_event'(apply([C], [], true, or_holds(D, E))),
 3343	'chr debug_event'(remove(C)),
 3344	C=suspension(_, _, _, _, _, or_holds, F, _, G),
 3345	setarg(2, C, removed),
 3346	term_variables(F, K, H),
 3347	term_variables(G, H),
 3348	nb_getval('$chr_store_global_list_user____or_holds___3', I),
 3349	'chr sbag_del_element'(I, C, J),
 3350	b_setval('$chr_store_global_list_user____or_holds___3', J),
 3351	detach_or_holds___3(K, C),
 3352	or_holds(D, E).
 3353or_holds___3__0(_, _, _, A) :-
 3354	setarg(2, A, active).
 3355
 3356:- dynamic wumpus/2. 3357
 3358wumpus(8, 3).
 3359
 3360:- multifile message_property/2. 3361
 3362
 3363complex_action(do(C, A), B, E) :-
 3364	execute(A, B, D),
 3365	execute(C, D, E).
 3366complex_action(go_to(D, E), A, H) :-
 3367	holds(at(B, C), A),
 3368	adjacent(B, C, F, D, E),
 3369	turn_to(F, A, G),
 3370	execute(go, G, H).
 3371
 3372attach_duplicate_free___1([], _).
 3373attach_duplicate_free___1([A|T], F) :-
 3374	(   get_attr(A, user, B)
 3375	->  B=v(C, D, E, G, H, I, J, K, L, M, N, O, P, Q),
 3376	    (   C/\4=:=4
 3377	    ->  R=v(C, D, E, [F|G], H, I, J, K, L, M, N, O, P, Q)
 3378	    ;   S is C\/4,
 3379		R=v(S, D, E, [F], H, I, J, K, L, M, N, O, P, Q)
 3380	    ),
 3381	    put_attr(A, user, R)
 3382	;   put_attr(A,
 3383		     user,
 3384		     v(4, [], [], [F], [], [], [], [], [], [], [], [], [], []))
 3385	),
 3386	attach_duplicate_free___1(T, F).
 3387
 3388neq_all(A, B, C) :-
 3389	or_neq_c(forall, A, B, C).
 3390
 3391all_not_holds___3__3(E, F, A, G) :-
 3392	(   'chr newvia_1'(A, B)
 3393	->  get_attr(B, user, C),
 3394	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
 3395	;   nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
 3396		      D)
 3397	), !,
 3398	all_not_holds___3__3__0__6(D, E, F, A, G).
 3399all_not_holds___3__3(A, B, C, D) :-
 3400	all_not_holds___3__4(A, B, C, D).
 3401
 3402not_holds_all___2__0(B, C, A) :-
 3403	'chr debug_event'(try([A],
 3404			      [],
 3405			      true,
 3406			      all_not_holds(B, 0#=0, C))), !,
 3407	'chr debug_event'(apply([A],
 3408				[],
 3409				true,
 3410				all_not_holds(B, 0#=0, C))),
 3411	'chr debug_event'(remove(A)),
 3412	A=suspension(_, _, _, _, _, not_holds_all, D, E),
 3413	setarg(2, A, removed),
 3414	term_variables(term(D, E), H),
 3415	nb_getval('$chr_store_global_list_user____not_holds_all___2', F),
 3416	'chr sbag_del_element'(F, A, G),
 3417	b_setval('$chr_store_global_list_user____not_holds_all___2', G),
 3418	detach_not_holds_all___2(H, A),
 3419	all_not_holds(B, 0#=0, C).
 3420not_holds_all___2__0(H, A, I) :-
 3421	(   'chr newvia_1'(A, B)
 3422	->  get_attr(B, user, C),
 3423	    C=v(_, _, _, _, _, _, _, _, _, _, _, _, D, _)
 3424	;   nb_getval('$chr_store_global_list_user____cancel___2', D)
 3425	),
 3426	'chr sbag_member'(E, D),
 3427	E=suspension(_, active, _, _, _, _, G, F),
 3428	F==A,
 3429	\+ G\=H,
 3430	'chr debug_event'(try([I], [E], \+G\=H, true)), !,
 3431	'chr debug_event'(apply([I], [E], \+G\=H, true)),
 3432	'chr debug_event'(remove(I)),
 3433	I=suspension(_, _, _, _, _, not_holds_all, J, K),
 3434	setarg(2, I, removed),
 3435	term_variables(term(J, K), N),
 3436	nb_getval('$chr_store_global_list_user____not_holds_all___2', L),
 3437	'chr sbag_del_element'(L, I, M),
 3438	b_setval('$chr_store_global_list_user____not_holds_all___2', M),
 3439	detach_not_holds_all___2(N, I).
 3440not_holds_all___2__0(_, _, A) :-
 3441	setarg(2, A, active).
 3442
 3443:- dynamic prolog_load_file/2. 3444:- multifile prolog_load_file/2. 3445
 3446
 3447all_holds___3__4(_, _, _, A) :-
 3448	setarg(2, A, active).
 3449
 3450:- dynamic exception/3. 3451:- multifile exception/3. 3452
 3453exception(undefined_global_variable, A, retry) :-
 3454    chr_runtime:
 3455    (   chr_runtime_global_variable(A),
 3456	chr_init
 3457    ).
 3458exception(undefined_global_variable, A, retry) :-
 3459    chr_runtime:
 3460    (   chr_runtime_debug_global_variable(A),
 3461	chr_debug_init
 3462    ).
 3463exception(undefined_global_variable, A, retry) :-
 3464    guard_entailment:
 3465    (   '$chr_prolog_global_variable'(A),
 3466	'$chr_initialization'
 3467    ).
 3468exception(undefined_global_variable, A, retry) :-
 3469    chr_translate:
 3470    (   '$chr_prolog_global_variable'(A),
 3471	'$chr_initialization'
 3472    ).
 3473exception(undefined_global_variable, A, retry) :-
 3474    user:
 3475    (   '$chr_prolog_global_variable'(A),
 3476	'$chr_initialization'
 3477    ).
 3478exception(undefined_global_variable, A, retry) :-
 3479    clpfd:
 3480    (   make_clpfd_var(A), !
 3481    ).
 3482
 3483attach_not_holds___2([], _).
 3484attach_not_holds___2([A|T], D) :-
 3485	(   get_attr(A, user, B)
 3486	->  B=v(C, E, F, G, H, I, J, K, L, M, N, O, P, Q),
 3487	    (   C/\1=:=1
 3488	    ->  R=v(C, [D|E], F, G, H, I, J, K, L, M, N, O, P, Q)
 3489	    ;   S is C\/1,
 3490		R=v(S, [D], F, G, H, I, J, K, L, M, N, O, P, Q)
 3491	    ),
 3492	    put_attr(A, user, R)
 3493	;   put_attr(A,
 3494		     user,
 3495		     v(1, [D], [], [], [], [], [], [], [], [], [], [], [], []))
 3496	),
 3497	attach_not_holds___2(T, D).
 3498
 3499is_predicate(A/B) :-
 3500	current_predicate(A/B),
 3501	functor(C, A, B),
 3502	predicate_property(C, visible).
 3503
 3504variable(A, B) :-
 3505	nb_setval(A, B).
 3506
 3507or_neq_c(G, A, B, J) :-
 3508	functor(A, C, E),
 3509	functor(B, D, F),
 3510	(   C=D,
 3511	    E=F
 3512	->  A=..[_|H],
 3513	    B=..[_|I],
 3514	    or_neq(G, H, I, J)
 3515	;   J= (0#=0)
 3516	).
 3517
 3518all_not_holds___3__1__0__4([], A, B, C, D) :-
 3519	all_not_holds___3__2(A, B, C, D).
 3520all_not_holds___3__1__0__4([A|V], E, F, C, J) :-
 3521	(   A=suspension(_, active, _, _, _, _, D, B),
 3522	    B==C,
 3523	    member(H, D, U),
 3524	    copy_fluent(E, F, G, I),
 3525	    G=H,
 3526	    \+ call(#\+I),
 3527	    'chr debug_event'(try([A],
 3528				  [J],
 3529				  (member(L, O, N), copy_fluent(E, F, K, M), K=L, \+call(#\+M)),
 3530				  or_holds(N, C)))
 3531	->  'chr debug_event'(apply([A],
 3532				    [J],
 3533				    (member(L, O, N), copy_fluent(E, F, K, M), K=L, \+call(#\+M)),
 3534				    or_holds(N, C))),
 3535	    'chr debug_event'(remove(A)),
 3536	    A=suspension(_, _, _, _, _, or_holds, P, Q),
 3537	    setarg(2, A, removed),
 3538	    term_variables(term(P, Q), T),
 3539	    nb_getval('$chr_store_global_list_user____or_holds___2', R),
 3540	    'chr sbag_del_element'(R, A, S),
 3541	    b_setval('$chr_store_global_list_user____or_holds___2', S),
 3542	    detach_or_holds___2(T, A),
 3543	    setarg(2, J, active),
 3544	    or_holds(U, C),
 3545	    (   J=suspension(_, active, _, _, _, _, _, _, _)
 3546	    ->  setarg(2, J, inactive),
 3547		all_not_holds___3__1__0__4(V,
 3548					   E,
 3549					   F,
 3550					   C,
 3551					   J)
 3552	    ;   true
 3553	    )
 3554	;   all_not_holds___3__1__0__4(V,
 3555				       E,
 3556				       F,
 3557				       C,
 3558				       J)
 3559	).
 3560
 3561duplicate_free___1__0(A, B) :-
 3562	nonvar(A),
 3563	A=[C|D],
 3564	'chr debug_event'(try([B],
 3565			      [],
 3566			      true,
 3567			      (not_holds(C, D), duplicate_free(D)))), !,
 3568	'chr debug_event'(apply([B],
 3569				[],
 3570				true,
 3571				(not_holds(C, D), duplicate_free(D)))),
 3572	'chr debug_event'(remove(B)),
 3573	B=suspension(_, _, _, _, _, duplicate_free, E),
 3574	setarg(2, B, removed),
 3575	term_variables(E, H),
 3576	nb_getval('$chr_store_global_list_user____duplicate_free___1', F),
 3577	'chr sbag_del_element'(F, B, G),
 3578	b_setval('$chr_store_global_list_user____duplicate_free___1', G),
 3579	detach_duplicate_free___1(H, B),
 3580	not_holds(C, D),
 3581	duplicate_free(D).
 3582duplicate_free___1__0(A, B) :-
 3583	A==[],
 3584	'chr debug_event'(try([B], [], true, true)), !,
 3585	'chr debug_event'(apply([B], [], true, true)),
 3586	'chr debug_event'(remove(B)),
 3587	B=suspension(_, _, _, _, _, duplicate_free, C),
 3588	setarg(2, B, removed),
 3589	term_variables(C, F),
 3590	nb_getval('$chr_store_global_list_user____duplicate_free___1', D),
 3591	'chr sbag_del_element'(D, B, E),
 3592	b_setval('$chr_store_global_list_user____duplicate_free___1', E),
 3593	detach_duplicate_free___1(F, B).
 3594duplicate_free___1__0(_, A) :-
 3595	setarg(2, A, active).
 3596
 3597init(A) :-
 3598	A=[has(2), wumpus(D, E)|F],
 3599	xdim(B),
 3600	ydim(C),
 3601	H is B+1,
 3602	G is C+1,
 3603	D in 1..B,
 3604	E in 1..C,
 3605	not_holds(wumpus(1, 1), A),
 3606	not_holds_all(wumpus(_, _), F),
 3607	not_holds(dead, F),
 3608	not_holds(pit(1, 1), F),
 3609	not_holds_all(pit(_, 0), F),
 3610	not_holds_all(pit(_, G), F),
 3611	not_holds_all(pit(0, _), F),
 3612	not_holds_all(pit(H, _), F),
 3613	not_holds_all(at(_, _), F),
 3614	not_holds_all(facing(_), F),
 3615	duplicate_free(A).
 3616
 3617not_holds___2__4(H, A, I) :-
 3618	(   'chr newvia_1'(A, B)
 3619	->  get_attr(B, user, C),
 3620	    C=v(_, _, _, _, _, _, _, _, _, _, _, _, D, _)
 3621	;   nb_getval('$chr_store_global_list_user____cancel___2', D)
 3622	),
 3623	'chr sbag_member'(E, D),
 3624	E=suspension(_, active, _, _, _, _, G, F),
 3625	F==A,
 3626	\+ G\=H,
 3627	'chr debug_event'(try([I], [E], \+G\=H, true)), !,
 3628	'chr debug_event'(apply([I], [E], \+G\=H, true)),
 3629	'chr debug_event'(remove(I)),
 3630	I=suspension(_, _, _, _, _, not_holds, J, K),
 3631	setarg(2, I, removed),
 3632	term_variables(term(J, K), N),
 3633	nb_getval('$chr_store_global_list_user____not_holds___2', L),
 3634	'chr sbag_del_element'(L, I, M),
 3635	b_setval('$chr_store_global_list_user____not_holds___2', M),
 3636	detach_not_holds___2(N, I).
 3637not_holds___2__4(_, _, A) :-
 3638	setarg(2, A, active).
 3639
 3640backtrack(_, _, [], A) :-
 3641	execute(exit, A, _).
 3642backtrack(D, E, [A, B|F], C) :-
 3643	go_back(A, B, C, G),
 3644	main_loop(D, E, F, G).
 3645
 3646not_holds_all(A, B) :-
 3647	C=suspension(D, active, _, 0, user:not_holds_all___2__0(A, B, C), not_holds_all, A, B),
 3648	term_variables(term(A, B), F),
 3649	'chr gen_id'(D),
 3650	nb_getval('$chr_store_global_list_user____not_holds_all___2', E),
 3651	b_setval('$chr_store_global_list_user____not_holds_all___2',
 3652		 [C|E]),
 3653	attach_not_holds_all___2(F, C),
 3654	setarg(2, C, inactive),
 3655	'chr debug_event'(insert(not_holds_all(A, B)#C)),
 3656	(   'chr debug_event'(call(C)),
 3657	    not_holds_all___2__0(A, B, C)
 3658	;   'chr debug_event'(fail(C)), !,
 3659	    fail
 3660	),
 3661	(   'chr debug_event'(exit(C))
 3662	;   'chr debug_event'(redo(C)),
 3663	    fail
 3664	).
 3665
 3666all_holds___3__2__0__5([], A, B, C, D) :-
 3667	all_holds___3__3(A, B, C, D).
 3668all_holds___3__2__0__5([A|U], D, E, C, I) :-
 3669	(   A=suspension(_, active, _, _, _, _, G, T, B),
 3670	    B==C,
 3671	    copy_fluent(D, E, F, H),
 3672	    F=G,
 3673	    \+ call(#\+H),
 3674	    'chr debug_event'(try([A],
 3675				  [I],
 3676				  (copy_fluent(D, E, J, K), J=L, \+call(#\+K)),
 3677				  or_holds(M, C)))
 3678	->  'chr debug_event'(apply([A],
 3679				    [I],
 3680				    (copy_fluent(D, E, J, K), J=L, \+call(#\+K)),
 3681				    or_holds(M, C))),
 3682	    'chr debug_event'(remove(A)),
 3683	    A=suspension(_, _, _, _, _, if_then_or_holds, N, O, P),
 3684	    setarg(2, A, removed),
 3685	    term_variables(term(N, O, P), S),
 3686	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
 3687		      Q),
 3688	    'chr sbag_del_element'(Q, A, R),
 3689	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
 3690		     R),
 3691	    detach_if_then_or_holds___3(S, A),
 3692	    setarg(2, I, active),
 3693	    or_holds(T, C),
 3694	    (   I=suspension(_, active, _, _, _, _, _, _, _)
 3695	    ->  setarg(2, I, inactive),
 3696		all_holds___3__2__0__5(U,
 3697				       D,
 3698				       E,
 3699				       C,
 3700				       I)
 3701	    ;   true
 3702	    )
 3703	;   all_holds___3__2__0__5(U, D, E, C, I)
 3704	).
 3705
 3706detach_cancel___2([], _).
 3707detach_cancel___2([A|T], E) :-
 3708	(   get_attr(A, user, B)
 3709	->  B=v(C, H, I, J, K, L, M, N, O, P, Q, R, D, S),
 3710	    (   C/\2048=:=2048
 3711	    ->  'chr sbag_del_element'(D, E, F),
 3712		(   F==[]
 3713		->  G is C/\ -2049,
 3714		    (   G==0
 3715		    ->  del_attr(A, user)
 3716		    ;   put_attr(A,
 3717				 user,
 3718				 v(G,
 3719				   H,
 3720				   I,
 3721				   J,
 3722				   K,
 3723				   L,
 3724				   M,
 3725				   N,
 3726				   O,
 3727				   P,
 3728				   Q,
 3729				   R,
 3730				   [],
 3731				   S))
 3732		    )
 3733		;   put_attr(A,
 3734			     user,
 3735			     v(C,
 3736			       H,
 3737			       I,
 3738			       J,
 3739			       K,
 3740			       L,
 3741			       M,
 3742			       N,
 3743			       O,
 3744			       P,
 3745			       Q,
 3746			       R,
 3747			       F,
 3748			       S))
 3749		)
 3750	    ;   true
 3751	    )
 3752	;   true
 3753	),
 3754	detach_cancel___2(T, E).
 3755
 3756all_not_holds___3__0(I, J, A, O) :-
 3757	(   'chr newvia_1'(A, B)
 3758	->  get_attr(B, user, C),
 3759	    C=v(_, _, _, _, _, _, _, D, _, _, _, _, _, _)
 3760	;   nb_getval('$chr_store_global_list_user____all_holds___3', D)
 3761	),
 3762	'chr sbag_member'(E, D),
 3763	E=suspension(_, active, _, _, _, _, G, H, F),
 3764	F==A,
 3765	copy_fluent(G, H, K, M),
 3766	copy_fluent(I, J, L, N),
 3767	K=L,
 3768	call(M#/\N),
 3769	'chr debug_event'(try([E, O],
 3770			      [],
 3771			      (copy_fluent(G, H, P, R), copy_fluent(I, J, Q, S), P=Q, call(R#/\S)),
 3772			      false)), !,
 3773	'chr debug_event'(apply([E, O],
 3774				[],
 3775				(copy_fluent(G, H, P, R), copy_fluent(I, J, Q, S), P=Q, call(R#/\S)),
 3776				false)),
 3777	'chr debug_event'(remove(E)),
 3778	E=suspension(_, _, _, _, _, all_holds, T, U, V),
 3779	setarg(2, E, removed),
 3780	term_variables(term(T, U, V), Y),
 3781	nb_getval('$chr_store_global_list_user____all_holds___3', W),
 3782	'chr sbag_del_element'(W, E, X),
 3783	b_setval('$chr_store_global_list_user____all_holds___3', X),
 3784	detach_all_holds___3(Y, E),
 3785	'chr debug_event'(remove(O)),
 3786	O=suspension(_, _, _, _, _, all_not_holds, Z, A1, B1),
 3787	setarg(2, O, removed),
 3788	term_variables(term(Z, A1, B1), E1),
 3789	nb_getval('$chr_store_global_list_user____all_not_holds___3', C1),
 3790	'chr sbag_del_element'(C1, O, D1),
 3791	b_setval('$chr_store_global_list_user____all_not_holds___3', D1),
 3792	detach_all_not_holds___3(E1, O),
 3793	false.
 3794all_not_holds___3__0(_, _, A, B) :-
 3795	A==[],
 3796	'chr debug_event'(try([B], [], true, true)), !,
 3797	'chr debug_event'(apply([B], [], true, true)),
 3798	'chr debug_event'(remove(B)),
 3799	B=suspension(_, _, _, _, _, all_not_holds, C, D, E),
 3800	setarg(2, B, removed),
 3801	term_variables(term(C, D, E), H),
 3802	nb_getval('$chr_store_global_list_user____all_not_holds___3', F),
 3803	'chr sbag_del_element'(F, B, G),
 3804	b_setval('$chr_store_global_list_user____all_not_holds___3', G),
 3805	detach_all_not_holds___3(H, B).
 3806all_not_holds___3__0(E, F, A, G) :-
 3807	(   'chr newvia_1'(A, B)
 3808	->  get_attr(B, user, C),
 3809	    C=v(_, D, _, _, _, _, _, _, _, _, _, _, _, _)
 3810	;   nb_getval('$chr_store_global_list_user____not_holds___2', D)
 3811	), !,
 3812	all_not_holds___3__0__0__3(D, E, F, A, G).
 3813all_not_holds___3__0(A, B, C, D) :-
 3814	all_not_holds___3__1(A, B, C, D).
 3815
 3816not_holds___2__1(J, A, L) :-
 3817	(   'chr newvia_1'(A, B)
 3818	->  get_attr(B, user, C),
 3819	    C=v(_, _, _, _, _, _, _, _, D, _, _, _, _, _)
 3820	;   nb_getval('$chr_store_global_list_user____all_not_holds___3',
 3821		      D)
 3822	),
 3823	'chr sbag_member'(E, D),
 3824	E=suspension(_, active, _, _, _, _, G, H, F),
 3825	F==A,
 3826	copy_fluent(G, H, I, K),
 3827	I=J,
 3828	\+ call(#\+K),
 3829	'chr debug_event'(try([L],
 3830			      [E],
 3831			      (copy_fluent(G, H, M, N), M=J, \+call(#\+N)),
 3832			      true)), !,
 3833	'chr debug_event'(apply([L],
 3834				[E],
 3835				(copy_fluent(G, H, M, N), M=J, \+call(#\+N)),
 3836				true)),
 3837	'chr debug_event'(remove(L)),
 3838	L=suspension(_, _, _, _, _, not_holds, O, P),
 3839	setarg(2, L, removed),
 3840	term_variables(term(O, P), S),
 3841	nb_getval('$chr_store_global_list_user____not_holds___2', Q),
 3842	'chr sbag_del_element'(Q, L, R),
 3843	b_setval('$chr_store_global_list_user____not_holds___2', R),
 3844	detach_not_holds___2(S, L).
 3845not_holds___2__1(E, A, F) :-
 3846	(   'chr newvia_1'(A, B)
 3847	->  get_attr(B, user, C),
 3848	    C=v(_, _, _, _, D, _, _, _, _, _, _, _, _, _)
 3849	;   nb_getval('$chr_store_global_list_user____or_holds___2', D)
 3850	), !,
 3851	not_holds___2__1__0__5(D, E, A, F).
 3852not_holds___2__1(A, B, C) :-
 3853	not_holds___2__2(A, B, C).
 3854
 3855cancel___2__4(E, A, F) :-
 3856	(   'chr newvia_1'(A, B)
 3857	->  get_attr(B, user, C),
 3858	    C=v(_, _, _, _, _, _, _, _, _, _, D, _, _, _)
 3859	;   nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
 3860		      D)
 3861	), !,
 3862	cancel___2__4__0__5(D, E, A, F).
 3863cancel___2__4(A, B, C) :-
 3864	cancel___2__5(A, B, C).
 3865
 3866not_holds___2__2__0__6([], A, B, C) :-
 3867	not_holds___2__3(A, B, C).
 3868not_holds___2__2__0__6([A|N], D, C, F) :-
 3869	(   A=suspension(_, active, _, _, _, _, E, _, B),
 3870	    B==C,
 3871	    D==E,
 3872	    'chr debug_event'(try([A], [F], D==G, true))
 3873	->  'chr debug_event'(apply([A], [F], D==G, true)),
 3874	    'chr debug_event'(remove(A)),
 3875	    A=suspension(_, _, _, _, _, if_then_or_holds, H, I, J),
 3876	    setarg(2, A, removed),
 3877	    term_variables(term(H, I, J), M),
 3878	    nb_getval('$chr_store_global_list_user____if_then_or_holds___3',
 3879		      K),
 3880	    'chr sbag_del_element'(K, A, L),
 3881	    b_setval('$chr_store_global_list_user____if_then_or_holds___3',
 3882		     L),
 3883	    detach_if_then_or_holds___3(M, A),
 3884	    setarg(2, F, active),
 3885	    (   F=suspension(_, active, _, _, _, _, _, _)
 3886	    ->  setarg(2, F, inactive),
 3887		not_holds___2__2__0__6(N, D, C, F)
 3888	    ;   true
 3889	    )
 3890	;   not_holds___2__2__0__6(N, D, C, F)
 3891	).
 3892
 3893detach_not_holds___2([], _).
 3894detach_not_holds___2([A|T], E) :-
 3895	(   get_attr(A, user, B)
 3896	->  B=v(C, D, H, I, J, K, L, M, N, O, P, Q, R, S),
 3897	    (   C/\1=:=1
 3898	    ->  'chr sbag_del_element'(D, E, F),
 3899		(   F==[]
 3900		->  G is C/\ -2,
 3901		    (   G==0
 3902		    ->  del_attr(A, user)
 3903		    ;   put_attr(A,
 3904				 user,
 3905				 v(G,
 3906				   [],
 3907				   H,
 3908				   I,
 3909				   J,
 3910				   K,
 3911				   L,
 3912				   M,
 3913				   N,
 3914				   O,
 3915				   P,
 3916				   Q,
 3917				   R,
 3918				   S))
 3919		    )
 3920		;   put_attr(A,
 3921			     user,
 3922			     v(C,
 3923			       F,
 3924			       H,
 3925			       I,
 3926			       J,
 3927			       K,
 3928			       L,
 3929			       M,
 3930			       N,
 3931			       O,
 3932			       P,
 3933			       Q,
 3934			       R,
 3935			       S))
 3936		)
 3937	    ;   true
 3938	    )
 3939	;   true
 3940	),
 3941	detach_not_holds___2(T, E).
 3942
 3943#\+A :-
 3944	#\A.
 3945
 3946detach_all_not_holds___3([], _).
 3947detach_all_not_holds___3([A|T], E) :-
 3948	(   get_attr(A, user, B)
 3949	->  B=v(C, H, I, J, K, L, M, N, D, O, P, Q, R, S),
 3950	    (   C/\128=:=128
 3951	    ->  'chr sbag_del_element'(D, E, F),
 3952		(   F==[]
 3953		->  G is C/\ -129,
 3954		    (   G==0
 3955		    ->  del_attr(A, user)
 3956		    ;   put_attr(A,
 3957				 user,
 3958				 v(G,
 3959				   H,
 3960				   I,
 3961				   J,
 3962				   K,
 3963				   L,
 3964				   M,
 3965				   N,
 3966				   [],
 3967				   O,
 3968				   P,
 3969				   Q,
 3970				   R,
 3971				   S))
 3972		    )
 3973		;   put_attr(A,
 3974			     user,
 3975			     v(C,
 3976			       H,
 3977			       I,
 3978			       J,
 3979			       K,
 3980			       L,
 3981			       M,
 3982			       N,
 3983			       F,
 3984			       O,
 3985			       P,
 3986			       Q,
 3987			       R,
 3988			       S))
 3989		)
 3990	    ;   true
 3991	    )
 3992	;   true
 3993	),
 3994	detach_all_not_holds___3(T, E).
 3995
 3996cancel___2__2__0__3([], A, B, C) :-
 3997	cancel___2__3(A, B, C).
 3998cancel___2__2__0__3([A|O], E, C, G) :-
 3999	(   A=suspension(_, active, _, _, _, _, D, B),
 4000	    B==C,
 4001	    member(F, D),
 4002	    \+ E\=F,
 4003	    'chr debug_event'(try([A],
 4004				  [G],
 4005				  (member(H, I), \+E\=H),
 4006				  true))
 4007	->  'chr debug_event'(apply([A],
 4008				    [G],
 4009				    (member(H, I), \+E\=H),
 4010				    true)),
 4011	    'chr debug_event'(remove(A)),
 4012	    A=suspension(_, _, _, _, _, or_holds, J, K),
 4013	    setarg(2, A, removed),
 4014	    term_variables(term(J, K), N),
 4015	    nb_getval('$chr_store_global_list_user____or_holds___2', L),
 4016	    'chr sbag_del_element'(L, A, M),
 4017	    b_setval('$chr_store_global_list_user____or_holds___2', M),
 4018	    detach_or_holds___2(N, A),
 4019	    setarg(2, G, active),
 4020	    (   G=suspension(_, active, _, _, _, _, _, _)
 4021	    ->  setarg(2, G, inactive),
 4022		cancel___2__2__0__3(O, E, C, G)
 4023	    ;   true
 4024	    )
 4025	;   cancel___2__2__0__3(O, E, C, G)
 4026	).
 4027
 4028copy_term_vars(C, A, B) :-
 4029	copy_term(A, B),
 4030	term_variables(B, C).
 4031
 4032neq_all(A, B) :-
 4033	or_neq(forall, A, B).
 4034
 4035detach_or_holds___3([], _).
 4036detach_or_holds___3([A|T], E) :-
 4037	(   get_attr(A, user, B)
 4038	->  B=v(C, H, I, J, K, D, L, M, N, O, P, Q, R, S),
 4039	    (   C/\16=:=16
 4040	    ->  'chr sbag_del_element'(D, E, F),
 4041		(   F==[]
 4042		->  G is C/\ -17,
 4043		    (   G==0
 4044		    ->  del_attr(A, user)
 4045		    ;   put_attr(A,
 4046				 user,
 4047				 v(G,
 4048				   H,
 4049				   I,
 4050				   J,
 4051				   K,
 4052				   [],
 4053				   L,
 4054				   M,
 4055				   N,
 4056				   O,
 4057				   P,
 4058				   Q,
 4059				   R,
 4060				   S))
 4061		    )
 4062		;   put_attr(A,
 4063			     user,
 4064			     v(C,
 4065			       H,
 4066			       I,
 4067			       J,
 4068			       K,
 4069			       F,
 4070			       L,
 4071			       M,
 4072			       N,
 4073			       O,
 4074			       P,
 4075			       Q,
 4076			       R,
 4077			       S))
 4078		)
 4079	    ;   true
 4080	    )
 4081	;   true
 4082	),
 4083	detach_or_holds___3(T, E).
 4084
 4085attach_if_then_or_holds___4([], _).
 4086attach_if_then_or_holds___4([A|T], N) :-
 4087	(   get_attr(A, user, B)
 4088	->  B=v(C, D, E, F, G, H, I, J, K, L, M, O, P, Q),
 4089	    (   C/\1024=:=1024
 4090	    ->  R=v(C, D, E, F, G, H, I, J, K, L, M, [N|O], P, Q)
 4091	    ;   S is C\/1024,
 4092		R=v(S, D, E, F, G, H, I, J, K, L, M, [N], P, Q)
 4093	    ),
 4094	    put_attr(A, user, R)
 4095	;   put_attr(A,
 4096		     user,
 4097		     v(1024, [], [], [], [], [], [], [], [], [], [], [N], [], []))
 4098	),
 4099	attach_if_then_or_holds___4(T, N).
 4100
 4101:- dynamic gold/2. 4102
 4103gold(9, 8).
 4104
 4105in_direction(A, D, G, C, F) :-
 4106	xdim(B),
 4107	ydim(E),
 4108	A