1/* Part of LogicMOO Base logicmoo_util_bb_env
    2% Provides a prolog database *env*
    3% ===================================================================
    4% File '$FILENAME.pl'
    5% Purpose: An Implementation in SWI-Prolog of certain debugging tools
    6% Maintainer: Douglas Miles
    7% Contact: $Author: logicmoo@gmail.com ;
    8% Version: '$FILENAME.pl' 1.0.0
    9% Revision: $Revision: 1.1 $
   10% Revised At:  $Date: 2021/07/11 21:57:28 $
   11% Licience: LGPL
   12% ===================================================================
   13*/
   14% File: /opt/PrologMUD/pack/logicmoo_base/prolog/logicmoo/util/logicmoo_util_structs.pl
   15:- module(logicmoo_util_structs,
   16          [ % attr_portray_hook/2,
   17            % attr_unify_hook/2,
   18            by_name_datatype/2,
   19            compile_argtypes/3,
   20            compile_struct_slots/6,
   21            datatype_to_init/2,
   22            decl_argtypes/1,
   23            decl_struct/1,
   24            ensure_instance/2,
   25            ensure_instance/3,
   26            ensure_struct/2,
   27            ensure_struct/3,
   28            extract_struct_parameter/4,
   29            extract_struct_parameter/5,
   30            hooked_gvar_get/2,
   31            hooked_gvar_put/2,
   32            if_changed_struct/3,
   33            key_match/2,
   34            member_arg_convert/5,
   35            %us:member_datatype/2,
   36            merge_values/3,
   37            nb_set_pairlist/3,
   38            nb_set_pairlist0/3,
   39            nb_set_s2list/4,
   40            nb_set_s2list0/4,
   41            nb_setarg_ex/3,
   42            new_struct/2,
   43            prop_get/1,
   44            prop_get/3,
   45            prop_get_map/3,
   46            prop_get_nvlist/2,
   47            prop_get_try/4,
   48            prop_merge/3,
   49            prop_put_extra_extra/2,
   50            prop_set/1,
   51            prop_set/3,
   52            prop_set_dict_real/4,
   53            prop_set_map/3,
   54            prop_set_nvlist/2,
   55            prop_set_try/4,
   56            record_onto_var/3,
   57            record_var_names/1,
   58            record_var_names/2,
   59            record_var_type/2,
   60            sisctus_key/2,
   61            struct_sclass/2,
   62            t2ot/2,
   63            t2ot_0/2,
   64            term_to_ord_term/2,
   65            to_datatype/3
   66          ]).

Utility LOGICMOO_UTIL_STRUCTS

This module allows use of C++ like structures in prolog.

   73:- meta_predicate
   74        sisctus_key(:, -).   75:- module_transparent
   76        by_name_datatype/2,
   77        compile_argtypes/3,
   78        compile_struct_slots/6,
   79        datatype_to_init/2,
   80        decl_argtypes/1,
   81        decl_struct/1,
   82        ensure_instance/2,
   83        ensure_instance/3,
   84        ensure_struct/2,
   85        ensure_struct/3,
   86        extract_struct_parameter/4,
   87        extract_struct_parameter/5,
   88        hooked_gvar_get/2,
   89        hooked_gvar_put/2,
   90        if_changed_struct/3,
   91        key_match/2,
   92        member_arg_convert/5,
   93        %us:member_datatype/2,
   94        merge_values/3,
   95        %module_local_init /2,
   96        nb_set_pairlist/3,
   97        nb_set_pairlist0/3,
   98        nb_set_s2list/4,
   99        nb_set_s2list0/4,
  100        nb_setarg_ex/3,
  101        new_struct/2,
  102        prop_get/1,
  103        prop_get/3,
  104        prop_get_map/3,
  105        prop_get_nvlist/2,
  106        prop_get_try/4,
  107        prop_merge/3,
  108        prop_put_extra_extra/2,
  109        prop_set/1,
  110        prop_set/3,
  111        prop_set_dict_real/4,
  112        prop_set_map/3,
  113        prop_set_nvlist/2,
  114        prop_set_try/4,
  115        record_onto_var/3,
  116        record_var_names/1,
  117        record_var_names/2,
  118        record_var_type/2,
  119        struct_sclass/2,
  120        t2ot/2,
  121        t2ot_0/2,
  122        term_to_ord_term/2,
  123        to_datatype/3.  124
  125% :- dynamic module_local_init/2.
  126
  127:- if(current_module(logicmoo_utils)).  128:- public((
  129  prop_get/1,prop_get/3,prop_set/1,prop_set/3,prop_merge/3,
  130  prop_set_nvlist/2,
  131  decl_argtypes/1,
  132  decl_struct/1,
  133  %us:struct_decl/1,
  134  if_changed_struct/3,
  135  prop_get_nvlist/2,
  136  term_to_ord_term/2,
  137  new_struct/2,
  138  ensure_struct/2,ensure_struct/3,
  139  ensure_instance/2,ensure_instance/3)).  140:- else.  141
  142:- endif.  143:- set_module(class(library)).  144
  145
  146
  147:- ensure_loaded(library(record)).  148:- ensure_loaded(library(rbtrees)).  149:- ensure_loaded(library(ordsets)).  150
  151/*
  152default_point2d/1,
  153is _point2d/1,
  154make_point2d/2,
  155make_point2d/3,
  156nb_set_x_of_point2d/2,
  157nb_set_y_of_point2d/2,
  158point2d_data/3,
  159point2d_x/2,
  160point2d_y/2,
  161set_point2d_field/3,
  162set_point2d_fields/3,
  163set_point2d_fields/4,
  164set_x_of_point2d/2,
  165set_x_of_point2d/3,
  166set_y_of_point2d/2,
  167set_y_of_point2d/3,
  168*/
  169:- record(point2d(x:integer=0, y:integer=0)).  170     /*
  171        default_point2d(Point),
  172        point2d_x(Point, X),
  173        set_x_of_point2d(10, Point, Point1),
  174
  175        make_point2d([y(20)], YPoint),
  176   */
  177
  178:- use_module(library(assoc)).  179:- module_transparent(import_dynamic/1).  180import_dynamic(M:F/A):- 
  181  multifile(M:F/A),
  182  dynamic(M:F/A),
  183  M:export(M:F/A),
  184  system:import(M:F/A),
  185  import(M:F/A).
  186
  187:- import_dynamic(us:member_datatype/3).  188:- import_dynamic(us:member_init/3).  189:- import_dynamic(us:member_loc/3).  190:- import_dynamic(us:struct_datatype/2).  191:- import_dynamic(us:struct_decl/1).  192:- import_dynamic(us:struct_names/2).  193:- import_dynamic(us:struct_prototype/2).  194
  195% :- us:struct_datatype(_,_) -> true; true.
  196
  197
  198%= 	 	 
 record_onto_var(?VALUE1, ?VALUE2, ?VALUE3) is semidet
Record Onto Variable.
  204record_onto_var(AttribName,AV,Value):-
  205 ignore((
  206 atom(Value),var(AV), 
  207 ((get_attr(AV,lp,Dict),nonvar(Dict))-> true; (new_struct(map,Dict),put_attr(AV,lp,Dict))),
  208 (prop_get(AttribName,Dict,_)->true;prop_set(AttribName,Dict,AV)))).
  209
  210
  211%= 	 	 
 record_var_names(:TermARG1) is semidet
Record Variable Names.
  217record_var_names(V):- \+ compound(V),!.
  218record_var_names(N=V):-!,record_var_names(V,N).
  219record_var_names(List):-is_list(List),!,maplist(record_var_names,List).
  220record_var_names(Comp):-functor(Comp,_,A),arg(A,Comp,E),!,record_var_names(E).
  221
  222
  223%= 	 	 
 record_var_names(?VALUE1, ?VALUE2) is semidet
Record Variable Names.
  229record_var_names(ATTVAR,Value):-record_onto_var(vn,ATTVAR,Value).
  230
  231
  232
  233%= 	 	 
 record_var_type(?VALUE1, ?VALUE2) is semidet
Record Variable Type.
  239record_var_type(ATTVAR,Type):-record_onto_var(type,ATTVAR,Type).
  240
  241
  242/*
  243
  244prop_get(Name,mutable(Dict),Value):-!,nonvar(Dict),prop_get(Name,Dict,Value).
  245
  246
  247?- 
  248  prop_get(uses_domain, problem('blocks-3-0',blocks,[],[block([a,b,c])],[handempty,clear(a),clear(b),clear(c),ontable(a),ontable(b),ontable(c)],
  249   [on(b,a),on(c,b)],[],[],[],extraprops{constraints:[],goal:[on(b,a),on(c,b)],init:[handempty,clear(a),clear(b),clear(c),ontable(a),ontable(b),ontable(c)],
  250     length:[],metric:[],object:[block([a,b,c])],
  251      problem_filename:'/opt/PrologMUD/pack/logicmoo_base/prolog/logicmoo/planner/orig_pddl_parser/test/blocks/blocks-03-0.pddl',
  252      problem_name:'blocks-3-0',requires:[],uses_domain:blocks}),X).
  253
  254
  255
  256  ?-
  257
  258   Y = problem('blocks-3-0',blocks,[],[block([a,b,c])],[handempty,clear(a),clear(b),clear(c),ontable(a),ontable(b),ontable(c)],[on(b,a),
  259     on(c,b)],[],[],[],extraprops{constraints:[],goal:[on(b,a),on(c,b)],init:[handempty,clear(a),clear(b),clear(c),ontable(a),
  260     ontable(b),ontable(c)],length:[],metric:[],object:[block([a,b,c])],problem_filename:
  261     '/opt/PrologMUD/pack/logicmoo_base/prolog/logicmoo/planner/orig_pddl_parser/test/blocks/blocks-03-0.pddl',
  262     problem_name:'blocks-3-0',requires:[],uses_domain:blocks}).
  263
  264   ?- prop_get(init, $Y , O).
  265
  266   ?- prop_merge(init, $Y , suey(y)).
  267
  268      ?- prop_get(init, $Y , O).
  269
  270
  271   ?- prop_set(init, $Y , suey(y)).
  272
  273
  274*/
  275:-meta_predicate(sisctus_key(:,-)).  276
  277%= 	 	 
 sisctus_key(?CALL1, -IN2) is semidet
Sisctus Key.
  283sisctus_key(Module:Key, Atom) :- atom(Module), !,atomic(Key),atomic_list_concat([Module, Key], :, Atom).
  284
  285
  286%= 	 	 
 prop_get(?VALUE1) is semidet
Prop Get.
  292prop_get(Call):- Call=..[P,A,B],prop_get(P,A,B).
  293
  294
  295%= 	 	 
 prop_get(?VALUE1, ?VALUE2, ?VALUE3) is semidet
Prop Get.
  301prop_get(Name,Dict,Value):- (var(Name);var(Dict)),!,trace_or_throw(var_prop_get(Name,Dict,Value)).
  302prop_get(Name,Dict,Value):- nonvar(Value),!,must(prop_get(Name,Dict,ValueVar)),!,Value=ValueVar.
  303prop_get(_,     Dict, _ ):- ( \+ \+ Dict=[] ),!, fail.
  304prop_get(Name, Struct,  Value):- prop_get_try(Name, Struct,  Value, _),!.
  305prop_get(Name, Struct,  Value):- Name \= extraprops, prop_get(extraprops, Struct,  Extra),
  306                                              prop_get_try(Name, Extra,  Value, _),!.
  307prop_get(Name,_Struct, Value):-hooked_gvar_get(Name,  Value).
  308
  309
  310%= 	 	 
 hooked_gvar_get(?VALUE1, ?VALUE2) is semidet
Gvar Get.

hooked_gvar_get(Name, Value):- sisctus_key(Name,N),nb_current(N,ValueV),!,Value=ValueV.

  317hooked_gvar_get(Name,  Value):- nb_current(Name,Value),!.
  318hooked_gvar_get(_Name,  []):-!.
  319
  320
  321%= 	 	 
 hooked_gvar_put(?VALUE1, ?VALUE2) is semidet
Gvar Put.

hooked_gvar_put(Name, Value):- sisctus_key(Name,N),nb_current(N,_),!,nb_setval(N,Value).

  328hooked_gvar_put(Name,  Value):- nb_setval(Name,Value).
  329
  330
  331
  332
  333%= 	 	 
 key_match(?VALUE1, ?VALUE2) is semidet
Key Match.
  339key_match(Name,N):-atom(N), (Name=N -> true ; atom_concat(':',Name,N)).
  340
  341
  342%= 	 	 
 prop_get_try(?VALUE1, ?VALUE2, ?VALUE3, ?VALUE4) is semidet
Prop Get Try.
  348prop_get_try(_,     Dict, _  ,_ ):- ( \+ \+ Dict=[] ),!, fail.
  349prop_get_try(Name, bb,   Value, gvar(Name,Value)):- !, must(hooked_gvar_get(Name,Value)).
  350prop_get_try(_   , Atomic,  _  , _  ):- atomic(Atomic),!,fail.
  351prop_get_try(Name, Dict,   Value, Ref):- prop_get_map(Name, Dict, Value),!,must(Dict=Ref).
  352prop_get_try(Name, STRUCT,  Value, Ref):- STRUCT = mutable(Struct), !, prop_get_try(Name, Struct,  Value, Ref).
  353
  354
  355%= 	 	 
 prop_get_map(?VALUE1, :TermARG2, ?VALUE3) is semidet
Prop Get Map.
  361prop_get_map(_,    Dict,       _ ):- ( \+ \+ Dict=[] ),!, fail.
  362prop_get_map(Name, Struct,  Value):- is_list(Struct),memberchk(Name=Value,Struct).
  363prop_get_map(Name, Dict,    Value):- is_dict(Dict),!,get_dict(Name,Dict,Value).
  364prop_get_map(Name, Dict,    Value):- is_rbtree_t4(Dict),!,nb_rb_get_node(Dict,Name,Value).
  365prop_get_map(Name, Dict,    Value):- is_assoc(Dict),!,get_assoc(Dict,Name,Value).
  366
  367prop_get_map(Name, Struct,  Value):- Name==sclass, compound(Struct),functor(Struct,Value,_),!.
  368
  369prop_get_map(sclass, sterm(Type,_), Type).
  370prop_get_map(Name, sterm(_,LIST), Value):- append(_,[N,V|_],LIST),key_match(Name,N),!,V=Value.
  371
  372prop_get_map(Indx, Struct,  Value):- integer(Indx),!, arg(Indx,Struct,Value).
  373
  374prop_get_map(Name, Struct,  Value):- us:member_loc(StructName,Name,N), functor(Struct,StructName,_),!,
  375      must((integer(N) -> arg(N,Struct,Value); prop_get_map(Name, Struct,  Value))).
  376
  377
  378
  379
  380%= 	 	 
 prop_put_extra_extra(?VALUE1, ?VALUE2) is semidet
Prop Put Extra Extra.
  386prop_put_extra_extra(Struct,More):- must_det_l((prop_get(extraprops,Struct,Extras),prop_set(extraprops,Extras,More))).
  387  
  388
  389
  390
  391%= 	 	 
 prop_set(?VALUE1) is semidet
Prop Set.
  397prop_set(Call):- Call=..[P,A,B],prop_set(P,A,B).
  398
  399
  400
  401%= 	 	 
 prop_set(?VALUE1, ?VALUE2, ?VALUE3) is semidet
Prop Set.
  407prop_set(Name,Dict,Value):- (var(Name);var(Dict)),!,trace_or_throw(var_prop_set(Name,Dict,Value)).
  408prop_set(_,     Dict, _ ):- ( \+ \+ Dict=[] ),!, fail.
  409prop_set(Name,Dict,Value):- 
  410 member_arg_convert(Dict,Name,_,Value,NewValue) -> 
  411    must(((prop_set_try(Name,Dict,NewValue, NewDict ),NewDict==Dict)));
  412    must(((prop_set_try(Name,Dict,Value, NewDict ),NewDict==Dict))).
  413
  414
  415%= 	 	 
 prop_set_try(?VALUE1, ?VALUE2, ?VALUE3, ?VALUE4) is semidet
Prop Set Try.
  421prop_set_try(Name,Dict,Value,_):- (var(Name);var(Dict);var(Value)),!,trace_or_throw(var_prop_set(Name,Dict,Value)).
  422prop_set_try(_,    Dict,   _, _):- ( \+ \+ Dict=[] ),!, fail.
  423prop_set_try([Name],Dict,Value,NewDict):-!, prop_set_try(Name,Dict,Value, NewDict).
  424prop_set_try(Name, bb,   Value, _):- !, hooked_gvar_put(Name,Value).
  425prop_set_try(_,    Struct,   _, _):- ( \+ compound(Struct)),!,fail.
  426prop_set_try([Name,Last],Dict,Value,WasNewDict):- prop_get(Name,Dict,SubDict),prop_set_try(Last,SubDict,Value,NewSubDict),NewSubDict\==SubDict,prop_set_try(Name,Dict,NewSubDict,WasNewDict),!.
  427prop_set_try([Name|More],Dict,Value,WasNewDict):-prop_get(Name,Dict,SubDict),prop_set_try(More,SubDict,Value,NewDict),NewDict\==SubDict,prop_set_try(Name,Dict,NewDict,WasNewDict).
  428
  429prop_set_try( Name,Dict,Value, Dict):- Name = sclass, functor(Dict,F,_), F==Value,!.
  430prop_set_try( Name,Dict,Value, Dict):-  prop_set_map(Name,Dict,Value),!.
  431prop_set_try( Name,Dict,Value, NewDict) :- is_dict(Dict),!,prop_set_dict_real(Name,Dict,Value,NewDict).
  432
  433
  434
  435%= 	 	 
 prop_set_map(?VALUE1, ?VALUE2, ?VALUE3) is semidet
Prop Set Map.
  441prop_set_map(Name,Dict,Value):- (var(Name);var(Dict);var(Value)),!,trace_or_throw(var_prop_set_map(Name,Dict,Value)).
  442prop_set_map(sclass, STERM, Type):- STERM=sterm(Type,_), nb_setarg_ex(1,STERM,Type).
  443prop_set_map(Name, STERM, Value):- STERM=sterm(_,List),
  444  nb_set_s2list(Name,List,Value,NewList),(List\==NewList -> nb_setarg_ex(2,STERM,NewList) ; true).
  445
  446prop_set_map(Name,HDict,Value):- is_list(HDict), memberchk(sclass=_,HDict),!,nb_set_pairlist(Name,HDict,Value).
  447
  448prop_set_map(Name,HDict,Value):- compound(HDict), HDict = mutable(Dict),
  449   (Dict == [] -> nb_setarg(1,HDict,[Name=Value]) ;
  450    must_det_l((prop_set_try(Name,Dict,Value,NewDict),(Dict == NewDict -> true ; 
  451     (must(nonvar(NewDict)),nb_setarg_ex(1,HDict,NewDict)))))).
  452
  453prop_set_map(Name,Dict,Value):- is_rbtree_t4(Dict),!,nb_rb_insert(Name,Dict,Value).
  454prop_set_map(Name,List,Value):- is_list(List), !, nb_set_pairlist(Name,List,Value).
  455prop_set_map(Index,Dict,Value):- integer(Index),!, nb_setarg_ex(Index,Dict,Value).
  456prop_set_map(Name,Dict,Value):- functor(Dict,StructName,_),
  457   (us:member_loc(StructName,Name,N) -> nb_setarg_ex(N,Dict,Value);
  458     must_det_l((prop_get(extraprops,Dict,Extra),nonvar(Extra),prop_set(Name,Extra,Value)))).
  459
  460
  461
  462
  463
  464%= 	 	 
 prop_set_dict_real(?VALUE1, ?VALUE2, ?VALUE3, ?VALUE2) is semidet
Prop Set Dict Real.
  470prop_set_dict_real(Name,Dict,Value, Dict):-  get_dict(Name,Dict,Old),!, (Value==Old -> (!); ((nb_set_dict(Name,Dict,Value)))),!.
  471prop_set_dict_real(Name,Dict,Value, NewDict):- put_dict(Name,Dict,Value,NewDict).
  472
  473
  474%= 	 	 
 nb_set_pairlist(?VALUE1, ?VALUE2, ?VALUE3) is semidet
Non Backtackable Set Pairlist.
  480nb_set_pairlist(Name,List,Value):- must(List=[_|_]), must(nb_set_pairlist0(Name,List,Value)).
  481
  482%= 	 	 
 nb_set_pairlist0(?VALUE1, ?VALUE2, ?VALUE3) is semidet
Non Backtackable Set Pairlist Primary Helper.
  488nb_set_pairlist0(Name,List,Value):- 
  489     List = [PName=_|T],!,
  490          ((PName==Name -> nb_setarg_ex(1,List,Name=Value) ;
  491           T == [] -> nb_setarg_ex(2,List,[Name=Value]) ;
  492           nb_set_pairlist0(Name,T,Value))).
  493
  494
  495%= 	 	 
 nb_set_s2list(?VALUE1, ?VALUE2, ?VALUE3, ?VALUE4) is semidet
Non Backtackable Set S2list.
  501nb_set_s2list(Name,List,Value,NewList):- must(List=[_|_]), must(nb_set_s2list0(Name,List,Value,NewList)).
  502
  503
  504%= 	 	 
 nb_set_s2list0(?VALUE1, ?VALUE2, ?VALUE3, ?VALUE2) is semidet
Non Backtackable Set S2list Primary Helper.
  510nb_set_s2list0(Name,[],Value,[Name,Value]).
  511nb_set_s2list0(Name,LIST,Value,LIST):- append(_,[N|REST],LIST),key_match(Name,N),nb_setarg_ex(1,REST,Value),!.
  512nb_set_s2list0(Name,LIST,Value,LIST):- LIST = [_|A2REST],A2REST=[_|REST],nb_setarg_ex(2,A2REST,[Name,Value|REST]).
  513
  514nb_set_s2list0(Name,LIST,Value,NEWLIST):- 
  515   ((append(_,[N|REST],LIST),key_match(Name,N)) -> (nb_setarg_ex(1,REST,Value),NEWLIST=LIST);
  516   append(LIST,[Name,Value],NEWLIST)).
  517
  518
  519
  520%= 	 	 
 prop_merge(:TermARG1, ?VALUE2, ?VALUE3) is semidet
Prop Merge.
  526prop_merge([Name],Struct,Value):-!, prop_merge(Name,Struct,Value).
  527prop_merge([Name|More],Struct,Value):-!, prop_get(Name,Struct,Ref),prop_merge(More,Ref,Value).
  528prop_merge(Name,Struct,ValueIn):- term_to_ord_term(ValueIn,Value),
  529   (prop_get(Name,Struct,Old) -> merge_values(Old,Value,New) ;  Value=New),
  530   prop_set(Name,Struct,New),!.
  531
  532
  533% term_to_ord_term(+Term, -OrdTerm)
  534%
  535%   Go throught the term and look for sets, return the same term
  536%   with all sets become ordered.
  537%
  538
  539
  540%= 	 	 
 term_to_ord_term(?VALUE1, ?VALUE2) is semidet
Term Converted To Ord Term.
  546term_to_ord_term(Term, OrdTerm):-t2ot(Term, OrdTerm).
  547
  548
  549%= 	 	 
 t2ot(?VALUE1, ?VALUE1) is semidet
T2ot.
  555t2ot(A, A):- \+ compound(A), !.
  556t2ot(vv(T), T):-!.
  557t2ot(T, OTO):-t2ot_0(T, OT),(T==OT->OTO=T;OTO=OT).
  558
  559
  560
  561%= 	 	 
 t2ot_0(?VALUE1, ?VALUE2) is semidet
t2ot Primary Helper.
  567t2ot_0([H|T], R):-
  568    t2ot(H, OH),
  569    t2ot(T, OT),
  570    ord_add_element(OT, OH, R),
  571    !.
  572%    write(OH), write(OT), write('   '), write(R), nl.
  573
  574t2ot_0(T, OT):-
  575    T =.. [F,P],
  576    !,
  577    t2ot(P, OP),
  578    OT =..[F,OP].
  579t2ot_0(T, OT):-
  580    T =.. [F,P|Ps],
  581    NT=.. [F|Ps],
  582    t2ot(P, OP),
  583    t2ot(NT, ONT),
  584    ONT =.. [_|OPs],
  585    OT =.. [F,OP|OPs],
  586    !. 
  587
  588
  589
  590%= 	 	 
 merge_values(?VALUE1, ?VALUE3, ?VALUE3) is semidet
Merge Values.
  596merge_values(Var,Value,Value):-var(Var),!.
  597merge_values([], Value,Value).
  598merge_values(Old,Value,Value):-Old==Value,!.
  599merge_values(Old,Value,New):-is_list(Old),!,(is_list(Value)->ord_union(Old,Value,New);ord_add_element(Old,Value,New)).
  600merge_values(Old,Value,[Value,Old]).
  601
  602
  603%= 	 	 
 nb_setarg_ex(?VALUE1, ?VALUE2, ?VALUE3) is semidet
Non Backtackable Setarg Ex.
  609nb_setarg_ex(Name,Struct,New):-(var(Name);var(Struct);var(New)),!,trace_or_throw(var_prop_set_map(Name,Struct,New)).
  610nb_setarg_ex(Name,Struct,New):-arg(Name,Struct,Old),nb_setarg(Name,Struct,New),ignore(Old=New).
  611
  612
  613%= 	 	 
 us:member_datatype(?VALUE1, ?VALUE2) is semidet
Member Datatype.
  619us:member_datatype(prototype,compound).
  620
  621
  622%= 	 	 
 by_name_datatype(?VALUE1, ?VALUE2) is semidet
By Name Datatype.
  628by_name_datatype(init, sorted).
  629by_name_datatype(goal, sorted).
  630by_name_datatype(assign_effect, sorted).
  631by_name_datatype(effects, sorted).
  632by_name_datatype(negativ_effect, sorted).
  633by_name_datatype(positiv_effect, sorted).
  634by_name_datatype(preconditions, sorted).
  635
  636
  637:- functor(t{a:t},A,_),asserta(dict_functor(A)).  638
  639
  640% member_arg_convert(+StructName,+Name,?N,+Value,-NewValue).
  641
  642
  643%= 	 	 
 struct_sclass(?VALUE1, ?VALUE2) is semidet
Struct Sclass.
  649struct_sclass(sterm(SC,_),SC).
  650struct_sclass(mutable(Struct),SC):-!,struct_sclass(Struct,SC).
  651struct_sclass([sclass=SC|_],SC).
  652struct_sclass([],any).
  653struct_sclass(Struct,SC):-prop_get(sclass,Struct,SC).
  654struct_sclass(Struct,SC):-functor(Struct,F,_),(dict_functor(F)->prop_get(sclass,Struct,SC);SC=F).
  655
  656
  657%= 	 	 
 member_arg_convert(?VALUE1, ?VALUE2, ?VALUE3, ?VALUE4, ?VALUE4) is semidet
Member Argument Convert.
  663member_arg_convert( _,Name,_,Value,Value):-var(Name),!.
  664member_arg_convert(_,Name,_N,Value,NewValue):-by_name_datatype(Name,Type),!,to_datatype(Type,Value,NewValue).
  665member_arg_convert(_,varnames,_N,Value,Value):-!.
  666member_arg_convert(Struct,Name,N,Value,NewValue):- \+ \+ (Struct=[] ),!,member_arg_convert(any,Name,N,Value,NewValue).
  667member_arg_convert(Struct,Name,N,Value,NewValue):- \+atom(Struct),!, struct_sclass(Struct,SC),!,member_arg_convert(SC,Name,N,Value,NewValue).
  668member_arg_convert(uppercase_string,charAt(_),_,Char,Converted):-to_upper(Char,Converted).
  669member_arg_convert(StructName,Name,_N,Value,NewValue):-us:member_datatype(StructName,Name,Type),to_datatype(Type,Value,NewValue).
  670member_arg_convert(StructName,_Name,N,Value,NewValue):-us:struct_datatype(StructName,ArgTypes),arg(N,ArgTypes,Datatype),to_datatype(Datatype,Value,NewValue).
  671member_arg_convert(_Type,Datatype,_,Value,NewValue):-to_datatype(Datatype,Value,NewValue).
  672member_arg_convert(_Type,_Named,_,UnConverted,UnConverted).
  673
  674
  675
  676%= 	 	 
 if_changed_struct(?VALUE1, ?VALUE2, ?VALUE3) is semidet
If Changed.
  682if_changed_struct(Value,NewValue,NewValueO):- must((NewValue=@=Value -> NewValueO=Value ; NewValueO=NewValue)).
  683%if_changed_struct(Ex,I,O):- call(Ex,I,O)-> I\==O.
  684
  685
  686%= 	 	 
 to_datatype(?Type, ?Value, ?Value) is semidet
Converted To Datatype.
  692to_datatype(=,Value,Value).
  693to_datatype(sorted,Value,NewValueO):-term_to_ord_term(Value,NewValue),!,if_changed_struct(Value,NewValue,NewValueO).
  694to_datatype(_Type,Value,Value).
  695
  696
  697
  698%= 	 	 
 decl_struct(?VALUE1) is semidet
Declare Struct.
  704decl_struct(StructDecl):- 
  705  must_det_l((
  706    compile_argtypes(StructDecl,1,StructPrototype),    
  707    functor(StructPrototype,StructName,_),
  708    show_call(ain(us:struct_prototype(StructName,StructPrototype))))),!.
  709
  710
  711%= 	 	 
 decl_argtypes(?VALUE1) is semidet
Declare Argument Types.
  717decl_argtypes(StructDecl):- 
  718  compile_argtypes(StructDecl,"NotSlotted",_),!.
  719
  720
  721%= 	 	 
 compile_argtypes(?VALUE1, ?VALUE2, ?VALUE3) is semidet
Compile Argument Types.
  727compile_argtypes(StructDecl,Loc,StructPrototype):- 
  728 must_det_l((
  729    functor(StructDecl,StructName,_),
  730    StructDecl=..[StructName|PARGS],
  731    compile_struct_slots(StructName,Loc,PARGS,PArgNames,PArgTypes,InitArgs),
  732    StructPrototype=..[StructName|InitArgs],
  733  (number(Loc) -> 
  734    ((
  735      ArgNames=..[StructName|PArgNames],ain(us:struct_names(StructName,ArgNames)),
  736      Datatypes=..[StructName|PArgTypes],ain(us:struct_datatypes(StructName,Datatypes))));
  737    true))).
  738    
  739
  740
  741
  742%= 	 	 
 compile_struct_slots(?VALUE1, ?VALUE2, :TermARG3, :TermARG4, :TermARG5, :TermARG6) is semidet
Compile Struct Slots.
  748compile_struct_slots(_,_,[],[],[],[]).
  749compile_struct_slots(StructType,Loc,[Param|ARGS],[Name|ArgNames],[Datatype|Datatypes],[Init|InitTypes]):-
  750   extract_struct_parameter(=,Param,Name,Datatype,Init),
  751   (number(Loc)->(ain(us:member_loc(StructType,Name,Loc)), Loc2 is Loc + 1);Loc2=Loc),
  752   ain(us:member_datatype(StructType,Name,Datatype)),
  753   (nonvar(Init)-> ain(us:member_init(StructType,Name,Datatype));true),   
  754   compile_struct_slots(StructType,Loc2,ARGS,ArgNames,Datatypes,InitTypes).
  755
  756
  757
  758%= 	 	 
 extract_struct_parameter(?VALUE1, ?VALUE2, ?VALUE3, ?VALUE4, ?VALUE5) is semidet
Extract Struct Parameter.
  764extract_struct_parameter(_Def,Name:Datatype,Name,Datatype,Init):-!,
  765  datatype_to_init(Datatype,Init).
  766
  767extract_struct_parameter(Def,Decl=Init,Name,Datatype,Init):-!,
  768  extract_struct_parameter(Def,Decl,Name,Datatype).
  769
  770extract_struct_parameter(Def,Decl,Name,Datatype,Init):-
  771   extract_struct_parameter(Def,Decl,Name,Datatype),!,
  772   datatype_to_init(Datatype,Init).
  773
  774
  775%= 	 	 
 extract_struct_parameter(?VALUE1, ?VALUE2, ?VALUE2, ?VALUE1) is semidet
Extract Struct Parameter.
  781extract_struct_parameter(_Def,Decl,Name,Type):-Decl=..[K1,K2,Name],!,Type=..[K1,K2].
  782extract_struct_parameter(_Def,Decl,Name,Type):-Decl=..[Type,Name],!.
  783extract_struct_parameter(Def,Name,Name,Def).
  784   
  785
  786%= 	 	 
  787
  788% module_local_init(_UserModule,SystemModule) is semidet.
  789%
  790% Hook To [module_local_init/2] For Module Logicmoo_util_structs.
  791% Module Local Init.
  792%
  793% @TODO module_local_init(_UserModule,SystemModule):- ain(SystemModule:'==>'(us:struct_decl(StructDecl),decl_struct(StructDecl))).
  794
  795
  796
  797%= 	 	 
 ensure_instance(?VALUE1, ?VALUE2) is semidet
Ensure Instance.
  803ensure_instance(Type,Struct):-ensure_struct(Type,Struct).
  804
  805%= 	 	 
 ensure_instance(?VALUE1, ?VALUE2, ?VALUE3) is semidet
Ensure Instance.
  811ensure_instance(Type,List,Struct):-ensure_struct(Type,List,Struct).
  812
  813
  814%= 	 	 
 ensure_struct(?VALUE1, ?VALUE2) is semidet
Ensure Struct.
  820ensure_struct(Type,Struct):- nonvar(Struct)->prop_set(sclass,Struct,Type);new_struct(Type,Struct).
  821
  822%= 	 	 
 ensure_struct(?VALUE1, ?VALUE2, ?VALUE3) is semidet
Ensure Struct.
  828ensure_struct(Type,List,Struct):- must_det_l((ensure_instance(Type,Struct),prop_set_nvlist(Struct,List))).
  829
  830
  831%= 	 	 
 prop_set_nvlist(?VALUE1, :TermARG2) is semidet
Prop Set Nvlist.
  837prop_set_nvlist(Struct,[N=V|More]):-must_det_l((prop_set(N,Struct,V),( More==[]->true;prop_set_nvlist(Struct,More)))).
  838
  839%= 	 	 
 prop_get_nvlist(?VALUE1, :TermARG2) is semidet
Prop Get Nvlist.
  845prop_get_nvlist(Struct,[N=V|More]):-must_det_l((ignore(show_failure(why,prop_get(N,Struct,V))),( More==[]->true;prop_get_nvlist(Struct,More)))).
  846
  847
  848%= 	 	 
 new_struct(?VALUE1, ?VALUE2) is semidet
New Struct.
  854new_struct(Type,Struct):- var(Type),!,trace_or_throw(var_new_struct(Type,Struct)).
  855new_struct(Type,Struct):- us:struct_prototype(Type,Struct),!,us:struct_prototype(Type,Struct).
  856new_struct(Type,Struct):- us:struct_datatype(Type,DType),!,new_struct(DType,Struct).
  857new_struct(Type,mutable([sclass=Type])):-!.
  858new_struct(Type,[sclass=Type]):-!.
  859
  860
  861
  862
  863%= 	 	 
 datatype_to_init(?VALUE1, ?VALUE2) is semidet
Datatype Converted To Init.
  869datatype_to_init(dict, Dict):- Dict = mutable([]). % sclass=dict
  870datatype_to_init(rb,   NewArg):-rb_new(NewArg),!.
  871datatype_to_init(assoc,NewArg):-empty_assoc(NewArg),!.
  872datatype_to_init(actions,[]).
  873datatype_to_init(sorted,[]).
  874datatype_to_init(_,_).
  875
  876/*
  877new_struct(map, mutable(O)):- dict_create(O,Name,[]),!.
  878%new_struct(Type,Struct):- rb_new(O),rb_insert_new(O,sclass,Type,Struct),!.
  879%new_struct(Type,Struct):- rb_insert_new(_O,sclass,Type,Struct),!.
  880new_struct(Name,mutable(O)):- dict_create(O,Name,[]),!.
  881*/
  882:- fixup_exports.