1% any.pl
    2% Dec 13, 2035
    3% Douglas Miles
    4%
    5% This file defines the basic ANY verb that has the four elements of 
    6% 
    7%  action_requires_states(Agent,StateRules,REQS),
    8%  action_removes_states(Agent,StateRules,REMS),
    9%  states_types(Agent,StateRules,TYPES),
   10%  action_adds_states(Agent,StateRules,ADDS),
   11% 
   12
   13% :-swi_module(user). 
   14:- swi_module(any, []).   15
   16
   17
   18:- include(prologmud(mud_header)).   19
   20% :- register_module_type (mtCommand).
   21action_rules(_,_,_,_):-fail.
   22
   23to_verb_args(Act,List):-safe_univ(Act,List).
   24
   25action_adds_states(Agent,Action,A):- action_rules(Agent,VERB,SENT,StateRules),to_verb_args(Action,[VERB|SENT]), member(+(A),StateRules).
   26action_removes_states(Agent,Action,A):- action_rules(Agent,VERB,SENT,StateRules),to_verb_args(Action,[VERB|SENT]), member(-(A),StateRules).
   27action_requires_states(Agent,Action,A):- action_rules(Agent,VERB,SENT,StateRules),to_verb_args(Action,[VERB|SENT]),member(?(A),StateRules).
   28
   29:- op(200,fy,'?').   30==>action_rules(Agent,actTestWield,[Obj],[?mudPossess(Agent,Obj),?isa(Obj,tUseAble),-mudStowing(Agent,Obj),+mudWielding(Agent,Obj)]).
   31==>action_rules(Agent,actTestStow,[Obj],[?mudPossess(Agent,Obj),?isa(Obj,tStowAble),?genlPreds(Using,'mudControls'),
   32  - t(Using,Agent,Obj),+mudStowing(Agent,Obj)]).
   33
   34guess_verb_template(Action):-
   35       action_rules(_Agent,Verb,Args,ListA),
   36       once((to_verb_args(Action,[Verb|Args]),
   37            must(attempt_attribute_args(_AndOr,ftAskable,ListA)),
   38            must(term_variables(ListA,Vars)),
   39            must(attribs_to_atoms(Vars,Vars)))). 
   40         
   41
   42% Use something
   43baseKB:agent_call_command(Agent,ACT) :-
   44   call((action_rules(Agent,VERB,SENT,_StateRules),safe_univ(ACT,[VERB|SENT]))),
   45   
   46      action_requires_states(Agent,[VERB|SENT],REQS),
   47      action_removes_states(Agent,[VERB|SENT],REMS),
   48      action_adds_states(Agent,[VERB|SENT],ADDS),
   49     call_update_charge(Agent,VERB),
   50     ((
   51         req1(REQS)) ->
   52         ((clr(REMS),
   53         ain(ADDS),
   54         call_update_charge(Agent,VERB)));	
   55%Nothing to use
   56      (add_cmdfailure(Agent,SENT))).
   57
   58:- include(prologmud(mud_footer)).