13
15:-swi_module(where_cmd, []). 16
17:- include(prologmud(mud_header)). 18
20
22baseKB:agent_text_command(Agent,["where",BE,X],Agent,actWhere(X)):-memberchk(BE,[is,are,be,were]).
23baseKB:agent_text_command(Agent,["where_is",X],Agent,actWhere(X)).
24baseKB:action_info(actWhere(ftTerm),"Tells where something is").
25baseKB:agent_call_command(_Agent,actWhere(SObj)) :-
26 forall(
27 (mudAtLoc(Obj,LOC), match_object(SObj,Obj)),
28 fmt(cmdresult(actWhere,mudAtLoc(Obj,LOC)))).
29
30
31baseKB:action_info(actWho(isOptional(tAgent,isMissing)),"Lists who is online (where they are at least)").
32
33baseKB:agent_call_command(_Gent,actWho(W)) :- must(mud_cmd_who(W)),!.
34baseKB:agent_call_command(_Gent,actWho) :- must(mud_cmd_who(_W)),!.
35
36mud_cmd_who(isMissing):- mud_cmd_who_1(_),!.
37mud_cmd_who(Who):- mud_cmd_who_1(Who),!.
38
39mud_cmd_who_1(Who):-
40 must( forall(no_repeats(tAgent(Who)),
41 ignore((
42 no_repeats(inRegion(Who,Where)),
43 ignore(lmcache:agent_session(Who,Session)),
44 fmt(cmdresult(actWho(Who),inRegion(Who,Where),agent_session(Who,Session))))))).
45
46:- include(prologmud(mud_footer)).