2
    3action_agent_verb_subject_prep_object(Action, Agent, Verb, Thing, At, Thing2):-
    4  Action=..[Verb,Agent, Thing|Args], \+ verbatum_anon(Verb), !,
    5  preposition(_,At),
    6  append(_,[Thing2],Args).
    7
   28
   29
   30     67
   68
   72
   73security_of(_Agent, admin) :- true.     74security_of(_Agent, wizard) :- true.    75
.
   77
   78:- ensure_loaded('../poor_bugger.pl').   79:- ensure_loaded('adv_io.pl').   80:- ensure_loaded('adv_util.pl').   81:- ensure_loaded('adv_debug.pl').   82:- ensure_loaded('adv_edit.pl').   83
   84
   85
   98
   99:- op(900, xfx, props).  100:- op(300, fx, ~).  101
  102
  103istate([
  104    105
  106  h(exit(south), pantry, kitchen),   107  h(exit(north), kitchen, pantry),
  108  h(exit(down), pantry, basement),
  109  h(exit(up), basement, pantry),
  110  h(exit(south), kitchen, garden),
  111  h(exit(north), garden, kitchen),
  112  h(exit(east), kitchen, dining_room),
  113  h(exit(west), dining_room, kitchen),
  114  h(exit(north), dining_room, living_room),
  115  h(exit(east), living_room, dining_room),
  116  h(exit(south), living_room, kitchen),
  117  h(exit(west), kitchen, living_room),
  118                                           
  119  h(in, shelf, pantry),   120  h(on, lamp, table),
  121  h(in, floyd, pantry),
  122  h(held_by, wrench, floyd),
  123  h(in, rock, garden),
  124  h(in, mushroom, garden),
  125  h(in, player, kitchen),
  126  h(worn_by, watch, player),
  127  h(held_by, bag, player),
  128  h(in, coins, bag),
  129  h(in, table, kitchen),
  130  h(on, box, table),
  131  h(in, bowl, box),
  132  h(in, flour, bowl),
  133  h(in, shovel, basement),
  134  h(in, videocamera, living_room),
  135  h(in, screendoor, kitchen),
  136  h(in, screendoor, garden),
  137
  138    139
  140  character props [has_rel(held_by), has_rel(worn_by)],
  141
  142  props(floyd, [
  143    inherit(character),
  144    agent_type(autonomous),
  145    emits_light,
  146    volume(50), mass(200),   147    name('Floyd the robot'),
  148    nouns(robot),
  149    adjs(metallic),
  150    desc('Your classic robot: metallic with glowing red eyes, enthusiastic but not very clever.'),
  151    can_be(switched(OnOff), t),
  152    on,
  153      154    effect(switch(On), setprop($(self), state(on, t))),
  155    effect(switch(Off), setprop($(self), state(on, f))),
  156    end_of_list
  157  ]),
  158  props(player, [
  159    inherit(character),
  160    agent_type(console),
  161    volume(50),   162    mass(50),   163    can_eat
  164  ]),
  165
  166    167
  168  place props [can_be(move, f), default_rel(in)],
  169
  170  props(basement, [
  171    inherit(place),
  172    desc('This is a very dark basement.'),
  173    dark
  174  ]),
  175  props(dining_room, [inherit(place)]),
  176  props(garden,    [
  177    inherit(place),
  178      179    goto(Agent, Walk, up, 'You lack the ability to fly.'),
  180    effect(goto(Agent, Walk, _, north), getprop(screendoor, open)),
  181    oper(goto(Agent, Walk, _, north),
  182           183         precond(getprop(screendoor, open), ['you must open the door first']),
  184           185         body(inherited)
  186    ),
  187      188    cant_goto(Agent, Walk, 'The fence surrounding the garden is too tall and solid to pass.')
  189  ]),
  190  props(kitchen,   [inherit(place)]),
  191  props(living_room, [inherit(place)]),
  192  props(pantry, [
  193    inherit(place),
  194    nouns(closet),
  195    nominals(kitchen),
  196    desc('You\'re in a dark pantry.'),
  197    dark
  198  ]),
  199
  200    201
  202  props(bag, [
  203    default_rel(in),
  204    volume_capacity(10),
  205    dark
  206  ]),
  207  props(bowl, [
  208    default_rel(in),
  209    volume_capacity(2),
  210    breaks_into(shards),
  211    name('porcelain bowl'),
  212    desc('This is a modest glass cooking bowl with a yellow flower motif glazed into the outside surface.')
  213  ]),
  214  props(box, [
  215    default_rel(in),
  216    volume_capacity(15),
  217    breaks_into(splinters),
  218      219    closed(true),
  220      221    locked(fail),
  222    dark
  223  ]),
  224  coins props [shiny],
  225  flour props [edible],
  226  props(lamp, [
  227    name('shiny brass lamp'),
  228    nouns(light),
  229    nominals(brass),
  230    adjs(shiny),
  231    shiny,
  232    can_be(switched(OnOff), t),
  233    state(on, t),
  234    emits_light,
  235    effect(switch(On), setprop(Agent, emits_light)),
  236    effect(switch(Off), delprop(Agent, emits_light)),
  237    breaks_into(broken_lamp)
  238  ]),
  239  broken_lamp props [
  240    name('dented brass lamp'),
  241      242    nouns(light),
  243    nominals(brass),
  244    adjs(dented),
  245    can_be(switched(OnOff), t)
  246      247      248  ],
  249  mushroom props [
  250      251    name('speckled mushroom'),
  252    singular,
  253    nouns([mushroom, fungus, toadstool]),
  254    adjs([speckled]),
  255      256    initial('A speckled mushroom grows out of the sodden earth, on a long stalk.'),
  257      258    desc('The mushroom is capped with blotches, and you aren\'t at all sure it\'s not a toadstool.'),
  259    edible,
  260      261      262    before(eat, (random(100) =< 30, die('It was poisoned!'); 'yuck!')),
  263    after(take,
  264          (initial, 'You pick the mushroom, neatly cleaving its thin stalk.'))
  265  ],
  266  screendoor props [
  267    can_be(move, f),
  268      269    door_to(garden),
  270      271    closed(true)
  272  ],
  273  props(shelf , [default_rel(on), can_be(move, f)]),
  274  props(table , [default_rel(on), has_rel(under)]),
  275  wrench props [shiny],
  276  videocamera props [
  277    agent_type(recorder),
  278    can_be(switched(OnOff), t),
  279    effect(switch(On), setprop(Agent, on)),
  280    effect(switch(Off), delprop(Agent, on)),
  281    breaks_into(broken_videocam)
  282  ],
  283  broken_videocam props [can_be(switched(OnOff), t)],
  284
  285  end_of_list
  286]):- On=on, Off = off, OnOff = on, Agent= ($(self)).
  287      
  328
  331create_agent(Agent, AgentType, S0, S2) :-
  332    333    334  declare(perceptq(Agent, []), S0, S1),
  335    336  declare(memories(Agent, [
  337    timestamp(0),
  338    model([]),
  339    goals([]),
  340    todo([]),
  341    agent(Agent),
  342    agent_type(AgentType)
  343  ]), S1, S2).
  344
  358
  360select_always(Item, List, ListWithoutItem) :-
  361  select(Item, List, ListWithoutItem),
  362  !.
  363select_always(_Item, ListWithoutItem, ListWithoutItem).
  364
  369
  371declare(Fact, S0, S9) :- append([Fact], S0, S9).
  372undeclare(Fact, S0, S9)   :- select(Fact, S0, S9).
  373undeclare_always(Fact, S0, S9) :- select_always(Fact, S0, S9).
  374declared(Fact, S0) :- member(Fact, S0).
  375
  377getprop(Object, Prop, S0) :-
  378  declared(props(Object, PropList), S0),
  379  member(Prop, PropList).
  380getprop(Object, Prop, S0) :-
  381  declared(props(Object, PropList), S0),
  382  member(inherit(Delegate), PropList),
  383  getprop(Delegate, Prop, S0).
  384
  386setprop(Object, Prop, S0, S2) :-
  387  undeclare(props(Object, PropList), S0, S1),
  388  select_always(Prop, PropList, PropList2),
  389  append([Prop], PropList2, PropList3),
  390  declare(props(Object, PropList3), S1, S2).
  391setprop(Object, Prop, S0, S2) :-
  392  declare(props(Object, [Prop]), S0, S2).
  393
  395delprop(Object, Prop, S0, S2) :-
  396  undeclare(props(Object, PropList), S0, S1),
  397  select(Prop, PropList, NewPropList),
  398  declare(props(Object, NewPropList), S1, S2).
  399
  401queue_agent_percept(Agent, Event, S0, S2) :-
  402  select(perceptq(Agent, Queue), S0, S1),
  403  append(Queue, [Event], NewQueue),
  404  append([perceptq(Agent, NewQueue)], S1, S2).
  405
  406queue_event(Event, S0, S2) :-
  407  queue_agent_percept(player, Event, S0, S1),
  408  queue_agent_percept(floyd, Event, S1, S2).
  409
  410queue_local_percept(Agent, Event, Places, S0, S1) :-
  411  member(Where, Places),
  412  h(open_traverse, Agent, Where, S0),
  413  queue_agent_percept(Agent, Event, S0, S1).
  414queue_local_percept(_Agent, _Event, _Places, S0, S0).
  415
  416queue_local_event(Event, Places, S0, S2) :-
  417  queue_local_percept(player, Event, Places, S0, S1),
  418  queue_local_percept(floyd , Event, Places, S1, S2).
  419
  429
  463
  464capitalize([First|Rest], [Capped|Rest]) :-
  465  capitalize(First, Capped).
  466capitalize(Atom, Capitalized) :-
  467  atom(Atom),   468  downcase_atom(Atom, Lower),
  469  atom_chars(Lower, [First|Rest]),
  470  upcase_atom(First, Upper),
  471  atom_chars(Capitalized, [Upper|Rest]).
  472
  477compile_eng(Context, subj(Agent), Person) :-
  478  member(agent(Agent), Context),
  479  member(person(Person), Context).
  480compile_eng(Context, subj(Other), Compiled) :-
  481  compile_eng(Context, Other, Compiled).
  482compile_eng(Context, Agent, Person) :-
  483  member(agent(Agent), Context),
  484  member(person(Person), Context).
  485compile_eng(Context, person(Second, _Third), Compiled) :-
  486  member(subj(Agent), Context),
  487  member(agent(Agent), Context),
  488  compile_eng(Context, Second, Compiled).
  489compile_eng(Context, person(_Second, Third), Compiled) :-
  490  compile_eng(Context, Third, Compiled).
  491compile_eng(Context, cap(Eng), Compiled) :-
  492  compile_eng(Context, Eng, Lowercase),
  493  capitalize(Lowercase, Compiled).
  494compile_eng(_Context, silent(_Eng), '').
  495compile_eng(_Context, [], '').
  496compile_eng(Context, [First|Rest], [First2|Rest2]) :-
  497  compile_eng(Context, First, First2),
  498  compile_eng(Context, Rest, Rest2).
  499compile_eng(_Context, Atom, Atom).
  500
  501nospace(_, ', ').
  502nospace(_, ';').
  503nospace(_, ':').
  504nospace(_, '.').
  505nospace(_, '?').
  506nospace(_, '!').
  507nospace(_, '\'').
  508nospace('\'', _).
  509nospace(_, '"').
  510nospace('"', _).
  511nospace(_, Letter) :- system:char_type(Letter, space).
  512nospace(Letter, _) :- char_type(Letter, space).
  513
  514no_space_words('', _).
  515no_space_words(_, '').
  516no_space_words(W1, W2) :-
  517  atomic(W1),
  518  atomic(W2),
  519  atom_chars(W1, List),
  520  last(List, C1),
  521  atom_chars(W2, [C2|_]),
  522  nospace(C1, C2).
  523
  524insert_spaces([W], [W]).
  525insert_spaces([W1, W2|Tail1], [W1, W2|Tail2]) :-
  526  no_space_words(W1, W2),
  527  !,
  528  insert_spaces([W2|Tail1], [W2|Tail2]).
  529insert_spaces([W1, W2|Tail1], [W1, ' ', W3|Tail2]) :-
  530  insert_spaces([W2|Tail1], [W3|Tail2]).
  531insert_spaces([], []).
  532
  533make_atomic(Atom, Atom) :-
  534  atomic(Atom), !.
  535make_atomic(Term, Atom) :-
  536  term_to_atom(Term, Atom).
  537
  538eng2txt(Agent, Person, Eng, Text) :-
  539    540  findall(subj(Subject), call(findterm(subj(Subject), Eng)), Context),
  541    542  maplist(compile_eng([agent(Agent), person(Person)|Context]), Eng, Compiled),
  543    544  flatten(Compiled, FlatList),
  545    546  findall(Atom, (member(Term, FlatList), make_atomic(Term, Atom)), AtomList),
  547  findall(Atom2, (member(Atom2, AtomList), Atom2\=''), AtomList2),
  548    549  bugout('insert_spaces(~w)~n', [AtomList2], printer),
  550  insert_spaces(AtomList2, SpacedList),
  551    552  concat_atom(SpacedList, Text).
  553eng2txt(_Agent, _Person, Text, Text).
  554
  556
  557list2eng([], ['<nothing>']).
  558list2eng([Single], [Single]).
  559list2eng([Last2, Last1], [Last2, 'and', Last1]).
  560list2eng([Item|Items], [Item, ', '|Tail]) :-
  561  list2eng(Items, Tail).
  562
  563prop2eng( Obj, emits_light, ['The', Obj, 'is glowing.']).
  564prop2eng(_Obj, edible,     ['It looks tasty!']).
  565prop2eng(_Obj, breaks_into(_), ['It looks breaks_into.']).
  566prop2eng(_Obj, closed(true), ['It is closed.']).
  567prop2eng(_Obj, closed(fail), ['It is open.']).
  568prop2eng(_Obj, open(fail), ['It is closed.']).
  569prop2eng(_Obj, open(true), ['It is open.']).
  570prop2eng(_Obj, open,       ['It is open.']).
  571prop2eng(_Obj, closed,     ['It is closed.']).
  572prop2eng(_Obj, locked,     ['It is locked.']).
  573prop2eng(_Obj, shiny,      ['It\'s shiny!']).
  574prop2eng(_Obj, _Prop,      []).
  575
  576proplist2eng(_Obj, [], []).
  577proplist2eng(Obj, [Prop|Tail], Text) :-
  578  prop2eng(Obj, Prop, Text1),
  579  proplist2eng(Obj, Tail, Text2),
  580  append(Text1, Text2, Text).
  581
  582logical2eng(_CAgent, exits_are(At, Here, Exits), 
  583            [cap(At), 'the', subj(Here), ', exits are', ExitText, '.', '\n']) :-
  584  list2eng(Exits, ExitText).
  585
  586logical2eng(Agent, can_sense_from_here(Agent, At, Here, Sense, Nearby),
  587            ['From', At, cap(subj(Here)), cap(subj(Agent)), ',',  'can', person(Sense, es(Sense)), ':', SeeText, '.']) :-
  588  findall(X, (member(X, Nearby), X\=Agent), OtherNearby),
  589  list2eng(OtherNearby, SeeText).
  590
  591logical2eng(Agent, rel_to(held_by, Items),
  592            [cap(subj(Agent)), person(are, is), 'carrying:'|Text]) :-
  593  list2eng(Items, Text).
  594logical2eng(Agent, sense_childs(Agent, _Sense, _Parent, _At, []), []).
  595logical2eng(Agent, sense_childs(Agent, Sense, Parent, At, List),
  596            [cap(subj(Agent)), At, cap(subj(Parent)), person(Sense, es(Sense)), ':'|Text]) :-
  597  list2eng(List, Text).
  598logical2eng(_Agent, moved(What, From, At, To),
  599            [cap(subj(What)), 'moves from', From, 'to', At, To]).
  600logical2eng(_Agent, transformed(Before, After), [Before, 'turns into', After, .]).
  601logical2eng(_Agent, destroyed(Thing), [Thing, 'is destroyed.']).
  602logical2eng(Agent, sense_props(Agent, Sense, Object, PropList),
  603            [cap(subj(Agent)), person(Sense, es(Sense)), Desc, '.'|PropDesc] ) :-
  604  member(name(Desc), PropList),
  605  proplist2eng(Object, PropList, PropDesc).
  606logical2eng(Agent, sense_props(Agent, Sense, Object, PropList),
  607            [cap(subj(Agent)), person(Sense, es(Sense)), 'a', Object, '.'|PropDesc] ) :-
  608  proplist2eng(Object, PropList, PropDesc).
  609logical2eng(_Agent, say(Speaker, Eng), [cap(subj(Speaker)), ': "', Text, '"']) :-
  610  eng2txt(Speaker, 'I', Eng, Text).
  611logical2eng(_Agent, talk(Speaker, Audience, Eng),
  612    [cap(subj(Speaker)), 'says to', Audience, ', "', Text, '"']) :-
  613  eng2txt(Speaker, 'I', Eng, Text).
  614logical2eng(_Agent, time_passes, ['Time passes.']).
  615logical2eng(_Agent, failure(Action), ['Action failed:', Action]).
  616logical2eng(_Agent, Logical, ['percept:', Logical]).
  617
  618percept2txt(Agent, [_Logical, English|_], Text) :-
  619  eng2txt(Agent, you, English, Text).
  620percept2txt(Agent, [Logical|_], Text) :-
  621  logical2eng(Agent, Logical, Eng),
  622  eng2txt(Agent, you, Eng, Text).
  623
  624the(S0, Object, Text) :-
  625  getprop(Object, name(D), S0),
  626  atom_concat('the ', D, Text).
  627
  628an(S0, Object, Text) :-
  629  getprop(Object, name(D), S0),
  630  atom_concat('a ', D, Text).
  631
  632num(_Singular, Plural, [], Plural).
  633num(Singular, _Plural, [_One], Singular).
  634num(_Singular, Plural, [_One, _Two|_Or_More], Plural).
  635
  636expand_english(S0, the(Object), Text) :-
  637  the(S0, Object, Text).
  638expand_english(S0, an(Object), Text) :-
  639  an(S0, Object, Text).
  640expand_english(_State, num(Sing, Plur, List), Text) :-
  641  num(Sing, Plur, List, Text).
  642expand_english(_State, [], '').
  643expand_english(S0, [Term|Tail], [NewTerm|NewTail]) :-
  644  expand_english(S0, Term, NewTerm),
  645  expand_english(S0, Tail, NewTail).
  646expand_english(_State, Term, Term).
  647
  650subsetof(touch, touch).
  651subsetof(move, touch).
  652subsetof(drop, move).
  653subsetof(eat,  touch).
  654subsetof(hit,  touch).
  655subsetof(put,  drop).
  656subsetof(give, drop).
  657subsetof(take, move).
  658subsetof(throw, drop).
  659subsetof(open, touch).
  660subsetof(close, touch).
  661subsetof(lock, touch).
  662subsetof(unlock, touch). 
  663 
  664subsetof(examine, examine).
  665
  667psubsetof(A, B) :- subsetof(A, B).
  668psubsetof(A, C) :-
  669  subsetof(A, B),
  670  subsetof(B, C).
  671
  672anonmous_verb(Verb):-
  673 member(Verb, [agent, create, delprop, destroy, echo, quit, memory, model, path, properties, setprop, state, trace, notrace, whereami, whereis, whoami]).
  674
  675action_agent_thing(Action, Verb, Agent, Thing):-
  676  Action=..[Verb,Agent|Args], \+ anonmous_verb(Verb), !,
  677  (Args=[Thing]->true;Thing=_),!.
  678
  679action_agent_verb_subject_prep_object(Action, Agent, Verb, Thing, At, Thing2):-
  680  Action=..[Verb,Agent, Thing|Args], \+ anonmous_verb(Verb), !,
  681  preposition(_,At),
  682  append(_,[Thing2],Args).
  683
  684reason2eng(cant(sense(visually, _It)),      'You can''t see that here.').
  685reason2eng(cant(reach(_It)),    'You can''t reach it.').
  686reason2eng(cant(manipulate(self)), 'You can''t manipulate yourself like that.').
  687reason2eng(alreadyhave(It),     ['You already have the', It, '.']).
  688reason2eng(mustgetout(_It),     'You must get out/off it first.').
  689reason2eng(self_relation(_It),  'Can\'t put thing inside itself!').
  690reason2eng(moibeus_relation(_, _), 'Topological error!').
  691reason2eng(toodark,             'It''s too dark to see!').
  692reason2eng(mustdrop(_It),       'You will have to drop it first.').
  693reason2eng(can_be(_It, move, f),      'Sorry, it\'s immobile.').
  694reason2eng(cantdothat,          'Sorry, you can\'t do that.').
  695reason2eng(R, R).
  696
  697
  713
  720
  738
  740memorize(_Agent, Figment, M0, M1) :- append([Figment], M0, M1).
  741memorize_list(_Agent, FigmentList, M0, M1) :- append(FigmentList, M0, M1).
  742forget(_Agent, Figment, M0, M1) :- select(Figment, M0, M1).
  743forget_always(_Agent, Figment, M0, M1) :- select_always(Figment, M0, M1).
  746thought(_Agent, Figment, M) :- member(Figment, M).
  747
  748thought(X,Y):- thought(_,X,Y).
  749
  750in_model(_Knower, E, L):- in_model(E, L).
  751
  752in_model(E, L):- member(E, L).
  753in_model(E, L):- member(holds_at(E,_), L).
  754
  756
  757agent_thought_model(Agent,Model,List):- dmust((memberchk(agent(Agent),List), member(model(Model),List))).
  758
  760
  762update_relation(NewAt, Item, NewParent, Timestamp, M0, M2) :-
  763  select_always(holds_at(h(_At, Item, _Where)), M0, M1),
  764  append([holds_at(h(NewAt, Item, NewParent), Timestamp)], M1, M2).
  765
  767update_relations(_NewAt, [], _NewParent, _Timestamp, M, M).
  768update_relations(NewAt, [Item|Tail], NewParent, Timestamp, M0, M2) :-
  769  update_relation(NewAt, Item, NewParent, Timestamp, M0, M1),
  770  update_relations(NewAt, Tail, NewParent, Timestamp, M1, M2).
  771
  774update_exit(At, From, Timestamp, M0, M2) :-
  775  select( holds_at(h(At, From, To), _), M0, M1),
  776  append([holds_at(h(At, From, To), Timestamp)], M1, M2).
  777update_exit(At, From, Timestamp, M0, M1) :-
  778  append([holds_at(h(At, From, '<unexplored>'), Timestamp)], M0, M1).
  779
  780update_exit(At, From, To, Timestamp, M0, M2) :-
  781  select_always( holds_at(h(At, From, _To), _), M0, M1),
  782  append([holds_at(h(At, From, To), Timestamp)], M1, M2).
  783
  784update_exits([], _From, _T, M, M).
  785update_exits([Exit|Tail], From, Timestamp, M0, M2) :-
  786  update_exit(Exit, From, Timestamp, M0, M1),
  787  update_exits(Tail, From, Timestamp, M1, M2).
  788
  792
  798
  799update_model(Agent, rel_to(held_by, Objects), Timestamp, _Memory, M0, M1) :-
  800  update_relations(held_by, Objects, Agent, Timestamp, M0, M1).
  801update_model(Agent, sense_childs(Agent, _Sense, Object, At, Children), Timestamp, _Mem, M0, M1) :-
  802  update_relations(At, Children, Object, Timestamp, M0, M1).
  803update_model(Agent, sense_props(Agent, _Sense, Object, PropList), Stamp, _Mem, M0, M2) :-
  804  select_always(holds_at(props(Object, _),_), M0, M1),
  805  append([holds_at(props(Object, PropList), Stamp)], M1, M2).
  806update_model(_Agent, exits_are(_At, Here, Exits), Timestamp, _Mem, M0, M4) :-
  807    808  findall(exit(E), member(E, Exits), ExitRelations),
  809  update_exits(ExitRelations, Here, Timestamp, M0, M4).  810update_model(Agent, moved(Agent, There, At, Here), Timestamp, Mem, M0, M2) :-
  811    812  in_model(holds_at(t(_, Agent, There), _T0), M0),
  813    814    815  append(RecentMem, [did(goto(Agent, Walk, _AtGo, ExitName))|OlderMem], Mem),   816  \+ member(did(goto(Agent, Walk, _, _)), RecentMem),                 817  memberchk(timestamp(_T1), OlderMem),                 818    819    820  update_exit(exit(ExitName), There, Here, Timestamp, M0, M1),   821  update_relation(At, Agent, Here, Timestamp, M1, M2).   822update_model(_Agent, moved(Object, _From, At, To), Timestamp, _Mem, M0, M1) :-
  823  update_relation(At, Object, To, Timestamp, M0, M1).
  824update_model(_Agent, _Percept, _Timestamp, _Memory, M, M).
  825
  827update_model_all(_Agent, [], _Timestamp, _Memory, M, M).
  828update_model_all(Agent, [Percept|Tail], Timestamp, Memory, M0, M2) :-
  829  update_model(Agent, Percept, Timestamp, Memory, M0, M1),
  830  update_model_all(Agent, Tail, Timestamp, Memory, M1, M2).
  831
  832path2directions([Here, There], [goto(_Agent, walk, *, ExitName)], Model) :-
  833  in_model(h(exit(ExitName), Here, There), Model).
  834path2directions([Here, There], [goto(_Agent, walk, in, There)], Model) :-
  835  in_model(h(descended, Here, There), Model).
  836path2directions([Here, Next|Trail], [goto(_Agent, walk, *, ExitName)|Tail], Model) :-
  837  in_model(h(exit(ExitName), Here, Next), Model),
  838  path2directions([Next|Trail], Tail, Model).
  839path2directions([Here, Next|Trail], [goto(_Agent, walk, in, Next)|Tail], Model) :-
  840  in_model( h(descended, Here, Next), Model),
  841  path2directions([Next|Trail], Tail, Model).
  842
  843find_path1( [First|_Rest], Dest, First, _Model) :-
  844  First = [Dest|_].
  845find_path1([[Last|Trail]|Others], Dest, Route, Model) :-
  846  findall([Z, Last|Trail],
  847          (in_model(h(_At, Last, Z), Model), \+ member(Z, Trail)),
  848          List),
  849  append(Others, List, NewRoutes),
  850  find_path1(NewRoutes, Dest, Route, Model).
  851find_path( Start, Dest, Route, Model) :-
  852  find_path1( [[Start]], Dest, R, Model),
  853  reverse(R, RR),
  854  path2directions(RR, Route, Model).
  855
  857
  858precond_matches_effect(Cond, Cond).
  859
  860precond_matches_effects(path(Here, There), StartEffects) :-
  861  find_path(Here, There, _Route, StartEffects).
  862precond_matches_effects(exists(Object), StartEffects) :-
  863  in_model(h(_, Object, _), StartEffects)
  864  ;
  865  in_model(h(_, _, Object), StartEffects).
  866precond_matches_effects(_Agent, Cond, Effects) :-
  867  member(E, Effects),
  868  precond_matches_effect(Cond, E).
  869
  871
  872oper_act( goto(Agent, walk, *, ExitName),
  873     [ Here \= Agent, There \= Agent,
  874       h(in, Agent, Here),
  875       h(exit(ExitName), Here, There)],   876     [ h(in, Agent, There),
  877       ~h(in, Agent, Here)]).
  878oper_act( take(Agent, Thing),   879     [ Thing \= Agent, exists(Thing),
  880       There \= Agent,
  881       h(At, Thing, There),
  882       h(At, Agent, There)],
  883     [ h(held_by, Thing, Agent),
  884       ~h(At, Thing, There)]).
  885oper_act( take(Agent, Thing),   886     [ Thing \= Agent, exists(Thing),
  887       h(At, Thing, What),
  888       h(At, What, There),
  889       h(At, Agent, There) ],
  890     [ h(held_by, Thing, Agent),
  891       ~h(At, Thing, There)]) :- fail, extra.
  892oper_act( drop(Agent, Thing),
  893     [ Thing \= Agent, exists(Thing),
  894       h(held_by, Thing, Agent)],
  895     [ ~h(held_by, Thing, Agent)] ).
  896oper_act( talk(Agent, Player, [please, give, me, the, Thing]),
  897     [ Thing \= Agent, exists(Thing),
  898       h(held_by, Thing, Player),
  899       h(At, Player, Where),
  900       h(At, Agent, Where) ],
  901     [ h(held_by, Thing, Agent),
  902       ~h(held_by, Thing, Player)] ) :- extra.
  903oper_act( give(Agent, Thing, Recipient),
  904     [ Thing \= Agent, Recipient \= Agent,
  905       exists(Thing), exists(Recipient),
  906       Where \= Agent,
  907       h(held_by, Thing, Agent),
  908       h(in, Recipient, Where), exists(Where),
  909       h(in, Agent, Where)],
  910     [ h(held_by, Thing, Recipient),
  911       ~h(held_by, Thing, Agent)
  912     ] ).
  913oper_act( put(Agent, Thing, Relation, What),   914     [ Thing \= Agent, What \= Agent, Where \= Agent,
  915       Thing\=What, What\=Where, Thing\=Where,
  916       h(held_by, Thing, Agent), exists(Thing),
  917       h(in, What, Where), exists(What), exists(Where),
  918       h(in, Agent, Where)],
  919     [ h(Relation, Thing, What),
  920       ~h(held_by, Thing, Agent)] ).
  927
  929initial_operators(Agent, Operators) :-
  930  findall(oper(Agent, Action, Conds, Effects),
  931          oper_act( Action, Conds, Effects),
  932          Operators).
  933
  934precondition_matches_effect(Cond, Effect) :-
  935    936  Cond = Effect.   941precondition_matches_effects(Cond, Effects) :-
  942  member(E, Effects),
  943  precondition_matches_effect(Cond, E).
  944preconditions_match_effects([Cond|Tail], Effects) :-
  945  precondition_matches_effects(Cond, Effects),
  946  preconditions_match_effects(Tail, Effects).
  947
  950new_plan(CurrentState, GoalState, Plan) :-
  951  Plan = plan([step(start , oper( true, [], CurrentState)),
  952               step(finish, oper( true, GoalState, []))],
  953              [before(start, finish)],
  954              [],
  955              []).
  956
  957isbefore(I, J, Orderings) :-
  958  member(before(I, J), Orderings).
  962
  973
  974add_ordering(B, Orderings, Orderings) :-
  975  member(B, Orderings), !.
  976add_ordering(before(I, J), Order0, Order1) :-
  977  I \= J,
  978  \+ isbefore(J, I, Order0),
  979  add_ordering3(before(I, J), Order0, Order0, Order1).
  980add_ordering(B, Order0, Order0) :-
  981  once(pick_ordering(Order0, List)),
  982  bugout('  FAILED add_ordering ~w to ~w~n', [B, List], planner),
  983  fail.
  984
  986add_ordering3(before(I, J), [], OldOrderings, NewOrderings) :-
  987  union([before(I, J)], OldOrderings, NewOrderings).
  988add_ordering3(before(I, J), [before(J, K)|Rest], OldOrderings, NewOrderings) :-
  989  I \= K,
  990  union([before(J, K)], OldOrderings, Orderings1),
  991  add_ordering3(before(I, J), Rest, Orderings1, NewOrderings).
  992add_ordering3(before(I, J), [before(H, I)|Rest], OldOrderings, NewOrderings) :-
  993  H \= J,
  994  union([before(H, J)], OldOrderings, Orderings1),
  995  add_ordering3(before(I, J), Rest, Orderings1, NewOrderings).
  996add_ordering3(before(I, J), [before(H, K)|Rest], OldOrderings, NewOrderings) :-
  997  I \= K,
  998  H \= J,
  999  add_ordering3(before(I, J), Rest, OldOrderings, NewOrderings).
 1000
 1003insert(X, [], [X]).
 1004insert(A, [A|R], [A|R]).
 1005insert(A, [B|R], [B|R1]) :-
 1006   A \== B,
 1007   insert(A, R, R1).
 1008
 1009add_orderings([], Orderings, Orderings).
 1010add_orderings([B|Tail], Orderings, NewOrderings) :-
 1011  add_ordering(B, Orderings, Orderings2),
 1012  add_orderings(Tail, Orderings2, NewOrderings).
 1013
 1014del_ordering_node(I, [before(I, _)|Tail], Orderings) :-
 1015  del_ordering_node(I, Tail, Orderings).
 1016del_ordering_node(I, [before(_, I)|Tail], Orderings) :-
 1017  del_ordering_node(I, Tail, Orderings).
 1018del_ordering_node(I, [before(X, Y)|Tail], [before(X, Y)|Orderings]) :-
 1019  X \= I,
 1020  Y \= I,
 1021  del_ordering_node(I, Tail, Orderings).
 1022del_ordering_node(_I, [], []).
 1023
 1024ordering_nodes(Orderings, Nodes) :-
 1025  setof(Node,
 1026        Other^(isbefore(Node, Other, Orderings);isbefore(Other, Node, Orderings)),
 1027        Nodes).
 1028
 1029pick_ordering(Orderings, List) :-        
 1030  ordering_nodes(Orderings, Nodes),
 1031  pick_ordering(Orderings, Nodes, List).
 1032
 1033pick_ordering(Orderings, Nodes, [I|After]) :-
 1034  select(I, Nodes, RemainingNodes),
 1035  forall(member(J, RemainingNodes), \+ isbefore(J, I, Orderings) ),
 1036  pick_ordering(Orderings, RemainingNodes, After).
 1037pick_ordering(_Orderings, [], []).
 1038
 1039test_ordering :-
 1040  bugout('ORDERING TEST:~n', planner),
 1041  once(add_orderings(
 1042   [ before(start, finish),
 1043     before(start, x),
 1044     before(start, y), before(y, finish),
 1045     before(x, z),
 1046     before(z, finish)
 1047   ],
 1048   [],
 1049   Orderings)),
 1050  bugout('  ordering is ~w~n', [Orderings], planner),
 1051  pick_ordering(Orderings, List),
 1052  bugout('  picked ~w~n', [List], planner),
 1053  fail.
 1054test_ordering :- bugout('  END ORDERING TEST~n', planner).
 1055
 1056cond_is_achieved(step(J, _Oper), C, plan(Steps, Orderings, _, _)) :-
 1057  member(step(I, oper( _, _, Effects)), Steps),
 1058  precondition_matches_effects(C, Effects),
 1059  isbefore(I, J, Orderings),
 1060  bugout('      Cond ~w of step ~w is achieved!~n', [C, J], planner).
 1061cond_is_achieved(step(J, _Oper), C, plan(_Steps, _Orderings, _, _)) :-
 1062  bugout('      Cond ~w of step ~w is NOT achieved.~n', [C, J], planner),
 1063  !, fail.
 1064
 1067step_is_achieved(step(_J, oper( _, [], _)), _Plan).   1068step_is_achieved(step(J, oper( _, [C|Tail], _)), plan(Steps, Orderings, _, _)) :-
 1069  cond_is_achieved(step(J, _), C, plan(Steps, Orderings, _, _)),
 1070  step_is_achieved(step(J, oper( _, Tail, _)), plan(Steps, Orderings, _, _)).
 1071  
 1072all_steps_are_achieved([Step|Tail], Plan) :-
 1073  step_is_achieved(Step, Plan),
 1074  all_steps_are_achieved(Tail, Plan).
 1075all_steps_are_achieved([], _Plan).
 1076
 1077is_solution(plan(Steps, O, B, L)) :-
 1078  all_steps_are_achieved(Steps, plan(Steps, O, B, L)).
 1079
 1081operator_as_step(oper( Act, Cond, Effect), step(Id, oper( Act, Cond, Effect))) :-
 1082  Act =.. [Functor|_],
 1083  atom_concat(Functor, '_step_', Prefix),
 1084  gensym(Prefix, Id).
 1085
 1087operators_as_steps([], []).
 1088operators_as_steps([Oper | OpTail], [Step | StepTail]) :-
 1089  copy_term(Oper, FreshOper),  1090  operator_as_step(FreshOper, Step),
 1091  operators_as_steps(OpTail, StepTail).
 1092
 1093cond_as_goal(ID, Cond, goal(ID, Cond)).
 1094conds_as_goals(_, [], []).
 1095conds_as_goals(ID, [C|R], [G|T]) :-
 1096  cond_as_goal(ID, C, G),
 1097  conds_as_goals(ID, R, T).
 1098
 1099cond_equates(Cond0, Cond1) :- Cond0 = Cond1.
 1100cond_equates(h(X, Y, Z), h(X, Y, Z)).
 1101cond_equates(~(~(Cond0)), Cond1) :- cond_equates(Cond0, Cond1).
 1102cond_equates(Cond0, ~(~(Cond1))) :- cond_equates(Cond0, Cond1).
 1103cond_negates(~Cond0, Cond1) :- cond_equates(Cond0, Cond1).
 1104cond_negates(Cond0, ~Cond1) :- cond_equates(Cond0, Cond1).
 1105
 1108protect(causes(StepI, _Cond0, _StepJ), StepI, _Cond1, Order0, Order0) :-
 1109  !.  1110protect(causes(_StepI, _Cond0, StepJ), StepJ, _Cond1, Order0, Order0) :-
 1111  !.  1114protect(causes(_StepI, Cond0, _StepJ), _StepK, Cond1, Order0, Order0) :-
 1115  \+ cond_negates(Cond0, Cond1),
 1116  !.
 1117protect(causes(StepI, Cond0, StepJ), StepK, _Cond1, Order0, Order0) :-
 1118  bugout('  THREAT: ~w <> causes(~w, ~w, ~w)~n',
 1119         [StepK, StepI, Cond0, StepJ], planner),
 1120  fail.
 1121protect(causes(StepI, _Cond0, StepJ), StepK, _Cond1, Order0, Order1) :-
 1122   1123  add_ordering(before(StepK, StepI), Order0, Order1),
 1124  bugout('    RESOLVED with ~w~n', [before(StepK, StepI)], planner)
 1125  ;
 1126  add_ordering(before(StepJ, StepK), Order0, Order1),
 1127  bugout('    RESOLVED with ~w~n', [before(StepJ, StepK)], planner).
 1128protect(causes(StepI, Cond0, StepJ), StepK, _Cond1, Order0, Order0) :-
 1129  bugout('  FAILED to resolve THREAT ~w <> causes(~w, ~w, ~w)~n',
 1130         [StepK, StepI, Cond0, StepJ], planner),
 1131  once(pick_ordering(Order0, Serial)),
 1132  bugout('    ORDERING is ~w~n', [Serial], planner),
 1133  fail.
 1134
 1136protect_link(_Link, _StepID, [], Order0, Order0).
 1137protect_link(Link, StepID, [Cond|Effects], Order0, Order2):-
 1138  protect(Link, StepID, Cond, Order0, Order1),
 1139  protect_link(Link, StepID, Effects, Order1, Order2).
 1140
 1143protect_links([], _StepID, _Effects, Order0, Order0).
 1144protect_links([Link|Tail], StepID, Effects, Order0, Order2) :-
 1145  protect_link(Link, StepID, Effects, Order0, Order1),
 1146  protect_links(Tail, StepID, Effects, Order1, Order2).
 1147
 1149protect_link_all(_Link, [], Order0, Order0).
 1150protect_link_all(Link, [step(StepID, oper( _, _, Effects))|Steps], Order0, Order2) :-
 1151  protect_link(Link, StepID, Effects, Order0, Order1),
 1152  protect_link_all(Link, Steps, Order1, Order2).
 1153
 1156add_binding((X\=Y), Bindings, [(X\=Y)|Bindings]) :-
 1157  X \== Y,  1158   1159  bindings_valid(Bindings).
 1160
 1161bindings_valid([]).
 1162bindings_valid([(X\=Y)|Bindings]) :-
 1163  X \== Y,
 1164  bindings_valid(Bindings).
 1168
 1169bindings_safe([]) :- bugout('  BINDINGS are SAFE~n', planner).
 1170bindings_safe([(X\=Y)|Bindings]) :-
 1171  X \= Y,
 1172  bindings_safe(Bindings).
 1176
 1177choose_operator([goal(GoalID, GoalCond)|Goals0], Goals0,
 1178                 _Operators,
 1179                 plan(Steps, Order0, Bindings, OldLinks),
 1180                 plan(Steps, Order9, Bindings, NewLinks),
 1181                 Depth, Depth ) :-
 1182   1183  member(step(StepID, oper( _Action, _Preconds, Effects)), Steps),
 1184  precondition_matches_effects(GoalCond, Effects),
 1185  add_ordering(before(StepID, GoalID), Order0, Order1),
 1186   1187  protect_link_all(causes(StepID, GoalCond, GoalID), Steps, Order1, Order9),
 1188  union([causes(StepID, GoalCond, GoalID)], OldLinks, NewLinks),
 1189  bindings_valid(Bindings),
 1190  bugout('  EXISTING step ~w satisfies ~w~n', [StepID, GoalCond], planner).
 1191choose_operator([goal(_GoalID, X \= Y)|Goals0], Goals0,
 1192                 _Operators,
 1193                 plan(Steps, Order, Bindings, Links),
 1194                 plan(Steps, Order, NewBindings, Links),
 1195                 Depth, Depth ) :-
 1196  add_binding((X\=Y), Bindings, NewBindings),
 1197  bugout('  BINDING ADDED: ~w~n', [X\=Y], planner).
 1198choose_operator([goal(GoalID, ~ GoalCond)|Goals0], Goals0,
 1199                 _Operators,
 1200                 plan(Steps, Order0, Bindings, OldLinks),
 1201                 plan(Steps, Order9, Bindings, NewLinks),
 1202                 Depth, Depth ) :-
 1203   1204  memberchk(step(start, oper( _Action, _Preconds, Effects)), Steps),
 1205  \+ precondition_matches_effects(GoalCond, Effects),
 1206  add_ordering(before(start, GoalID), Order0, Order1),
 1207   1208  protect_link_all(causes(start, GoalCond, GoalID), Steps, Order1, Order9),
 1209  union([causes(start, ~GoalCond, GoalID)], OldLinks, NewLinks),
 1210  bindings_valid(Bindings),
 1211  bugout('  START SATISFIES NOT ~w~n', [GoalCond], planner).
 1212choose_operator([goal(GoalID, exists(GoalCond))|Goals0], Goals0,
 1213                 _Operators,
 1214                 plan(Steps, Order0, Bindings, OldLinks),
 1215                 plan(Steps, Order9, Bindings, NewLinks),
 1216                 Depth, Depth ) :-
 1217  memberchk(step(start, oper( _Action, _Preconds, Effects)), Steps),
 1218  ( in_model(h(_At, GoalCond, _Where, _), Effects);
 1219    in_model(h(_At, _What, GoalCond, _), Effects)),
 1220  add_ordering(before(start, GoalID), Order0, Order1),
 1221   1222  protect_link_all(causes(start, GoalCond, GoalID), Steps, Order1, Order9),
 1223  union([causes(start, exists(GoalCond), GoalID)], OldLinks, NewLinks),
 1224  bindings_valid(Bindings),
 1225  bugout('  START SATISFIES exists(~w)~n', [GoalCond], planner).
 1226choose_operator([goal(GoalID, GoalCond)|Goals0], Goals2,
 1227                 Operators,
 1228                 plan(OldSteps, Order0, Bindings, OldLinks),
 1229                 plan(NewSteps, Order9, Bindings, NewLinks),
 1230                 Depth0, Depth ) :-
 1231   1232  Depth0 > 0,
 1233  Depth is Depth0 - 1,
 1234   1235  copy_term(Operators, FreshOperators),
 1236   1237   1238  member(oper( Action, Preconds, Effects), FreshOperators),
 1239  precondition_matches_effects(GoalCond, Effects),
 1240  operator_as_step(oper( Action, Preconds, Effects),
 1241                   step(StepID, oper( Action, Preconds, Effects)) ),
 1242   1243  add_orderings([before(start, StepID),
 1244                 before(StepID, GoalID),
 1245                 before(StepID, finish)],
 1246                Order0, Order1),
 1247   1248  protect_links(OldLinks, StepID, Effects, Order1, Order2),
 1249   1250  protect_link_all(causes(StepID, GoalCond, GoalID), OldSteps, Order2, Order9),
 1251   1252  append(OldSteps, [step(StepID, oper( Action, Preconds, Effects))], NewSteps),
 1253   1254  union([causes(StepID, GoalCond, GoalID)], OldLinks, NewLinks),
 1255   1256  conds_as_goals(StepID, Preconds, NewGoals),
 1257  append(Goals0, NewGoals, Goals2),
 1258  bindings_valid(Bindings),
 1259  bugout('  ~w CREATED ~w to satisfy ~w~n',
 1260         [Depth, StepID, GoalCond], autonomous),
 1261  pprint(oper( Action, Preconds, Effects), planner),
 1262  once(pick_ordering(Order9, List)),
 1263  bugout('    Orderings are ~w~n', [List], planner).
 1264choose_operator([goal(GoalID, GoalCond)|_G0], _G2, _Op, _P0, _P2, D, D) :-
 1265  bugout('  CHOOSE_OPERATOR FAILED on goal:~n    goal(~w, ~w)~n',
 1266         [GoalID, GoalCond], planner),
 1267  !, fail.
 1268choose_operator(G0, _G2, _Op, _P0, _P2, D, D) :-
 1269  bugout('  !!! CHOOSE_OPERATOR FAILED: G0 = ~w~n', [G0], planner), !, fail.
 1270
 1271planning_loop([], _Operators, plan(S, O, B, L), plan(S, O, B, L), _Depth, _TO ) :-
 1272  bugout('FOUND SOLUTION?~n', planner),
 1273  bindings_safe(B).
 1274planning_loop(Goals0, Operators, Plan0, Plan2, Depth0, Timeout) :-
 1275   1276  get_time(Now),
 1277  (Now > Timeout -> throw(timeout(planner)); true),
 1278  bugout('GOALS ARE: ~w~n', [Goals0], planner),
 1279  choose_operator(Goals0, Goals1, Operators, Plan0, Plan1, Depth0, Depth),
 1280   1281  planning_loop(Goals1, Operators, Plan1, Plan2, Depth, Timeout).
 1286
 1287serialize_plan( plan([], _Orderings, _B, _L), []) :- !.
 1288
 1289serialize_plan(plan(Steps, Orderings, B, L), Tail) :-
 1290  select(step(_, oper( true, _, _)), Steps, RemainingSteps),
 1291  !,
 1292  serialize_plan(plan(RemainingSteps, Orderings, B, L), Tail).
 1293
 1294serialize_plan(plan(Steps, Orderings, B, L), [Action|Tail]) :-
 1295  select(step(StepI, oper( Action, _, _)), Steps, RemainingSteps),
 1296  \+ (member(step(StepJ, _Oper), RemainingSteps),
 1297      isbefore(StepJ, StepI, Orderings)),
 1298  serialize_plan(plan(RemainingSteps, Orderings, B, L), Tail).
 1299
 1300serialize_plan(plan(_Steps, Orderings, _B, _L), _) :-
 1301  bugout('serialize_plan FAILED!~n', planner),
 1302  pick_ordering(Orderings, List),
 1303  bugout('  Orderings are ~w~n', [List], planner),
 1304  fail.
 1305
 1306select_unsatisfied_conditions([], [], _Model) :- !.
 1307select_unsatisfied_conditions([Cond|Tail], Unsatisfied, Model) :-
 1308  precondition_matches_effects(Cond, Model),
 1309  !,
 1310  select_unsatisfied_conditions(Tail, Unsatisfied, Model).
 1311select_unsatisfied_conditions([(~Cond)|Tail], Unsatisfied, Model) :-
 1312  \+ precondition_matches_effects(Cond, Model),
 1313  !,
 1314  select_unsatisfied_conditions(Tail, Unsatisfied, Model).
 1315select_unsatisfied_conditions([Cond|Tail], [Cond|Unsatisfied], Model) :-
 1316  !,
 1317  select_unsatisfied_conditions(Tail, Unsatisfied, Model).
 1318
 1319depth_planning_loop(PlannerGoals, Operators, SeedPlan, FullPlan,
 1320                    Depth, Timeout) :-
 1321  bugout('PLANNING DEPTH is ~w~n', [Depth], autonomous),
 1322  planning_loop(PlannerGoals, Operators, SeedPlan, FullPlan, Depth, Timeout),
 1323  !.
 1324depth_planning_loop(PlannerGoals, Operators, SeedPlan, FullPlan,
 1325                    Depth0, Timeout) :-
 1326  Depth0 =< 7,
 1327  Depth is Depth0 + 1,
 1328  depth_planning_loop(PlannerGoals, Operators, SeedPlan, FullPlan,
 1329                      Depth, Timeout).
 1330
 1331generate_plan(FullPlan, Mem0) :-
 1332  thought(Agent, agent(Agent), Mem0),
 1333  initial_operators(Agent, Operators),
 1334  bugout('OPERATORS are:~n', planner), pprint(Operators, planner),
 1335  thought(Agent, model(Model0), Mem0),
 1336   1337  thought(Agent, goals(Goals), Mem0),
 1338  new_plan(Model0, Goals, SeedPlan),
 1339  bugout('SEED PLAN is:~n', planner), pprint(SeedPlan, planner),
 1340  !,
 1341   1342  conds_as_goals(finish, Goals, PlannerGoals),
 1343  get_time(Now),
 1344  Timeout is Now + 60,  1345  catch(
 1346    depth_planning_loop(PlannerGoals, Operators, SeedPlan, FullPlan,
 1347                        1, Timeout),
 1348    timeout(planner),
 1349    (bugout('PLANNER TIMEOUT~n', autonomous), fail)
 1350  ),
 1351  bugout('FULL PLAN is:~n', planner), pprint(FullPlan, planner).
 1352
 1354
 1355add_goal(Agent, Goal, Mem0, Mem2) :-
 1356  bugout('adding goal ~w~n', [Goal], planner),
 1357  forget(Agent, goals(OldGoals), Mem0, Mem1),
 1358  append([Goal], OldGoals, NewGoals),
 1359  memorize(Agent, goals(NewGoals), Mem1, Mem2).
 1360
 1361add_goals(Goals, Mem0, Mem2) :-
 1362  forget(Agent, goals(OldGoals), Mem0, Mem1),
 1363  append(Goals, OldGoals, NewGoals),
 1364  memorize(Agent, goals(NewGoals), Mem1, Mem2).
 1365
 1366add_todo(Auto, Mem0, Mem3) :- Auto = auto(Agent),
 1367  1368 autonomous_decide_action(Agent, Mem0, Mem3),!.
 1369
 1370add_todo( Action, Mem0, Mem2) :-
 1371  forget(Agent, todo(OldToDo), Mem0, Mem1),
 1372  append(OldToDo, [Action], NewToDo),
 1373  memorize(Agent, todo(NewToDo), Mem1, Mem2).
 1374
 1375add_todo_all([], Mem0, Mem0).
 1376add_todo_all([Action|Rest], Mem0, Mem2) :-
 1377  add_todo( Action, Mem0, Mem1),
 1378  add_todo_all(Rest, Mem1, Mem2).
 1379
 1383consider_request(_Speaker, Agent, Action, M0, M0) :-
 1384  bugout('~w: considering request: ~w.~n', [Agent, Action], autonomous),
 1385  fail.
 1386consider_request(Requester, Agent, Query, M0, M1) :-
 1387  do_introspect(Query, Answer, M0),
 1388   1389  add_todo( talk(Agent, Requester, Answer), M0, M1).
 1390consider_request(_Speaker, Agent, forget(Agent, goals), M0, M2) :-
 1391  bugout('~w: forgetting goals.~n', [Agent], autonomous),
 1392  forget_always(Agent, goals(_), M0, M1),
 1393  memorize(Agent, goals([]), M1, M2).
 1394consider_request(_Speaker, Agent, goto(Agent, Walk, *, ExitName), M0, M1) :-
 1395  bugout('Queueing action ~w~n', goto(Agent, Walk, *, ExitName), autonomous),
 1396  add_todo( goto(Agent, Walk, *, ExitName), M0, M1).
 1397consider_request(Speaker, Agent, fetch(Object), M0, M1) :-
 1398   1399  add_goal(Agent, h(held_by, Object, Speaker), M0, M1).
 1400consider_request(_Speaker, Agent, put(Thing, Relation, Where), M0, M) :-
 1401  add_goal(Agent, h(Relation, Thing, Where), M0, M).
 1402consider_request(_Speaker, Agent, take(Thing), M0, M) :-
 1403  add_goal(Agent, h(held_by, Thing, Agent), M0, M).
 1404consider_request(_Speaker, Agent, Action, M0, M1) :-
 1405  bugout('Finding goals for action: ~w~n', [Action], autonomous),
 1406  initial_operators(Agent, Operators),
 1407  findall(Effects,
 1408          member(oper( Action, _Conds, Effects), Operators),
 1409          [UnambiguousGoals]),
 1410  bugout('Request: ~w --> goals ~w.~n', [Action, UnambiguousGoals], autonomous),
 1411  add_goals(UnambiguousGoals, M0, M1).
 1412consider_request(_Speaker, _Agent, Action, M0, M1) :-
 1413  bugout('Queueing action: ~w~n', [Action], autonomous),
 1414  add_todo( Action, M0, M1).
 1415consider_request(Speaker, Agent, Action, M0, M0) :-
 1416  bugout('~w: did not understand request from ~w: ~w~n', [Agent, Speaker, Action], autonomous).
 1417
 1419process_percept_auto(Agent, [say(Agent, _)|_], _Stamp, Mem0, Mem0).
 1420process_percept_auto(Agent, [talk(Agent, _, _)|_], _Stamp, Mem0, Mem0).
 1421process_percept_auto(Agent, talk(Speaker, Agent, Words), _Stamp, Mem0, Mem1) :-
 1422  parse_command(Agent, Words, Action, Mem0),
 1423  consider_request(Speaker, Agent, Action, Mem0, Mem1).
 1424process_percept_auto(Agent, say(Speaker, [Agent|Words]), _Stamp, Mem0, Mem1) :-
 1425  parse_command(Agent, Words, Action, Mem0),
 1426  consider_request(Speaker, Agent, Action, Mem0, Mem1).
 1427process_percept_auto(Agent, Percept, _Stamp, Mem0, Mem0) :-
 1428  Percept =.. [Functor|_],
 1429  member(Functor, [talk, say]),
 1430  bugout('~w: Ignoring ~w~n', [Agent, Percept], autonomous).
 1431process_percept_auto(Agent, sense_props(Agent, Sense, Object, PropList), _Stamp, Mem0, Mem2) :-
 1432  bugout('~w: ~w~n', [Agent, sense_props(Agent, Sense, Object, PropList)], autonomous),
 1433  member(shiny, PropList),
 1434  member(model(Model), Mem0),
 1435  \+  h(descended, Object, Agent, Model),  1436  add_todo_all( [take(Agent, Object), print_('My shiny precious!')], Mem0, Mem2).
 1437
 1438process_percept_auto(Agent, can_sense_from_here(Agent, _At, _Here, Sense, Objects), _Stamp, Mem0, Mem2) :-
 1439  member(model(Model), Mem0),
 1440  findall(examine(Sense, Obj),
 1441          ( member(Obj, Objects),
 1442            \+ member(holds_at(props(Obj, _),_), Model)),
 1443          ExamineNewObjects),
 1444  add_todo_all(ExamineNewObjects, Mem0, Mem2).
 1445process_percept_auto(_Agent, _Percept, _Stamp, Mem0, Mem0).
 1446
 1447process_percept_player(Agent, [say(Agent, _)|_], _Stamp, Mem0, Mem0).
 1448process_percept_player(Agent, [talk(Agent, _, _)|_], _Stamp, Mem0, Mem0).
 1449   1450process_percept_player(Agent, Percept, _Stamp, Mem0, Mem0) :-
 1451  percept2txt(Agent, Percept, Text),
 1452  player_format(Agent, '~w~n', [Text]).
 1453  
 1454
 1455process_percept_main(Agent, Percept, Stamp, Mem0, Mem4) :-
 1456  forget(Agent, model(Model0), Mem0, Mem1),
 1457  update_model(Agent, Percept, Stamp, Mem1, Model0, Model1),
 1458  memorize(Agent, model(Model1), Mem1, Mem2),
 1459  process_percept_auto(Agent, Percept, Stamp, Mem2, Mem3),
 1460  process_percept_player(Agent, Percept, Stamp, Mem3, Mem4).
 1461process_percept_main(_Agent, Percept, _Stamp, Mem0, Mem0) :-
 1462  bugout('process_percept_main(~w) FAILED!~n', [Percept], general), !.
 1463
 1465process_percept_list(Agent, _, _Stamp, Mem, Mem) :-
 1466  thought(Agent, agent_type(recorder), Mem),
 1467  !.
 1468process_percept_list(Agent, [Percept|Tail], Stamp, Mem0, Mem4) :-
 1469   1470   1471  process_percept_main(Agent, Percept, Stamp, Mem0, Mem1),
 1472  process_percept_list(Agent, Tail, Stamp, Mem1, Mem4).
 1473process_percept_list(_Agent, [], _Stamp, Mem0, Mem0).
 1474process_percept_list(_Agent, _, _Stamp, Mem0, Mem0) :-
 1475  bugout('process_percept_list FAILED!~n', general).
 1476
 1478:- dynamic(useragent/1). 1479useragent(player).
 1480
 1481:- consult(adv_eng2cmd). 1482
 1483
 1484
 1486do_introspect(path(There), Answer, Memory) :-
 1487  agent_thought_model(Agent, Model, Memory),
 1488  in_model(h(_At, Agent, Here), Model),
 1489  find_path(Here, There, Route, Model),
 1490  Answer = ['Model is', Model, '\nShortest path is', Route].
 1491do_introspect(whereis(Thing), Answer, Memory) :-
 1492  agent_thought_model(Agent, Model, Memory),
 1493  in_model(holds_at(h(At, Thing, Where), T), Model),
 1494  At \= exit(_),
 1495  Answer = ['At time', T, subj(Agent), 'saw the', Thing, At, the, Where, .].
 1496do_introspect(whereis(Here), Answer, Memory) :-
 1497  agent_thought_model(Agent, Model, Memory),
 1498  in_model(h(_At, Agent, Here), Model),
 1499  Answer = 'Right here.'.
 1500do_introspect(whereis(There), Answer, Memory) :-
 1501  agent_thought_model(Agent, Model, Memory),
 1502  in_model(h(_At, Agent, Here), Model),
 1503  find_path(Here, There, Route, Model),
 1504  Answer = ['To get to the', There, ', ', Route].
 1505do_introspect(whereis(There), Answer, Memory) :-
 1506  agent_agent_thought_model(Agent,_Agent, Model, Memory),
 1507  ( in_model(h(exit(_), _, There), Model);
 1508    in_model(h(exit(_), There, _), Model)),
 1509  Answer = 'Can''t get there from here.'.
 1510do_introspect(whereis(X), Answer, Memory) :-
 1511  agent_thought_model(Agent, _Model, Memory),
 1512  Answer = [subj(Agent), person('don\'t', 'doesn\'t'),
 1513            'recall ever seeing a "', X, '".'].
 1514do_introspect(whois(X), Answer, Memory) :-
 1515  do_introspect(whereis(X), Answer, Memory).
 1516do_introspect(whois(X), [X, is, X, .], _Memory).
 1517do_introspect(whatis(X), Answer, Memory) :-
 1518  do_introspect(whereis(X), Answer, Memory).
 1519do_introspect(whatis(X), [X, is, X, .], _Memory).
 1520
 1521save_term(Filename, Term) :-
 1522  \+ access_file(Filename, exist),
 1523  open(Filename, write, FH),
 1524  write(FH, Term),
 1525  close(FH),
 1526  player_format('Saved to file "~w".~n', [Filename]).
 1527save_term(Filename, _) :-
 1528  access_file(Filename, exist),
 1529  player_format('Save FAILED! Does file "~w" already exist?~n', [Filename]).
 1530save_term(Filename, _) :-
 1531  player_format('Failed to open file "~w" for saving.~n', [Filename]).
 1532
 1533
 1534
 1535
 1536
 1537
 1538do_command(Agent, Action, S0, S1) :-
 1539  do_metacmd(Agent, Action, S0, S1), !.
 1540do_command(Agent, Action, S0, S1) :-
 1541  declared(memories(Agent, Mem), S0),
 1542  do_introspect(Action, Answer, Mem),!,
 1543  queue_agent_percept(Agent, [answer(Answer), Answer], S0, S1).
 1544   1545do_command(Agent, Action, S0, S3) :-
 1546  undeclare(memories(Agent, Mem0), S0, S1),
 1547  memorize(Agent, did(Action), Mem0, Mem1),
 1548  declare(memories(Agent, Mem1), S1, S2),
 1549  apply_act( Action, S2, S3).
 1550do_command(Agent, Action, S0, S0) :-
 1551  player_format(Agent, 'Failed or No Such Command: ~w~n', Action), !.
 1552
 1554
 1555do_todo(Agent, S0, S9) :-
 1556  undeclare(memories(Agent, Mem0), S0, S1),
 1557  forget(Agent, todo(OldToDo), Mem0, Mem1),
 1558  append([Action], NewToDo, OldToDo),
 1559  memorize(Agent, todo(NewToDo), Mem1, Mem2),
 1560  declare(memories(Agent, Mem2), S1, S2),
 1561  do_command(Agent, Action, S2, S9).
 1562do_todo(_Agent, S0, S0).
 1563
 1568
(Agent, S0, S9) :-
 1570  undeclare(memories(Agent, Mem0), S0, S1),
 1571  memorize_list(Agent, [did(look(Agent)), did(inventory(Agent))], Mem0, Mem1),
 1572  declare(memories(Agent, Mem1), S1, S2),
 1573  add_look(Agent, S2, S3),
 1574  apply_act( inventory(Agent), S3, S9).
 1575
 1576random_noise(Agent, [cap(subj(Agent)), Msg]) :-
 1577  random_member([
 1578    'hums quietly to himself.',
 1579    'checks his inspection cover.',
 1580    'buffs his chestplate.',
 1581    'fidgets uncomfortably.'
 1582    ], Msg).
 1583
 1584
 1585:- dynamic(adv:agent_last_action/3). 1586
 1587
 1588:- dynamic(adv:console_tokens/2). 1589telnet_decide_action(Agent, Mem0, Mem0):-
 1590  1591 thought(Agent, todo([Action|_]), Mem0),
 1592 (declared(h(in, Agent, Here), advstate)->true;Here=somewhere),
 1593 bugout('~w @ ~w telnet: Already about to: ~w~n', [Agent, Here, Action], telnet).
 1594
 1595telnet_decide_action(Agent, Mem0, Mem1) :-
 1596  1597 retract(adv:console_tokens(Agent, Words)), !,
 1598 dmust((parse_command(Agent, Words, Action, Mem0),
 1599 if_tracing(bugout('Telnet TODO ~p~n', [Agent: Words->Action], telnet)),
 1600 add_todo(Action, Mem0, Mem1))), !.
 1601telnet_decide_action(Agent, Mem, Mem) :-
 1602 nop(bugout('~w: Can\'t think of anything to do.~n', [Agent], telnet)).
 1603
 1604
 1605
 1606time_since_last_action(Agent,Action,When):- 
 1607 (adv:agent_last_action(Agent,Action,Last),clock_time(T),When is T - Last) *-> true; (clock_time(When),Action=wait(Agent)).
 1608
 1609set_last_action(Agent,Action):- 
 1610 clock_time(T),
 1611 retractall(adv:agent_last_action(Agent,_,_)),
 1612 assertz(adv:agent_last_action(Agent,Action,T)).
 1613
 1614do_autonomous_cycle(Agent):- time_since_last_action(Agent,_,When), When > 10, !.
 1615do_autonomous_cycle(Agent):- 
 1616 time_since_last_action(Other,_,When),
 1617 Other \== Agent, When < 1, !, 
 1618 retractall(adv:agent_last_action(Other,_,_)),
 1619 nop(bugout(time_since_last_action_for(Other,When,Agent))).
 1620
 1621
 1622
 1624maybe_autonomous_decide_goal_action(Agent, Mem0, Mem0) :- 
 1625 getprop(Agent, status(powered, f), advstate),!.
 1626
 1627maybe_autonomous_decide_goal_action(Agent, Mem0, Mem1) :- notrace((do_autonomous_cycle(Agent),
 1628 set_last_action(Agent,[auto(Agent)]))),
 1629 autonomous_decide_goal_action(Agent, Mem0, Mem1),!.
 1630maybe_autonomous_decide_goal_action(_Agent, Mem0, Mem0).
 1631
 1632
 1634autonomous_decide_goal_action(Agent, Mem0, Mem3) :-
 1635 dmust((
 1636    forget(Agent, goals(Goals), Mem0, Mem1),
 1637    member(model(ModelData), Mem1),
 1638    select_unsatisfied_conditions(Goals, Unsatisfied, ModelData),
 1639    subtract(Goals,Unsatisfied,Satisfied),
 1640    memorize(Agent, goals(Unsatisfied), Mem1, Mem1a),
 1641    (Satisfied==[] -> Mem1a=Mem2 ; memorize(Agent, satisfied(Satisfied), Mem1a, Mem2)),
 1642    autonomous_decide_action(Agent, Mem2, Mem3))).
 1643                         
 1644autonomous_decide_action(Agent, Mem0, Mem0) :-
 1645   1646  thought(Agent, todo([Action|_]), Mem0),
 1647  bugout('~w: about to: ~w~n', [Agent, Action], autonomous).
 1648autonomous_decide_action(Agent, Mem0, Mem1) :-
 1649   1650  thought(Agent, goals([_|_]), Mem0),
 1651  bugout('~w: goals exist: generating a plan...~n', [Agent], autonomous),
 1652  generate_plan(NewPlan, Mem0), !,
 1653  serialize_plan(NewPlan, Actions), !,
 1654  bugout('Planned actions are ~w~n', [Actions], autonomous),
 1655  Actions = [Action|_],
 1656  add_todo( Action, Mem0, Mem1).
 1657autonomous_decide_action(Agent, Mem0, Mem2) :-
 1658  forget(Agent, goals([_|_]), Mem0, Mem1),
 1659  memorize(Agent, goals([]), Mem1, Mem2),
 1660  bugout('~w: Can\'t solve goals.  Forgetting them.~n', [Agent], autonomous).
 1661autonomous_decide_action(Agent, Mem0, Mem1) :-
 1662   1663  agent_thought_model(Agent, Model, Mem0),
 1664  in_model(h(_At, Agent, Here), Model),
 1665  in_model(h(exit(ExitName), Here, '<unexplored>'), Model),
 1666  add_todo( goto(Agent, walk, *, ExitName), Mem0, Mem1).
 1667autonomous_decide_action(Agent, Mem0, Mem1) :-
 1668   1669  agent_thought_model(Agent, Model, Mem0),
 1670  in_model(h(_, Agent, Here), Model),
 1671  in_model(h(_, player, There), Model),
 1672  in_model(h(exit(ExitName), Here, There), Model),
 1673  add_todo( goto(Agent, walk, *, ExitName), Mem0, Mem1).
 1674autonomous_decide_action(Agent, Mem0, Mem1) :- fail,
 1675   1676  call(call,(ZERO is random(5))), ZERO == 0,!,
 1677  random_noise(Agent, Msg),
 1678  add_todo(print_(Agent, Msg), Mem0, Mem1).
 1679autonomous_decide_action(Agent, Mem0, Mem0) :-
 1680  bugout('~w: Can\'t think of anything to do.~n', [Agent], autonomous). 1681
 1682
 1683
 1684console_decide_action(Agent, Mem0, Mem1):- 
 1685  1686  1687 repeat,
 1688 notrace((
 1689 ttyflush,
 1690 agent_to_input(Agent,In),
 1691 dmust(is_stream(In)),
 1692 setup_console,
 1693 ensure_has_prompt(Agent),
 1694 read_line_to_tokens(Agent, In,[], Words0), 
 1695 (Words0==[]->(Words=[wait],makep);Words=Words0))),
 1696 parse_command(Agent, Words, Action, Mem0),      
 1697 !,
 1698 if_tracing(bugout('Console TODO ~p~n', [Agent: Words->Action], telnet)),
 1699 add_todo(Action, Mem0, Mem1), ttyflush, !.
 1700
 1701makep:- 
 1702 locally(set_prolog_flag(verbose_load,true),
 1703 with_no_dmsg(make:((
 1704  
 1705  '$update_library_index',
 1706 findall(File, make:modified_file(File), Reload0),
 1707 list_to_set(Reload0, Reload),
 1708 ( prolog:make_hook(before, Reload)
 1709 -> true
 1710 ; true
 1711 ),
 1712 print_message(silent, make(reload(Reload))),
 1713 maplist(reload_file, Reload),
 1714 print_message(silent, make(done(Reload))),
 1715 ( prolog:make_hook(after, Reload)
 1716 -> true
 1717 ; nop(list_undefined),
 1718  nop(list_void_declarations)
 1719 ))))).
 1720
 1721
 1722
 1723decide_action(Agent, Mem0, Mem0) :- 
 1724 thought(Agent, todo([Action|_]), Mem0),
 1725 (declared(h(in, Agent, Here), advstate)->true;Here=somewhere),
 1726 (trival_act(Action)->true;bugout('~w @ ~w: already about todo: ~w~n', [Agent, Here, Action], autonomous)).
 1727
 1729decide_action(Agent, Mem0, Mem1) :-
 1730 notrace(declared(inherits(telnet), Mem0)),!,
 1731 dmust(telnet_decide_action(Agent, Mem0, Mem1)).
 1732
 1734decide_action(Agent, Mem0, Mem1) :-
 1735 thought(Agent, agent_type(console), Mem0),
 1736  1737 ensure_has_prompt(Agent),
 1738 agent_to_input(Agent,In),
 1739 (tracing->catch(wait_for_input([In,user_input],Found,20),_,(nortrace,notrace,break));wait_for_input([In,user_input],Found,2)),
 1740 (Found==[] -> (Mem0=Mem1) ;  quietly(((console_decide_action(Agent, Mem0, Mem1))))).
 1741
 1742decide_action(Agent, Mem0, Mem3) :-
 1743  thought(Agent, agent_type(autonomous), Mem0),
 1744 maybe_autonomous_decide_goal_action(Agent, Mem0, Mem3).
 1745
 1746decide_action(Agent, Mem, Mem) :-
 1747  thought(Agent, agent_type(recorder), Mem).   1748decide_action(Agent, Mem0, Mem0) :-
 1749  bugout('decide_action(~w) FAILED!~n', [Agent], general).
 1750
 1751run_agent(Agent, S0, S) :-
 1752  undeclare(memories(Agent, Mem0), S0, S1),
 1753  undeclare(perceptq(Agent, PerceptQ), S1, S2),
 1754  thought(Agent, timestamp(T0), Mem0),
 1755  T1 is T0 + 1,
 1756  memorize(Agent, timestamp(T1), Mem0, Mem1),
 1757  process_percept_list(Agent, PerceptQ, T1, Mem1, Mem2),
 1758  memorize_list(Agent, PerceptQ, Mem2, Mem3),
 1759  decide_action(Agent, Mem3, Mem4),
 1760  declare(memories(Agent, Mem4), S2, S3),
 1761  declare(perceptq(Agent, []), S3, S4),
 1762  do_todo(Agent, S4, S).
 1763run_agent(Agent, S0, S0) :-
 1764  bugout('run_agent(~w) FAILED!~n', [Agent], general).
 1765
 1766
 1768
 1769:- dynamic(undo/1). 1770undo([u, u, u, u, u, u, u, u]).
 1771:- dynamic(advstate/1). 1773
 1774run_all_agents([], S0, S0).
 1775run_all_agents([Agent|AgentTail], S0, S2) :-
 1776  run_agent(Agent, S0, S1),
 1777  !,  1778  run_all_agents(AgentTail, S1, S2).
 1779
 1780create_agents([], S0, S0).
 1781create_agents([agentspec(Agent, Type)|Tail], S0, S2) :-
 1782  create_agent(Agent, Type, S0, S1),
 1783  create_agents(Tail, S1, S2).
 1784
 1785init_agents(S0, S2) :-
 1786  findall(agentspec(Agent, Type),
 1787          getprop(Agent, agent_type(Type), S0),
 1788          AgentList),
 1789  create_agents(AgentList, S0, S2).
 1790
 1791main(S0, S2) :-
 1792  findall(Agent1, getprop(Agent1, agent_type(console), S0), AgentList1),
 1793  findall(Agent2,
 1794          ( getprop(Agent2, agent_type(autonomous), S0),
 1795            ( getprop(Agent2, can_be(switched(on), t), S0) -> \+ getprop(Agent2, state(on, f), S0) ; true )
 1796          ), AgentList2),
 1797  append(AgentList1, AgentList2, AllAgents),
 1798  run_all_agents(AllAgents, S0, S2),
 1799  !.  1800main(S0, S0) :-
 1801  bugout('main FAILED~n', general).
 1802
 1803mainloop :-
 1804  repeat,
 1805    retract(advstate(S0)),
 1806    main(S0, S1),
 1807    asserta(advstate(S1)),
 1808    must_output_state(S1),
 1809    declared(quit, S1),
 1810  !.  1811
 1813main_loop(S0) :-
 1814  declared(quit, S0).
 1815main_loop(S0) :-
 1816  declared(undo, S0),
 1817  retract(undo([_, Prev|Tail])),
 1818  assertz(undo(Tail)),
 1819  !,
 1820  main_loop(Prev).
 1821main_loop(S0) :-
 1822   1823  retract(undo([U1, U2, U3, U4, U5, U6|_])),
 1824  assertz(undo([S0, U1, U2, U3, U4, U5, U6])),
 1825  run_agent(player, S0, S4),
 1826  run_agent(floyd, S4, S5),
 1827   1828   1829  !,
 1830  main_loop(S5).
 1831main_loop(_) :-
 1832  bugout('main_loop() FAILED!~n', general).
 1833
 1842add_look(_Agent, S1, S1).
 1843
 1844adventure :-
 1845   1846  test_ordering,
 1847  init_logging,
 1848  (retractall(advstate(_));true),
 1849  istate(S0),
 1850  init_agents(S0, S1),
 1851   1852   1853   1854  S1= S3,
 1855  asserta(advstate(S3)),
 1856  player_format(Agent, '=============================================~n', []),
 1857  player_format(Agent, 'Welcome to Marty\'s Prolog Adventure Prototype~n', []),
 1858  player_format(Agent, '=============================================~n', []),
 1859  mainloop,
 1860   1861  adv:input_log(FH),
 1862  close(FH),
 1863  notrace.
 1864adventure :-
 1865  adv:input_log(FH),
 1866  close(FH),
 1867  format('adventure FAILED~n', []),
 1868  !, fail.
 1869
 1870:- debug. 1872:- make. 1874
 1875
 1876:- defn_state_getter(cant(act,why)). 1877
 1878
 1879cant( Action, Why, State) :-
 1880 never_equal(Sense,Thing, Agent),
 1881 agent_act_verb_thing_sense(Agent, Action, Verb, Thing, Sense),
 1882 psubsetof(Verb, _),
 1883 \+ in_scope(Agent, Thing, State),
 1884 (Why = (\+ in_scope(Agent, Thing, Agent))).
 1885
 1886
 1887cant( Action,  Why, State) :-
 1888 never_equal(Sense,Thing, Agent),
 1889 agent_act_verb_thing_sense(Agent, Action, Verb, Thing, Sense),
 1890 psubsetof(Verb, examine(Agent, Sense)),
 1891 \+ can_sense(Agent, Sense, Thing, State),
 1892 (Why = ( reason( \+ can_sense(Agent, Sense, Thing)))).
 1893
 1900
 1901cant( Action, getprop(Thing, can_be(Move, f)), State) :-
 1902 agent_act_verb_thing_sense(_Agent, Action, Verb, Thing, _Sense),
 1903 psubsetof(Verb, Move),
 1904 getprop(Thing, can_be(Move, f), State).
 1905
 1906cant( Action, musthave( Thing), State) :-
 1907 agent_act_verb_thing_sense(Agent, Action, Verb, Thing, Sense),
 1908 psubsetof(Verb, drop),
 1909 \+ h(Sense, Thing, Agent, State).
 1910
 1911cant( Action, manipulate(self), _) :- Action =.. [Verb, Agent, Thing |_], Agent==Thing, psubsetof(Verb, touch).
 1912cant( take(Agent, Thing), alreadyhave(Thing), State) :-
 1913 h(descended, Thing, Agent, State).
 1914cant( take(Agent, Thing), mustgetout(Thing), State) :-
 1915 h(descended, Agent, Thing, State).
 1916
 1917cant( put(_Agent, Thing1, Dest), self_relation(Thing1), _S0):- 
 1918  dest_target(Dest,Object),Object==Thing1.
 1919cant( put(_Agent, Thing1, Dest), moibeus_relation( Thing1, Target), S0) :-
 1920 dest_target(Dest,Target),
 1921 h(descended, Target, Thing1, S0).
 1922
 1923cant( throw(_Agent, Thing1, _Prep, Thing1), self_relation( Thing1), _S0).
 1924cant( throw(_Agent, Thing1, _Prep, Target), moibeus_relation( Thing1, Target), S0) :-
 1925 h(descended, Target, Thing1, S0).
 1926
 1927
 1928cant( look(Agent), TooDark, State) :-
 1929 sensory_problem_solution(Sense, TooDark, _EmittingLight),
 1930  1931  1932 \+ can_sense_here(Agent, Sense, State).
 1933
 1938
 1939:- defn_state_0(equals_efffectly).
 1941equals_efffectly(sense, see, _).
 1942equals_efffectly(_, Value, Value).
 1943
 1944
 1945
 1946cant( examine(Agent, Sense, Thing), TooDark, State) :- 
 1947 equals_efffectly(sense, Sense, see),
 1948 never_equal(Sense,Thing, Agent),
 1949 sensory_problem_solution(Sense, TooDark, _EmittingLight),
 1950 \+ can_sense_here(Agent, Sense, State).
 1951
 1952cant( examine(Agent, Sense, Thing), Why, State) :-
 1953 never_equal(Sense,Thing, Agent),
 1954 \+ can_sense(Agent, Sense, Thing, State),
 1955 (Why = ( reason(  \+ can_sense(Agent, Sense, Thing)))).
 1956
 1957
 1958cant( goto(Agent, _Walk, Dest), mustdrop(Target), State) :- 
 1959 dest_target(Dest,Target),
 1960 nonvar(Target),
 1961 h(descended, Target, Agent, State).
 1962
 1963cant( EatCmd, cantdothat(Verb), State) :-
 1964 agent_act_verb_thing_sense(Agent, EatCmd, Verb, _Thing, _Sense),
 1965 getprop(Agent, knows_verbs(Verb, f), State).
 1966
 1967cant( Action, ~(in_scope(Agent, Thing, S0)), S0) :-
 1968  action_agent_thing(Action, Verb, Agent, Thing),
 1969  psubsetof(Verb, _),
 1970  \+ in_scope(Agent, Thing, S0).
 1971cant( Action, cant(sense(Sense, Thing)), S0) :-
 1972  action_agent_thing(Action, Verb, Agent, Thing),
 1973  psubsetof(Verb, examine),
 1974  \+ can_sense(Agent, Sense, Thing, S0).
 1975cant( Action, cant(reach(Thing)), S0) :-
 1976  action_agent_thing(Action, Verb, Agent, Thing),
 1977  psubsetof(Verb, touch),
 1978  \+ touchable(Agent, Thing, S0).
 1979
 1980cant( Action, props(Thing,[can_be(move, f)]), S0) :-
 1981  action_agent_thing(Action, Verb, _, Thing),
 1982  psubsetof(Verb, move),
 1983  getprop(Thing, can_be(move, f), S0).
 1984
 1985cant( Action, musthave(Thing), S0) :-
 1986  action_agent_thing(Action, Verb, Agent, Thing),
 1987  psubsetof(Verb, drop),
 1988  \+  open_traverse(Thing, Agent, S0).
 1989
 1990cant( Action, cant(manipulate(self)), _) :- \+ extra,
 1991  action_agent_thing(Action, Verb, Agent, Thing),
 1992  Agent == Thing,
 1993  psubsetof(Verb, touch).
 1994
 1995cant( take(Agent, Thing), alreadyhave(Thing), S0) :-
 1996  h(descended, Thing, Agent, S0).
 1997
 1998cant( take(Agent, Thing), mustgetout(Thing), S0) :-
 1999  h(descended, Agent, Thing, S0).
 2000
 2001cant( Action, Why, S0):-   
 2002   action_agent_verb_subject_prep_object(Action, _Agent, Verb, Thing1, _At, Thing2),
 2003   psubsetof(Verb, drop),
 2004   Thing1 = Thing2  -> Why = self_relation(Thing1) ;
 2005   h(descended, Thing2, Thing1, S0) -> Why = moibeus_relation(Thing1, Thing2).
 2006
 2007cant( look(Agent), toodark, S0) :-
 2008   2009   2010  \+ can_sense(Agent, visually, Agent, S0).
 2011
 2012
 2013cant( examine(Agent, Sense), toodark, S0) :-
 2014  \+ can_sense(Agent, Sense, Agent, S0).
 2015
 2016cant( examine(Agent, Sense, Thing), cant(sense(Sense, Thing)), S0) :-
 2017  \+ can_sense(Agent, Sense, Thing, S0).
 2018
 2019cant( goto(Agent, _Walk, _Relation, Object), mustdrop(Object), S0) :-
 2020  h(descended, Object, Agent, S0).
 2021
 2022cant( eat(Agent, _), cantdothat, S0) :-
 2023  \+ getprop(Agent, can_eat, S0)