1:- set_module(class(development)).    2:- '$set_source_module'(baseKB).    3:- use_module(library(pfc_lib)).    4% :- mpred_unload_file.
    5:- ensure_abox(baseKB).    6:- set_fileAssertMt(baseKB).    7% ensure this file does not get unloaded with mpred_reset
    8:- prolog_load_context(file,F), ain(mpred_unload_option(F,never)).    9
   10
   11:- sanity(ttRelationType(prologMultiValued)).   12
   13:- kb_shared(argsIsa/2).   14
   15feature_setting(N,V)/(feature_setting(N,Other),Other\==V)==> \+ feature_setting(N,Other). 
   16
   17feature_setting(assume_wff, true).
   18
   19% set false so make_wff/1 will be noticed (default is true)
   20feature_setting(make_wff,true)==> (feature_setting(add_admitted_arguments,true), feature_setting(assume_wff, false)).
   21feature_setting(add_admitted_arguments,true) ==> 
   22 ( (P/(compound(P),\+is_ftVar(P)) ==> 
   23  {with_current_why(P,ignore(\+ addAdmittedArguments(P)))})).
   24
   25feature_setting(make_wff,true)==> 
   26 ((argIsa(P, N, T)/(nonvar(T),nonvar(P),integer(N)))==>
   27          (tCol(T),
   28          (admittedArgument(P, N, E)/nonvar(E)==> isa(E,T)),
   29          (poss(admittedArgument(P, N, E))/nonvar(E)==> (isa(E,T))))).
   30
   31make_wff(true)==> (P/(compound(P),\+is_ftVar(P)) ==> {with_current_why(P,ignore(\+ deduceEachArgType(P)))}).
   32
   33% default is false
   34% ==> feature_setting(add_admitted_arguments,true).
   35
   36% default is false
   37==> feature_setting(admitted_arguments_modal,false).
   38
   39prologHybrid(argIsa/3).
   40
   41:- asserta(t_l:pfcExpansion).
 argIsa(?F, ?N, ?Type) is semidet
asserted Argument (isa/2) known.
   51% WEIRD .. is needed? argIsa(F/_,N,Type):- nonvar(F),!,argIsa(F,N,Type).
   52argIsa(F,N,Type):- var(F),!,tRelation(F),argIsa(F,N,Type).
   53argIsa(F,N,Type):- var(N),arity_no_bc(F,A),!,system_between(1,A,N),argIsa(F,N,Type).
   54%argIsa(F,1,F):- tCol(F), arity_no_bc(F,1),!.
   55% Managed Arity Predicates.
   56% argIsa(Pred,N,ftVoprop) :- number(N),arity_no_bc(Pred,A),N>A,!.
   57
   58==>argIsa(isEach(arity,arityMax,arityMin),2,ftInt).
   59
   60/*
   61argIsa(F,_,ftTerm):-member(F/_, [argIsa/3,predProxyAssert/2,negate_wrapper0/2,mudFacing/_,registered_module_type/2,       
   62                                ruleBackward/2,formatted_resultIsa/2, pt/_,rhs/_,nt/_,bt/_,bracket/3]),!.
   63argIsa(Prop,N1,Type):- is_2nd_order_holds(Prop),dmsg(todo(define(argIsa(Prop,N1,'Second_Order_TYPE')))),dumpST,dtrace,Type=argIsaFn(Prop,N1),!.
   64*/
   65/*
   66$mycont.set({V1=$a.value,V2=$b.value}/(VarIn)>>writeln(my_cont(V1,V2,VarIn))).
   67writeln($mycont).
   68*/
   69
   70:- kb_shared(mpred_f/5).   71:- kb_shared(mpred_f/6).   72:- kb_shared(mpred_f/4).   73:- kb_shared(mpred_f/7).   74
   75% :- rtrace.
   76%% argQuotedIsa( ?F, ?N, ?FTO) is semidet.
   77%
   78% Argument  (isa/2) Format Type.
   79%
   80:- kb_shared(argQuotedIsa/3).   81prologHybrid(argQuotedIsa(tRelation,ftInt,ttExpressionType)).
   82
   83% :- listing(argQuotedIsa/3).
   84% :- break.
   85% argQuotedIsa(F/_,N,Type):-nonvar(F),!,argQuotedIsa(F,N,Type).
   86argQuotedIsa(F,N,FTO):- argIsa(F,N,FT), must(to_format_type(FT,FTO)),!.
   87:- nortrace.   88
   89:- was_export(argIsa/3).   90
   91%= 	 	 
 argIsa(?F, ?N, ?Type) is semidet
Argument (isa/2) call Primary Helper.
   97argIsa(argIsa,1,tRelation).
   98argQuotedIsa(argIsa,2,ftInt).
   99argIsa(argIsa,3,tCol).  
  100argQuotedIsa(comment,2,ftString).
  101argQuotedIsa(isKappaFn,1,ftVar).
  102argQuotedIsa(isKappaFn,2,ftAskable).
  103%argIsa(isInstFn,1,tCol).
  104
  105
  106argQuotedIsa(quotedDefnIff,1,ftSpec).
  107argQuotedIsa(quotedDefnIff,2,ftCallable).
  108argQuotedIsa(meta_argtypes,1,ftSpec).
  109
  110
  111argIsa(isa,2,tCol).
  112%argIsa(mpred_isa,1,tPred).
  113%argIsa(mpred_isa,2,ftVoprop).
  114% argIsa(mpred_isa,3,ftVoprop).
  115
  116argIsa(formatted_resultIsa,1,ttExpressionType).
  117argIsa(formatted_resultIsa,2,tCol).
  118
  119argIsa(predicates,1,ftListFn(ftTerm)).
  120argIsa(resultIsa,2,tCol).
  121
  122argIsa(predTypeMax,1,tPred).
  123argIsa(predTypeMax,2,tCol).
  124argIsa(predTypeMax,3,ftInt).
  125
  126argIsa(predInstMax,1,tObj).
  127argIsa(predInstMax,2,tPred).
  128argQuotedIsa(predInstMax,3,ftInt).
  129
  130argQuotedIsa(props,1,ftID).
  131argQuotedIsa(props,N,ftVoprop):- integer(N), system_between(2,31,N).
  132
  133argIsa(apathFn,1,tRegion).
  134argIsa(apathFn,2,vtDirection).
  135argIsa(localityOfObject,1,tObj).
  136argIsa(localityOfObject,2,tSpatialThing).
  137
  138argIsa(typeProps,1,tCol).
  139argIsa(typeProps,N,ftVoprop):-system_between(2,31,N).
  140
  141argQuotedIsa(instTypeProps,1,ftProlog).
  142argIsa(instTypeProps,2,tCol).
  143argQuotedIsa(instTypeProps,N,ftVoprop):-system_between(3,31,N).
  144
  145
  146argIsa(must,1,ftCallable).
  147
  148%:- break.
  149(argsIsa(F,Type),arity(F,A),{system_between(1,A,N)})==>argIsa(F,N,Type).
  150
  151
  152
  153% argIsa(baseKB:agent_text_command,_,ftTerm).
  154
  155
  156argIsa('<=>',_,ftTerm).
  157argIsa(class_template,N,Type):- (N=1 -> Type=tCol;Type=ftVoprop).
  158==>argIsa(isEach(descriptionHere,mudDescription,nameString,mudKeyword),2,ftString).
  159
  160% argQuotedIsa(F,N,Type)==>argIsa(F,N,Type).
  161
  162% argQuotedIsa(F,N,Type):- functorDeclares(F),(N=1 -> Type=F ; Type=ftVoprop).
  163%argIsa(F,N,Type):- t(tCol,F),!,(N=1 -> Type=F ; Type=ftVoprop).
  164% :- sanity(listing(argQuotedIsa/3)).
  165
  166/*
  167{source_file(M:P,_),functor(P,F,A),
  168  \+ predicate_property(M:P,imported_from(_))} 
  169   ==> functor_module(M,F,A).
  170:- show_count(functor_module/3).
  171*/
  172
  173:- dynamic(functor_module/3).  174rtArgsVerbatum(functor_module).
  175
  176
  177:- if((current_prolog_flag(runtime_debug,D),D>1)).  178:- show_count(arity/2).  179:- endif.  180
  181
  182%= 	 	 
  183
  184%% argsIsa( ?WP, ?VALUE2) is semidet.
  185%
  186% Argument  (isa/2) call Helper number 3..
  187%
  188==>argsIsa(isEach(predProxyRetract,predProxyAssert,predProxyQuery,genlInverse),tPred).
  189argsIsa(disjointWith,tCol).
  190argQuotedIsa(ftFormFn,ftTerm).
  191argQuotedIsa(mudTermAnglify,ftTerm).
  192argsIsa(genls,tCol).
  193argsIsa(subFormat,ttExpressionType)