1%:- if(( ( \+ ((current_prolog_flag(logicmoo_include,Call),Call))) )). 
    2% :- module(world, []).
    3%:- endif.
    4/* * module  
    5% Common place to reduce redundancy World utility prediates
    6%
    7% Logicmoo Project PrologMUD: A MUD server written in Prolog
    8% Maintainer: Douglas Miles
    9% Dec 13, 2035
   10%
   11% Special thanks to code written on
   12% May 18, 1996
   13% written by John Eikenberry
   14% interface by Martin Ronsdorf
   15% general assistance Dr. Donald Nute
   16%
   17*/
   18
   19% mtProlog(world).
   20:-export((
   21        % a_unparsed/2,
   22       % call_agent_action/2,
   23       get_agent_sessions/2,
   24            %mud_isa/2,
   25            isa_any/2,
   26            put_in_world/1,
   27            pathBetween_call/3,
   28            obj_memb/2,
   29            prop_memb/2,            
   30            from_dir_target/3,
   31            create_instance/2,create_instance/3,
   32            create_agent/1,
   33            create_agent/2,
   34            in_world_move/3, check_for_fall/3,
   35            agent_into_corpse/1, display_stats/1,
   36            reverse_dir/2,
   37            
   38            round_loc/8,
   39            round_loc_target/8,
   40            dir_offset/5,
   41            number_to_dir/3,
   42            list_agents/1,
   43            
   44            agent_list/1,
   45            check_for_fall/3,
   46            list_object_dir_sensed/4,
   47            list_object_dir_near/3,
   48            num_near_reverse/3,
   49            asInvoked/2,
   50            %decl_type/1,
   51            
   52                       
   53         init_location_grid/1,
   54         grid_dist/3,
   55         to_3d/2,
   56         is_3d/1,
   57         in_grid/2,
   58         loc_to_xy/4,
   59         grid_size/4,
   60         doorLocation/5,
   61         foc_current_agent/1,
   62         locationToRegion/2,
   63         init_location_grid/2,
   64         
   65         do_act_affect/3,
   66         %spread/0,
   67         %growth/0,
   68         isaOrSame/2,
   69         current_agent_or_var/1)).   70
   71
   72:-discontiguous create_instance_0/3.   73
   74:-export((
   75          create_instance/2,
   76          create_instance/3,
   77          create_instance_0/3,
   78          create_agent/1,
   79          create_agent/2)).   80
   81:- dynamic  agent_list/1.   82% :- kb_shared(mudDescription/2).
   83
   84:- include(prologmud(mud_header)).   85% :- register_module_type (utility).
   86
   87ensure_pfc_loaded(F):-atom_concat(F,'.pfc',FF),ensure_loaded(FF).
   88
   89:- ensure_pfc_loaded(world_2d).   90:- ensure_pfc_loaded(world_text).   91:- ensure_pfc_loaded(world_text_output).   92:- ensure_pfc_loaded(world_effects).   93:- ensure_pfc_loaded(world_events).   94:- ensure_pfc_loaded(world_agent).   95:- ensure_pfc_loaded(world_npc).   96
   97% :- if_file_exists(include(logicmoo('vworld/world_spawning.pl'))).
   98
   99:-export(isaOrSame/2).  100isaOrSame(A,B):-A==B,!.
  101isaOrSame(A,B):-isa(A,B).
  102
  103intersect(A,EF,B,LF,Tests,Results):-findall( A-B, ((member(A,EF),member(B,LF),once(Tests))), Results),[A-B|_]=Results.
  104% is_property(P,_A),PROP=..[P|ARGS],CALL=..[P,Obj|ARGS],req1(CALL).
  105
  106obj_memb(E,L):-is_list(L)->member(E,L);E=L.
  107
  108isa_any(E,L):-flatten([E],EE),flatten([L],LL),!,intersect(A,EE,B,LL,isaOrSame(A,B),_Results).
  109
  110prop_memb(E,L):-flatten([E],EE),flatten([L],LL),!,intersect(A,EE,B,LL,isaOrSame(A,B),_Results).
  111
  112
  113tCol(tItem).
  114tCol(tAgent).
  115tCol(tRegion).
  116tCol(tItem).
  117tSet(tItem).
  118existingThing(O):-tItem(O).
  119existingThing(O):-tAgent(O).
  120existingThing(O):-tRegion(O).
  121anyInst(O):-tCol(O).
  122anyInst(O):-existingThing(O).
  123
  124/*
  125
  126
  127% meta_argtypes(typeGenls(col,metaclass)).
  128
  129%OLD decl_database_hook(change(assert,_),typeGenls(_,MC)):-assert_isa(MC,ttTypeType).
  130
  131% deduce_facts(typeGenls(T,MC),deduce_facts(genls(S,T),isa(S,MC))).
  132
  133
  134*/
  135
  136%genls(SubType,formattype):-isa(SubType,formattype).
  137
  138%cached(G):-catch(G,_,fail).
  139
  140
  141tCol(ttNotSpatialType).
  142
  143ttNotSpatialType(ftInt).
  144ttNotSpatialType(ftTerm).
  145
  146genls(tWearAble,tItem).
  147genls(tItem,tLookAble).
  148genls(tRegion,tLookAble).
  149genls(tObj,tLookAble).
  150genls(tKnife,tItem).
  151genls(tFood,tItem).
  152
  153
  154%ttSpatialType(FT):- nonvar(FT),ttExpressionType(FT),!,fail.
  155%ttSpatialType(FT):- nonvar(FT),ttNotSpatialType(FT),!,fail.
  156%ttSpatialType(tItem). %  col, formattype, 
  157% ttSpatialType(SubType):-member(SubType,[tAgent,tItem,tRegion]).
  158%ttSpatialType(S):- is_asserted(ttSpatialType(T)), impliedSubClass(S,T).
  159
  160%createableSubclassType(S,T):-req1(  ttSpatialType(T)),is_asserted(genls(S,T)).
  161%createableSubclassType(T,tSpatialThing):-req1( ttSpatialType(T)).
  162
  163create_agent(P):-functor(P,isKappaFn,_),!.
  164create_agent(P):-create_agent(P,[]).
  165create_agent(P,List):- must(create_instance(P,tAgent,List)),!.
  166
  167
  168
  169
  170:-export(create_instance/1).  171create_instance(P):- must(call_u((isa(P,What),ttSpatialType(What)))),must(create_instance(P,What,[])),!.
  172:-export(create_instance/2).  173create_instance(Name,Type):-create_instance(Name,Type,[]).
  174%create_instance(Name,Type):-create_instance(Name,Type,[]).
  175:-export(create_instance/3).  176create_instance(What,Type,Props):- 
  177  loop_check(time_call(create_instance_now(What,Type,Props)),dmsg(already_create_instance(What,Type,Props))).
  178
  179create_instance_now(What,Type,Props):-
  180  must((var(Type);atom_concat('t',_,Type ))),!,
  181 locally_tl(t_l:agenda_suspend_scans,
  182  locally_tl(t_l:deduceArgTypes(_),
  183  locally_hide(t_l:useOnlyExternalDBs,
  184   locally_hide(t_l:noRandomValues(_),
  185     locally_hide(t_l:infInstanceOnly(_),   
  186      locally_hide(t_l:infAssertedOnly(_),
  187        locally_hide(baseKB:use_cyc_database, 
  188     ((split_name_type(What,Inst,_WhatType),assert_isa(Inst,Type), (create_instance_0(What,Type,Props)->true)))))))))),!.
  189
  190:-discontiguous create_instance_0/3.  191
  192:-export(is_creating_now/1).  193:- dynamic(is_creating_now/1).  194:- dynamic(create_instance_0/3).  195
  196
  197create_instance_0(What,Type,List):- (var(What);var(Type);var(List)),trace_or_throw((var_create_instance_0(What,Type,List))).
  198create_instance_0(I,_,_):-is_creating_now(I),!.
  199create_instance_0(I,_,_):-asserta_if_new(is_creating_now(I)),fail.
  200create_instance_0(What,FormatType,List):- FormatType\==tCol, ttExpressionType(FormatType),!,trace_or_throw(ttExpressionType(FormatType,create_instance(What,FormatType,List))).
  201create_instance_0(SubType,tCol,List):-ain(tCol(SubType)),(List==[]->true;padd(SubType,List)).
  202
  203==>ttSpatialType(tAgent).
  204==>genls(tActor,tAgent).
  205==>genls(mobExplorer,tAgent).
  206
  207==>prologHybrid(predTypeMax/3).
  208==>prologHybrid(predInstMax/3).
  209
  210%NEXT TODO predInstMax(I,mudEnergy,NRG):- infSecondOrder, predTypeMax(mudEnergy,AgentType,NRG),isa(I,AgentType).
  211%predInstMax(I,mudHealth,Dam):- predTypeMax(mudHealth,AgentType,Dam),isa(I,AgentType).
  212
  213punless(Cond,Action):- once((call(Cond);call(Action))).
  214
  215create_instance_0(T,tAgent,List):-
  216  must_det_l((
  217   retractall(agent_list(_)),
  218   create_meta(T,_,tAgent,P),
  219   mreq(isa(P,tAgent)),
  220   padd(P,List),   
  221   % punless(mudPossess(P,_),modCreate:rez_to_inventory(P,food,_Food)),
  222   find_and_call(rez_to_inventory(P,tFood,_Food)),
  223   %reset_values(P),   
  224   padd(P, [ predInstMax(mudHealth,500),
  225                       predInstMax(mudEnergy,200),
  226                       mudHealth(500),
  227                       % mudEnergy(90),
  228                       mudAgentTurnnum(0),
  229                       mudScore(1)]),   
  230   % set_stats(P,[]),
  231   put_in_world(P),
  232   add_missing_instance_defaults(P))).
  233
  234add_missing_instance_defaults(P):- ain(tNewlyCreated(P)).
  235   
  236/*
  237reset_values(I):- forall(valueReset(To,From),reset_value(I,To,From)).
  238
  239reset_value(I,To,From):- prop(I,From,FromV), padd(I,To,FromV),!.
  240reset_value(I,To,From):- prop(I,From,FromV), padd(I,To,FromV),!.
  241   
  242   (contains_var(V,value),get_value(P,V,Result)) -> subst(V,P,isThis)
  243   argIsa(P,SVArgNum,Type),
  244   is_term_ft(V,Type),
  245
  246valueReset(score,0).
  247valueReset(health,max_health).
  248valueReset(charge,max_charge).
  249
  250*/
  251
  252tCol(tTable).
  253relationMostInstance(mudColor, tTable, vWhite).
  254
  255%typeProps(Type,Props),isa(Obj,Type),{flatten([Props],VoProps)} ==> props(Obj,VoProps).
  256ttSpatialType(tRegion).
  257
  258create_instance_0(T, tItem, List):-
  259   isa(T,What),What\=tItem, ttSpatialType(What),!,create_instance_0(T, What, List).
  260
  261/*
  262create_instance_0(T,Type,List):-
  263  createableSubclassType(Type,MetaType),!,
  264  must_det_l([
  265   create_meta(T,Type,MetaType,P),
  266   padd(P,List),
  267   add_missing_instance_defaults(P)]). 
  268*/
  269
  270create_instance_0(T,MetaType,List):-  
  271  call_u((must_det_l((
  272   create_meta(T,_Type,MetaType,P),
  273   padd(P,List),
  274   add_missing_instance_defaults(P))))),!. 
  275
  276create_instance_0(What,Type,Props):- leash(+call),wdmsg(assumed_To_HAVE_creted_isnance(What,Type,Props)),!.
  277
  278%ttSpatialType(col).
  279
  280
  281
  282% already convered mudPossess(Who,Thing):-genlInverse(W,mudPossess),into_mpred_form(t(W,Thing,Who),Call),req1(Call).
  283% already convered mudPossess(Who,Thing):-genlPreds(mudPossess,W),into_mpred_form(t(W,Who,Thing),Call),req1(Call).
  284
  285
  286% :- include(prologmud(mud_footer)).
  287
  288:- all_source_file_predicates_are_transparent.