1/* * module * 
    2% This is a *very* simple example of an agent meant to be 
    3% used as prey (dead prey turns into food) in simple simulations.
    4%
    5% prey.pl
    6%
    7% July 8, 1996
    8% John Eikenberry
    9%
   10% Dec 13, 2035
   11% Douglas Miles
   12%
   13*/
   14
   15:- include(prologmud(mud_header)).   16
   17% Declare the module name and the exported (public) predicates.
   18:-swi_module(mobPrey,[]).   19
   20:- include(prologmud(mud_header)).   21% :- register_module_type (planning).
   22% :- register_module_type (mtCommand).
   23
   24ttAgentType(mobPrey).
   25resultIsa(aPreyFn(ftInt),mobPrey).
   26
   27% Predicates asserted during run.
   28% :- dynamic memory/2. 
   29%:- dynamic agent_list/1.
   30
   31world_agent_plan(_World,Self,Act):-
   32   isa(Self,mobPrey),
   33   prey_idea(Self,Act).
   34   
   35% Possible agent actions.
   36prey_idea(Self,actMove(Dir)) :-
   37	mudGetPrecepts(Self,List),
   38	list_agents(Agents),
   39	obj_memb(NearAgnt,Agents),
   40	list_object_dir_sensed(_,List,NearAgnt,OppDir),
   41	reverse_dir(OppDir,Dir),
   42	number_to_dir(Num,Dir,vHere),
   43	nth1(Num,List,What),
   44	What == [].
   45prey_idea(Self,actTake(tNut)) :-
   46	mudNearBody(Self,What),
   47	member(tNut,What).
   48prey_idea(Self,actEat(tNut)) :-
   49	mudEnergy(Self,Charge),
   50	Charge < 120,
   51	mudPossess(Self,tNut).
   52prey_idea(Self,actMove(Dir)) :-
   53	mudGetPrecepts(Self,List),
   54	list_object_dir_sensed(_,List,tNut,Dir).
   55prey_idea(_Agent,_) :-
   56	actSpawnPrey.
   57
   58prey_idea(Agent,Act) :- move_or_sit_memory_idea(Agent,Act,[tNut]).
   59
   60
   61
   62% spawn new prey
   63% maybe(N) == N chance of each agent spawning a new agent each turn
   64
   65vtActionTemplate(actSpawn(tCol)).
   66
   67baseKB:agent_command(_Agent,actSpawn(mobPrey)):-actSpawnPrey.
   68
   69actSpawnPrey :-
   70	% maybe(10),
   71	spawn_prey(1),
   72	!,
   73	fail.
   74
   75% Doesn't actually create a new prey, but revives a dead one.
   76% This allows for absolute control of the max number of prey 
   77% which is important for performance considerations
   78% (too many prey slows the simulation to a crawl)
   79% 10 slows my P5-100 down a lot... 
   80spawn_prey(10) :-
   81	!.
   82spawn_prey(N) :-
   83       Prey = aPreyFn(N),
   84       assert_isa(Prey,mobPrey),
   85       put_in_world(Prey),!.
   86
   87       /*
   88       get_instance_default_props(Prey,Traits),
   89	\+ mudAgentTurnnum(Prey,_),
   90         req1(predInstMax(Prey,mudEnergy,NRG)),
   91         req1(predInstMax(Prey,mudHealth,Dam)),
   92         clr(mudEnergy(Prey,_)),
   93         clr(mudHealth(Prey,_)),
   94         ain(mudEnergy(Prey,NRG)),
   95         ain(mudHealth(Prey,Dam)),
   96         ain(mudAgentTurnnum(Prey,1)),
   97         clr(mudPossess(Prey,_)),
   98	set_stats(Prey,Traits),
   99	
  100        % add_missing_instance_defaults(Prey),
  101	!.
  102        */
  103
  104spawn_prey(N) :-
  105	Ntemp is N + 1,
  106	spawn_prey(Ntemp).
  107
  108
  109:- include(prologmud(mud_footer)).