17
20:- dbug(ensure_loaded('adv_robot_floyd')). 22
(Agent, S0, S9) :-
24 undeclare(memories(Agent, Mem0), S0, S1),
25 memorize_list([did(look(Spatial)), did(inventory)], Mem0, Mem1),
26 declare(memories(Agent, Mem1), S1, S2),
27 must_act(Agent, look(Spatial), S2, S3),
28 must_act(Agent, inventory, S3, S9).
29
30
31random_noise(Agent, [cap(subj(Agent)), Msg]) :-
32 random_member(Msg, [
33 'hums quietly to himself.',
34 'checks his inspection cover.',
35 'buffs his chestplate.',
36 'fidgets uncomfortably.'
37 ]).
38
39:- dynamic(adv:agent_last_action/3). 40
41
42do_autonomous_cycle(Agent):- time_since_last_action(Agent,When), When > 10, !.
43do_autonomous_cycle(Agent):-
44 time_since_last_action(Other,When),
45 Other \== Agent, When < 1, !,
46 retractall(adv:agent_last_action(Other,_,_)),
47 nop(dbug(time_since_last_action_for(Other,When,Agent))).
48
55
56maybe_autonomous_decide_goal_action(Agent, Mem0, Mem1) :- notrace((do_autonomous_cycle(Agent),
57 set_last_action(Agent,[auto]))),
58 autonomous_decide_goal_action(Agent, Mem0, Mem1).
59maybe_autonomous_decide_goal_action(_Agent, Mem0, Mem0).
60
61
62autonomous_decide_goal_action(Agent, Mem0, Mem3) :-
63 forget(goals(Goals), Mem0, Mem1),
64 thought_model(_Spatial,(ModelData), Mem1),
65 select_unsatisfied_conditions(Goals, Unsatisfied, ModelData),
66 memorize(goals(Unsatisfied), Mem1, Mem2),
67 autonomous_decide_action(Agent, Mem2, Mem3).
68
69autonomous_decide_action(Agent, Mem0, Mem0) :-
70 71 thought(todo([Action|_]), Mem0),
72 (declared(h(_Spatial, in, Agent, Here), Mem0)->true;Here=somewhere),
73 bugout('~w @ ~w: about to: ~w~n', [Agent, Here, Action], autonomous).
74
75autonomous_decide_action(Agent, Mem0, Mem1) :-
76 77 thought(goals([_|_]), Mem0),
78 bugout('~w: goals exist: generating a plan...~n', [Agent], autonomous),
79 generate_plan(NewPlan, Mem0), !,
80 serialize_plan(NewPlan, Actions), !,
81 bugout('Planned actions are ~w~n', [Actions], autonomous),
82 Actions = [Action|_],
83 add_todo(Action, Mem0, Mem1).
84autonomous_decide_action(Agent, Mem0, Mem2) :-
85 forget(goals([_|_]), Mem0, Mem1),
86 memorize(goals([]), Mem1, Mem2),
87 bugout('~w: Can\'t solve goals. Forgetting them.~n', [Agent], autonomous).
88autonomous_decide_action(Agent, Mem0, Mem1) :-
89 90 thought_model(Spatial,ModelData, Mem0),
91 in_model(h(Spatial, _How, Agent, Here, _), ModelData),
92 in_model(h(Spatial, exit(ExitName), Here, '<unexplored>', _), ModelData),
93 add_todo(goto(Spatial, (*), ExitName), Mem0, Mem1).
94autonomous_decide_action(Agent, Mem0, Mem1) :-
95 96 thought_model(Spatial,ModelData, Mem0),
97 in_model(h(Spatial, _, Agent, Here, _), ModelData),
98 dif(Agent, Player), current_player(Player),
99 in_model(h(Spatial, _, Player, There, _), ModelData),
100 in_model(h(Spatial, exit(ExitName), Here, There, _), ModelData),
101 add_todo(goto(Spatial, (*), ExitName), Mem0, Mem1).
102
103autonomous_decide_action(Agent, Mem0, Mem1) :-
104 0 is random(5),
105 random_noise(Agent, Msg),
106 add_todo(emote(spatial, see, *, Msg), Mem0, Mem1).
107autonomous_decide_action(Agent, Mem0, Mem0) :-
108 bugout('~w: Can\'t think of anything to do.~n', [Agent], autonomous+verbose). 109
110
111
114:- nop(ensure_loaded('adv_agent_listen')). 116
117consider_text(Speaker, Agent, Words, Mem0, Mem1):-
118 parse(Words, Action, Mem0),
119 consider_request(Speaker, Agent, Action, Mem0, Mem1).
120
122consider_request(_Speaker, Agent, Action, _M0, _M1) :-
123 bugout('~w: considering request: ~w.~n', [Agent, Action], autonomous),
124 fail.
125consider_request(_Speaker, Agent, take(Spatial, Object), M0, M1) :-
126 add_goal(h(Spatial, held_by, Object, Agent, _), M0, M1).
127consider_request(Requester, _Agent, Query, M0, M1) :-
128 do_introspect(Query, Answer, M0),
129 130 add_todo(emote(spatial, say, Requester, Answer), M0, M1).
131consider_request(_Speaker, Agent, forget(goals), M0, M2) :-
132 bugout('~w: forgetting goals.~n', [Agent], autonomous),
133 forget_always(goals(_), M0, M1),
134 memorize(goals([]), M1, M2).
135consider_request(_Speaker, _Agent, goto(Spatial, (*), ExitName), M0, M1) :-
136 bugout('Queueing action ~w~n', goto(Spatial, (*), ExitName), autonomous),
137 add_todo(goto(Spatial, (*), ExitName), M0, M1).
138consider_request(Speaker, _Agent, fetch(Spatial, Object), M0, M1) :-
139 140 add_goal(h(Spatial, held_by, Object, Speaker, _), M0, M1).
141consider_request(_Speaker, _Agent, put(Spatial, Thing, Relation, Where), M0, M) :-
142 add_goal(h(Spatial, Relation, Thing, Where, _), M0, M).
143consider_request(_Speaker, Agent, take(Spatial, Thing), M0, M) :-
144 add_goal(h(Spatial, held_by, Thing, Agent, _), M0, M).
145consider_request(_Speaker, Agent, Action, M0, M1) :-
146 bugout('Finding goals for action: ~w~n', [Action], autonomous),
147 initial_operators(Agent, Operators),
148 findall(Effects,
149 member(oper(Action, _Conds, Effects), Operators),
150 [UnambiguousGoals]),
151 bugout('Request: ~w --> goals ~w.~n', [Action, UnambiguousGoals], autonomous),
152 add_goals(UnambiguousGoals, M0, M1).
153consider_request(_Speaker, _Agent, Action, M0, M1) :-
154 bugout('Queueing action: ~w~n', [Action], autonomous),
155 add_todo(Action, M0, M1).
156consider_request(_Speaker, Agent, Action, M0, M0) :-
157 bugout('~w: did not understand request: ~w~n', [Agent, Action], autonomous).
158
159
160addressing_whom([Agent, Words], Agent, Words)