19
20
21in_model(E, L):- member(E, L).
22thought_model(Spatial, E, L):- in_model(model(Spatial, E), L).
23
24
25get_open_traverse(Open, Sense, Traverse, Spatial, OpenTraverse):- get_open_traverse(Traverse, Spatial, OpenTraverse),
26 nop((ignore(Open=open), ignore(Sense=see))).
27
28get_open_traverse(_Need, Spatial, OpenTraverse):- ignore(OpenTraverse = open_traverse(_How, Spatial)).
31equals_efffectly(sense, see, _).
32equals_efffectly(model, spatial, _).
33equals_efffectly(_, Value, Value).
34
35
36
39:- nop(ensure_loaded('adv_relation')). 41
42cant_be(Sense,Thing):-
43 notrace((freeze(Thing, (dmust(Thing\==Sense))), freeze(Sense, (dmust(Thing\==Sense))))).
44
45cant(Agent, Action, cant(sense(Spatial, Sense, Thing, Why)), State) :-
46 cant_be(Sense,Thing),
47 act_verb_thing_model_sense(Action, Verb, Thing, Spatial, Sense),
48 psubsetof(Verb, _),
49 \+ in_scope(Spatial, Thing, Agent, State),
50 (Why = (\+ in_scope(Spatial, Thing, Agent))).
51
52
53cant(Agent, Action, cant(sense(Spatial, Sense, Thing, Why)), State) :-
54 cant_be(Sense,Thing),
55 56 act_verb_thing_model_sense(Action, Verb, Thing, Spatial, Sense),
57 psubsetof(Verb, examine(Sense)),
58 \+ can_sense(Spatial, Sense, Thing, Agent, State),
59 (Why = ( \+ can_sense(Spatial, Sense, Thing, Agent))).
60
61cant(Agent, Action, cant(reach(Spatial, Thing)), State) :-
62 act_verb_thing_model_sense(Action, Verb, Thing, Spatial, _Sense),
63 psubsetof(Verb, touch),
64 \+ reachable(Spatial, Thing, Agent, State).
65
66cant(_Agent, Action, cant(move(Spatial, Thing)), State) :-
67 act_verb_thing_model_sense(Action, Verb, Thing, Spatial, _Sense),
68 psubsetof(Verb, move),
69 getprop(Thing, can_be(Spatial, move, f), State).
70
71cant(Agent, Action, musthave(Spatial, Thing), State) :-
72 act_verb_thing_model_sense(Action, Verb, Thing, Spatial, _Sense),
73 get_open_traverse(Verb, Spatial, OpenTraverse),
74 psubsetof(Verb, drop),
75 \+ related(Spatial, OpenTraverse, Thing, Agent, State).
76
77cant(Agent, Action, cant(manipulate(Spatial, self)), _) :-
78 Action =.. [Verb, Agent |_],
79 psubsetof(Verb, touch(Spatial)).
80cant(Agent, take(Spatial, Thing), alreadyhave(Thing), State) :-
81 related(Spatial, descended, Thing, Agent, State).
82cant(Agent, take(Spatial, Thing), mustgetout(Thing), State) :-
83 related(Spatial, descended, Agent, Thing, State).
84cant(_Agent, put(Spatial, Thing1, _How, Thing1), self_relation(Spatial, Thing1), _S0).
85cant(_Agent, put(Spatial, Thing1, _How, Thing2), moibeus_relation(Spatial, Thing1, Thing2), S0) :-
86 related(Spatial, descended, Thing2, Thing1, S0).
87cant(_Agent, throw(Spatial, Thing1, _How, Thing1), self_relation(Spatial, Thing1), _S0).
88cant(_Agent, throw(Spatial, Thing1, _How, Thing2), moibeus_relation(Spatial, Thing1, Thing2), S0) :-
89 related(Spatial, descended, Thing2, Thing1, S0).
90
91
92
93cant(Agent, look(Spatial), TooDark, State) :-
94 sensory_model_problem_solution(Sense, _Spatial, TooDark, _EmittingLight),
95 96 97 \+ has_sensory(Spatial, Sense, Agent, State).
98
103
104cant(Agent, examine(Sense, Thing), cant(sense(Spatial, Sense, Thing, TooDark)), State) :- equals_efffectly(sense, Sense, see),
105 cant_be(Sense,Thing),
106 sensory_model_problem_solution(Sense, Spatial, TooDark, _EmittingLight),
107 \+ has_sensory(Spatial, Sense, Agent, State).
108
109cant(Agent, examine(Sense, Thing), cant(sense(Spatial, Sense, Thing, Why)), State) :-
110 cant_be(Sense,Thing),
111 \+ can_sense(Spatial, Sense, Thing, Agent, State),
112 (Why = ( \+ can_sense(Spatial, Sense, Thing, Agent, State))).
113
114
115cant(Agent, goto(Spatial, _Relation, Object), mustdrop(Spatial, Object), State) :-
116 related(Spatial, descended, Object, Agent, State).
117
118cant(Agent, EatCmd, cantdothat(EatCmd), State) :-
119 action_model(EatCmd, Spatial),
120 getprop(Agent, can_do(Spatial, EatCmd, f), State).
121
122cant(Agent, EatCmd, cantdothat_verb(EatVerb, EatCmd), State) :-
123 act_verb_thing_model_sense(EatCmd, EatVerb, _Thing, Spatial, _Sense),
124 getprop(Agent, can_do(Spatial, EatVerb, f), State).
125
126
127
128
131:- nop(ensure_loaded('adv_relation')). 133
134related_with_prop(Spatial, How, Object, Place, Prop, State) :-
135 related(Spatial, How, Object, Place, State),
136 getprop(Object, Prop, State).
137
138is_state(Spatial, ~(Open), Object, State) :- ground(Open),!,
139 getprop(Object, state(Spatial, Open, f), State).
140is_state(Spatial, Open, Object, State) :-
141 getprop(Object, state(Spatial, Open, t), State).
144
145in_scope(_Spatial, Thing, _Agent, _State) :- Thing == '*', !.
146in_scope(Spatial, Thing, Agent, State) :-
147 get_open_traverse(_Open, _See, _Traverse, Spatial, OpenTraverse),
148 related(Spatial, OpenTraverse, Agent, Here, State),
149 (Thing=Here; related(Spatial, OpenTraverse, Thing, Here, State)).
150in_scope(Spatial, Thing, Agent, _State):- dbug(pretending_in_scope(Spatial, Thing, Agent)).
151
152reachable(_Spatial, Star, _Agent, _State) :- Star == '*', ! .
153reachable(Spatial, Thing, Agent, State) :-
154 get_open_traverse(touch, Spatial, OpenTraverse),
155 related(Spatial, child, Agent, Here, State), 156 (Thing=Here; related(Spatial, OpenTraverse, Thing, Here, State)).
157
158
161:- nop(ensure_loaded('adv_relation')). 163
164
165subrelation(in, child).
166subrelation(on, child).
169subrelation(worn_by, child).
170subrelation(held_by, child).
171
172has_rel(Spatial, How, X, State) :-
173 getprop(X, has_rel(Spatial, How), State).
174has_rel(Spatial, How, X, State) :-
175 getprop(X, has_rel(Spatial, Specific), State),
176 subrelation(Specific, How).
177
179related(_Spatial, _How, _X, _Y, []) :- !, fail.
180related(Spatial, How, X, Y, State):- quietly(related_hl(Spatial, How, X, Y, State)).
181
182
183related_hl(Spatial, How, X, Y, State) :- declared(h(Spatial, How, X, Y), State).
184related_hl(_Spatial, How, _X, _Y, _State) :- var(How), !, fail.
185related_hl(Spatial, child, X, Y, State) :- subrelation(How, child), related_hl(Spatial, How, X, Y, State).
186related_hl(Spatial, descended, X, Z, State) :-
187 related_hl(Spatial, child, X, Z, State).
188related_hl(Spatial, descended, X, Z, State) :-
189 related_hl(Spatial, child, Y, Z, State),
190 related_hl(Spatial, descended, X, Y, State).
191related_hl(Spatial, open_traverse(Traverse, Spatial), X, Z, State) :-
192 get_open_traverse(_Traverse, Spatial, open_traverse(Traverse, Spatial)),
193 related_hl(Spatial, child, X, Z, State).
194related_hl(Spatial, open_traverse(Traverse, Spatial), X, Z, State) :-
195 get_open_traverse(Open, _See, _Traverse, Spatial, open_traverse(Traverse, Spatial)),
196 related_hl(Spatial, child, Y, Z, State),
197 \+ is_state(Spatial, ~(Open), Y, State),
198 related_hl(Spatial, open_traverse(Traverse, Spatial), X, Y, State).
199related_hl(Spatial, inside, X, Z, State) :- related_hl(Spatial, in, X, Z, State).
200related_hl(Spatial, inside, X, Z, State) :- related_hl(Spatial, in, Y, Z, State),
201 related_hl(Spatial, descended, X, Y, State).
202related_hl(Spatial, exit(out), Inner, Outer, State) :-
203 related_hl(Spatial, child, Inner, Outer, State),
204 has_rel(Spatial, in, Inner, State),
205 has_rel(Spatial, child, Outer, State),
206 get_open_traverse(Open, _See, _Traverse, Spatial, _OpenTraverse),
207 \+ is_state(Spatial, ~(Open), Inner, State).
208related_hl(Spatial, exit(off), Inner, Outer, State) :-
209 related_hl(Spatial, child, Inner, Outer, State),
210 has_rel(Spatial, on, Inner, State),
211 has_rel(Spatial, child, Outer, State).
212related_hl(Spatial, exit(escape), Inner, Outer, State) :-
213 related_hl(Spatial, child, Inner, Outer, State),
214 has_rel(Spatial, child, Inner, State),
215 has_rel(Spatial, child, Outer, State).
216
217
218
219
222:- nop(ensure_loaded('adv_action')). 224
225moveto(Spatial, Object, How, Dest, Vicinity, Msg, State, S9) :-
226 undeclare(h(Spatial, _, Object, Here), State, VoidState),
227 declare(h(Spatial, How, Object, Dest), VoidState, S2),
228 queue_local_event(Spatial, [moved(Spatial, Object, Here, How, Dest), Msg], Vicinity, S2, S9).
229
230moveallto(_Spatial, [], _R, _D, _V, _M, S, S).
231moveallto(Spatial, [Object|Tail], Relation, Destination, Vicinity, Msg, S0, S2) :-
232 moveto(Spatial, Object, Relation, Destination, Vicinity, Msg, S0, S1),
233 moveallto(Spatial, Tail, Relation, Destination, Vicinity, Msg, S1, S2).
234
235disgorge(Spatial, Container, How, Here, Vicinity, Msg, S0, S9) :-
236 findall(Inner, related(Spatial, child, Inner, Container, S0), Contents),
237 bugout('~p contained ~p~n', [Container, Contents], general),
238 moveallto(Spatial, Contents, How, Here, Vicinity, Msg, S0, S9).
239disgorge(_Spatial, _Container, _How, _Here, _Vicinity, _Msg, S0, S0).
240
241thrown(Spatial, Thing, _Target, How, Here, Vicinity, S0, S9) :-
242 getprop(Thing, fragile(Broken), S0),
243 bugout('object ~p is fragile~n', [Thing], general),
244 undeclare(h(Spatial, _, Thing, _), S0, S1),
245 declare(h(Spatial, How, Broken, Here), S1, S2),
246 queue_local_event(Spatial, [transformed(Thing, Broken)], Vicinity, S2, S3),
247 disgorge(Spatial, Thing, How, Here, Vicinity, 'Something falls out.', S3, S9).
248thrown(Spatial, Thing, _Target, How, Here, Vicinity, S0, S9) :-
249 moveto(Spatial, Thing, How, Here, Vicinity, 'Thrown.', S0, S9).
250
251hit(Spatial, Target, _Thing, Vicinity, S0, S9) :-
252 getprop(Target, fragile(Broken), S0),
253 bugout('target ~p is fragile~n', [Target], general),
254 undeclare(h(Spatial, How, Target, Here), S0, S1),
255 queue_local_event(Spatial, [transformed(Target, Broken)], Vicinity, S1, S2),
256 declare(h(Spatial, How, Broken, Here), S2, S3),
257 disgorge(Spatial, Target, How, Here, Vicinity, 'Something falls out.', S3, S9).
258hit(_Spatial, _Target, _Thing, _Vicinity, S0, S0).
259
260
261
262
263act_verb_thing_model_sense(Action, Verb, Thing, Spatial, Sense):-
264 cant_be(Sense,Thing),
265 notrace(act_verb_thing_model_sense0(Action, Verb, Thing, Spatial, Sense)), !.
266
267act_verb_thing_model_sense0(goto(Spatial, *, Thing), goto, Thing, Spatial, see):-!.
268act_verb_thing_model_sense0(look(spatial), look, *, spatial, see):-!.
269act_verb_thing_model_sense0(look(spatial, spatial), look, *, spatial, see):-!.
270act_verb_thing_model_sense0(look, look, *, spatial, see):-!.
271act_verb_thing_model_sense0(look, look, *, spatial, Sense):- is_sense(Sense), !.
272
273act_verb_thing_model_sense0(Action, Verb, Thing, W1, Sense):-
274 Action=..[Verb, W1|Rest],
275 W1 == spatial, !,
276 Action2=..[Verb|Rest],
277 act_verb_thing_model_sense(Action2, Verb, Thing, _Spatial, Sense).
278act_verb_thing_model_sense0(Action, Verb, Thing, Spatial, Sense):-
279 Action=..[Verb, Sense|Rest],
280 is_sense(Sense), !,
281 Action2=..[Verb|Rest],
282 act_verb_thing_model_sense0(Action2, Verb, Thing, Spatial, _Sense).
283act_verb_thing_model_sense0(Action, Verb, Thing, Spatial, Sense):-
284 Action=..[Verb, W1|Rest],
285 atom(W1), atom_concat(W2, 'ly', W1), !,
286 Action2=..[Verb, W2|Rest],
287 act_verb_thing_model_sense0(Action2, Verb, Thing, Spatial, Sense).
288act_verb_thing_model_sense0(Action, Verb, Thing, Spatial, Sense):-
289 Action=..[Verb, Prep|Rest],
290 preposition(Spatial, Prep), !,
291 Action2=..[Verb|Rest],
292 act_verb_thing_model_sense0(Action2, Verb, Thing, _Spatial, Sense).
293act_verb_thing_model_sense0(Action, Verb, Thing, Spatial, Sense):-
294 Action=..[Verb, Thing|_], !,
295 act_verb_thing_model_sense0(Verb, _UVerb, _UThing, Spatial, Sense).
296act_verb_thing_model_sense0(Action, Verb, '*', Spatial, Sense):-
297 Action=..[Verb], dmust((action_sensory(Verb, Sense), action_model(Verb, Spatial))), !