1% ===================================================================
    2% File 'logicmoo_module_aiml_loader.pl'
    3% Purpose: An Implementation in SWI-Prolog of AIML
    4% Maintainer: Douglas Miles
    5% Contact: $Author: dmiles $@users.sourceforge.net ;
    6% Version: 'logicmoo_module_aiml.pl' 1.0.0
    7% Revision:  $Revision: 1.7 $
    8% Revised At:   $Date: 2002/07/11 21:57:28 $
    9% ===================================================================
   10
   11ppfs:-ppfs('../aiml/chomskyAIML/chomsky04*.aiml').
   12
   13% ppfs('../aiml/chomskyAIML/*.aiml').
   14
   15ppfs:-ppfs('../aiml/chomskyAIML/chomsky001.aiml').
   16ppfs(FN):-expand_file_name(FN,Exp),member(F,Exp),ppfs1(F),fail.
   17ppfs(_).
   18
   19ppfs1(File):-
   20    fileToLineInfoElements(_Ctx,File,Z),
   21    atom_concat(File,'.term',Elis),
   22    (file_newer(Elis,File) 
   23      -> 
   24       ('format'('%% skipping: ~q ~n',[Elis]),flush_output(user_output))
   25        ; 
   26         prolog_mustEach(('format'('%% writing: ~q ~n',[Elis]),flush_output(user_output),setup_call_cleanup(open(Elis,write,Str),writeEachTo(Str,Z),close(Str))))).
   27
   28writeEachTo(_Str,[]):-!.
   29writeEachTo(Str,Atom):-atom(Atom),'format'(Str,'atom_load(~q).~n',[Atom]),'format'('atom_load(~q).~n',[Atom]),!.
   30writeEachTo(Str,[H|T]):- !, maplist_safe(writeEachTo(Str),[H|T]).
   31writeEachTo(Str,element(aiml,[],STUFF)):- !,writeEachTo(Str,STUFF).
   32writeEachTo(Str,element(Foo,S,STUFF)):- member(Foo,[category,topic]),!,'format'(Str,'~q.~n',[element(Foo,S,STUFF)]),!.
   33writeEachTo(Str,S):-'format'(Str,'~q.~n',[S]), 'format'('%% UNK ~q.~n',[S]).
   34
   35
   36file_newer(File1,File2):-
   37   time_file_safe(File1,Time1), % fails on non-existent
   38   time_file_safe(File2,Time2),Time1>Time2.
   39
   40
   41
   42%:-module()
   43%:-include('logicmoo_utils_header.pl'). %<?
   44%:- style_check(-singleton).
   45%%:- style_check(-discontiguous).
   46/*
   47:- if((current_prolog_flag(version,MMmmPP),MMmmPP<70000)).
   48:- style_check(-atom).
   49:- style_check(-string).
   50:- endif.
   51*/

   52
   53
   54translate_single_aiml_file(Ctx,F0):-global_pathname(F0,File),F0\==File,!,translate_single_aiml_file(Ctx,File).
   55translate_single_aiml_file(Ctx,F0):-
   56  prolog_mustEach((
   57   global_pathname(F0,File),!,
   58   cateForFile(Ctx,File,FileMatch),!,
   59   atom_concat_safe(File,'.tmp.pl',PLNAME),
   60   translate_single_aiml_file(Ctx,File,PLNAME,FileMatch))),!.
   61
   62translate_aiml_structure(Ctx,Structure):- string(Structure),!,
   63   debugFmt(translate_aiml_structure_string(Ctx,Structure)),
   64   string_to_structure(Ctx,Structure,XMLStructures),
   65   load_aiml_structure(Ctx,XMLStructures),!.
   66
   67translate_aiml_structure(Ctx,Structure):-not(atom(Structure)),!, trace,
   68   debugFmt(translate_aiml_structure_no_atom(Ctx,Structure)),!.
   69
   70translate_aiml_structure(Ctx,Structure):- trace,
   71   debugFmt(translate_aiml_structure_atom(Ctx,Structure)),!,
   72   string_to_structure(Ctx,Structure,XMLStructures),
   73   load_aiml_structure(Ctx,XMLStructures),!.
   74
   75
   76cateForFile(_Ctx,SRCFILE,aimlCate(_GRAPH,_PRECALL,_TOPIC,_THAT,_INPUT,_PATTERN,_FLAGS,_CALL,_GUARD,_USERDICT,_TEMPLATE,_LINENO,SRCFILE:_-_,_RULESYM)):-useCateID,!.
   77cateForFile(_Ctx,SRCFILE,aimlCate(_GRAPH,_PRECALL,_TOPIC,_THAT,_INPUT,_PATTERN,_FLAGS,_CALL,_GUARD,_USERDICT,_TEMPLATE,_LINENO,SRCFILE:_-_)):-!.
   78cateForFile(Ctx,File,FileMatch):- atrace,withNamedValue(Ctx,[anonvarsFroCate=true], makeAimlCate(Ctx,[srcfile=File:_-_],FileMatch)),!.
   79
   80withNamedValue(Ctx,[N=V],Call):-withAttributes(Ctx,[N=V],Call),!.
   81
   82% =================================================================================
   83% AIML -> Prolog pretransating
   84% =================================================================================
   85
   86:-dynamic(creating_aiml_file/2).
   87:-dynamic(loaded_aiml_file/3).
   88:-dynamic(pending_aiml_file/2).
   89
   90do_pending_loads:-withCurrentContext(do_pending_loads).
   91do_pending_loads(Ctx):-forall(retract(pending_aiml_file(File,PLNAME)),load_pending_aiml_file(Ctx,File,PLNAME)).
   92
   93load_pending_aiml_file(Ctx,File,PLNAME):- debugFmt(load_pending_aiml_file(Ctx,File,PLNAME)),
   94  error_catch(prolog_must(dynamic_load(File,PLNAME)),E,(debugFmt(E),assert(pending_aiml_file(File,PLNAME)))),!.
   95
   96translate_single_aiml_file(_Ctx,File,PLNAME,FileMatch):- creating_aiml_file(File,PLNAME),!,
   97  throw_safe(already(creating_aiml_file(File,PLNAME),FileMatch)),!.
   98
   99translate_single_aiml_file(_Ctx,File,PLNAME,_FileMatch):-
  100   file_newer(PLNAME,File), % fails on non-existent
  101   %not(aimlOption(rebuild_Aiml_Files,true)),
  102   debugFmt(up_to_date(create_aiml_file(File,PLNAME))),!,
  103   retractall(creating_aiml_file(File,PLNAME)),!
  103.
  104
  105%%translate_single_aiml_file(_Ctx,File,PLNAME,FileMatch):- loaded_aiml_file(File,PLNAME,Time),!, throw_safe(already(loaded_aiml_file(File,PLNAME,Time),FileMatch)).
  106translate_single_aiml_file(Ctx,File,PLNAME,FileMatch):- loaded_aiml_file(File,PLNAME,Time),!,
  107   debugFmt(translate_single_aiml_file(loaded_aiml_file(File,PLNAME,Time),FileMatch)),
  108   prolog_must(retract(loaded_aiml_file(File,PLNAME,Time))),
  109   retractall(pending_aiml_file(File,PLNAME)),
  110   assertz(pending_aiml_file(File,PLNAME)),!,
  111   translate_single_aiml_file(Ctx,File,PLNAME,FileMatch).
  112
  113translate_single_aiml_file(Ctx,File,PLNAME,FileMatch):-
  114  call_cleanup(
  115     translate_single_aiml_file0(Ctx,File,PLNAME,FileMatch),
  116     translate_single_aiml_file1(File,PLNAME,FileMatch)).
  117
  118translate_single_aiml_file0(Ctx,File,PLNAME,FileMatch):-
  119 prolog_mustEach((
  120        asserta(creating_aiml_file(File,PLNAME)),
  121        debugFmt(doing(create_aiml_file(File,PLNAME))),
  122        aimlCateSig(CateSig),!,
  123   (format('%-----------------------------------------~n')),
  124        printPredCount('Cleaning',FileMatch,_CP),
  125   (format('%-----------------------------------------~n')),
  126        unify_listing(FileMatch),
  127        retractall(FileMatch),
  128   (format('%-----------------------------------------~n')),
  129        flag(cateSigCount,PREV_cateSigCount,0),
  130   (format('%-----------------------------------------~n')),
  131      withAttributes(Ctx,[withCategory=[translate_cate]], 
  132               ( fileToLineInfoElements(Ctx,File,AILSTRUCTURES),
  133                 tell(PLNAME),
  134                  load_aiml_structure(Ctx,AILSTRUCTURES))),
  135
  136   (format('%-----------------------------------------~n')),
  137         unify_listing_header(FileMatch),
  138         %printAll(FileMatch),
  139   (format('%-----------------------------------------~n')),
  140        listing(xmlns),
  141   (format('%-----------------------------------------~n')),
  142        told,
  143        flag(cateSigCount,NEW_cateSigCount,PREV_cateSigCount),
  144        printPredCount('Errant Lines',lineInfoElement(File,_,_,_),_EL),
  145        printPredCount('Total Categories',CateSig,_TC),!,
  146        debugFmt('NEW_cateSigCount=~q~n',[NEW_cateSigCount]),!,
  147        statistics(global,Mem),MU is (Mem / 1024 / 1024),
  148        debugFmt(statistics(global,MU)),!,
  149        printPredCount('Loaded',FileMatch, _FM),
  150        retractall(creating_aiml_file(File,PLNAME)))
  150)
  150,!
  150.
  151
  152stream_file(user,PLNAME):-!,atrace,stream_property(user,file_name(Name)),prolog_must(PLNAME=Name).
  153stream_file(PLNAMET,PLNAME):-atrace,is_stream(PLNAMET),stream_property(PLNAMET,file_name(Name)),prolog_must(PLNAME=Name).
  154stream_file(PLNAMET,PLNAME):-exists_file(PLNAMET),!,prolog_must(PLNAME=PLNAMET).
  155
  156
  157translate_single_aiml_file1(File,PLNAME,FileMatch):-
  158    catch((ignore((telling(PLNAMET),PLNAMET\==user,stream_file(PLNAMET,PLNAME),told))),_,true),
  159    catch((ignore((creating_aiml_file(File,PLNAME),retractall(creating_aiml_file(File,PLNAME)),delete_file(PLNAME)))),_,true),
  160    retractall(lineInfoElement(File,_,_,_)),
  161    retractall(FileMatch),
  162    retractall(xmlns(_,_,_)),   
  163    retractall(loaded_aiml_file(File,PLNAME,_Time)).
  164
  165/*
  166translate_single_aiml_filexxx(Ctx,File,PLNAME):-
  167  prolog_must((
  168     Dofile = true,
  169     aimlCateSig(CateSig),
  170   ifThen(Dofile,tell(PLNAME)),
  171   (format(user_error,'%~w~n',[File])),
  172   load_structure(File,X,[dialect(xml),space(remove)]),!,
  173   ATTRIBS = [srcfile=File],!,
  174   pushAttributes(Ctx,filelevel,ATTRIBS),
  175   load_aiml_structure_list(Ctx,X),!,
  176   popAttributes(Ctx,filelevel,ATTRIBS),!,
  177   ifThen(Dofile,((listing(CateSig),retractall(CateSig)))),
  178   ifThen(Dofile,(told /*,[PLNAME]*/ )))),!.
  179*/

  180
  181% ===================================================================
  182% ===================================================================
  183
  184convert_text('',[]):-!.
  185convert_text([],[]):-!.
  186convert_text(C,D):-is_list(C),!,convert_text_list(C,D),!.
  187convert_text(A,L):-atom(A),!,convert_atom(A,O),convert_text_list(O,L).
  188convert_text(A,[]):-ignore_aiml(A),!.
  189convert_text(E,File):-aiml_error(convert_text(E,File)),!,E=File.
  190
  191
  192convert_text_list([],[]):-!.
  193convert_text_list([A],B):-!,convert_text_list(A,B).
  194convert_text_list(M,C):-delete(M,'',B), (M == B -> C=B ; convert_text_list(B,C)).
  195convert_text_list([A|AA],BBB):-convert_text(A,B),convert_text_list(AA,BB),!,flattem_append(B,BB,BBB0),!,BBB=BBB0.
  196convert_text_list(A,C):-atom(A),atomWSplit(A,M),([A]==M->C=M;convert_text(M,C)),!.
  197convert_text_list(A,AA):-listify(A,AA).
  198
  199convert_atom(A,Z):-convert_atom0(A,Y),!,Y=Z.
  200convert_atom(E,File):-aiml_error(convert_atom(E,File)),!,E=File.
  201%convert_atom(A,C):-atom_number(A,C),!.
  202convert_atom0(A,C):-atomWSplit(A,M),!,convert_text(M,C),!.
  203convert_atom0(A,D):-literal_atom_safe(A,D),!.
  204convert_atom0(A,A):-concat_atom_safe([A],' ',A).
  205convert_atom0(A,A). %%:-!listify(A,AA).
  206
  207flattem_append(A,B,BBB):-flatten([A],AA),!,flatten([B],BB),!,append(AA,BB,BBB),!.
  208
  209
  210
  211% ===============================================================================================
  212%  PATTERN/TEMPLATE normalization
  213% ===============================================================================================
  214convert_template(_Ctx,X,_Y):-var(X),throw_safe(var(X)).
  215convert_template(_Ctx,_X,Y):-nonvar(Y),throw_safe(nonvar(Y)).
  216convert_template(_Ctx,[],[]):-!.
  217%%HIDE convert_template(Ctx,[I|P],L):-!,convert_template(I,IO),!,convert_template(Ctx,P,PO),append(IO,PO,L),!.
  218convert_template(_Ctx,I,[]):- notrace(ignore_aiml(I)),!.
  219
  220%%%HIDE            %%convert_template(_Ctx,[ATOM],O):-atom(ATOM),!,atomWSplit(ATOM,LIST),!,toAtomList(LIST,O),!.
  221convert_template(Ctx,I,GOOD):- atom(I),atomWSplit(I,LIST),toAtomList(LIST,O),[I] \== O,!, convert_template(Ctx,O,GOOD),!.
  222%%%HIDE            %%convert_template(Ctx,[I|P],GOOD):- is_list(I),!,append(I,P,IP),!,convert_template(Ctx,IP,GOOD),!.
  223%%%HIDE            %%convert_template(Ctx,[I|P],GOOD):- convert_template(Ctx,I,O), I \== O,!, convert_template(Ctx,[O|P],GOOD),!.
  224convert_template(Ctx,[I|P],GOOD):- convert_template(Ctx,I,O),!,convert_template(Ctx,P,L),!,append(O,L,GOOD),!.
  225%%%HIDE            %%convert_template(Ctx,[P],POL):-!,convert_template(Ctx,P,POL).
  226convert_template(Ctx,element(TAG,ATTRIBS,P),POL):-!, convert_element(Ctx,element(TAG,ATTRIBS,P),OUT),!,listify(OUT,POL).
  227convert_template(Ctx,P,POL):-convert_element(Ctx,P,PO),!,listify(PO,POL).
  228
  229toAtomList(A,O):-delete(A,'',O),!.
  230
  231convert_element(Ctx,Input,Out):- convert_element0(Ctx,Input,Out),!. % ,wdmsg(convert_element_in(Ctx,Input)),wdmsg(convert_element_out(Out)),!.
  232
  233convert_element0(Ctx,element(Tag, A, B),Out):-!,convert_ele(Ctx,element(Tag, A, B),M),!,M=Out,!.
  234convert_element0(_Ctx,Input,Out):-atomic(Input),convert_text_list(Input,Out),!.
  235convert_element0(Ctx,Input,Out):-convert_ele(Ctx,Input,M),!,prolog_must(M=Out).
  236
  237      
  238nameOrValue(ALIST, _VALUE, NORV, 0):-lastMember(name=NORV,ALIST),!.
  239nameOrValue(ALIST, _VALUE, NORV, 0):-lastMember(var=NORV,ALIST),!.
  240nameOrValue(_XATS, VALUE, NORV, 1):- NORV = VALUE.
  241
  242:-discontiguous(convert_ele/3).
  243
  244convert_ele(_Ctx,_X,Y):-nonvar(Y),throw_safe(nonvar(Y)).
  245convert_ele(_Ctx,In,_In):-not(ground(In)),aiml_error(not(ground(In))),!,fail.
  246
  247convert_ele(Ctx,li(A),li(AA)):-convert_template(Ctx,A,AA).
  248convert_ele(_Ctx,element(NSLocal,_A,_B),_Out):- var(NSLocal),!,throw_safe(not(atom(NSLocal))),!.
  249convert_ele(Ctx,element(_NS:Local,A,B),Out):- !,convert_ele(Ctx,element(Local,A,B),Out),!.
  250convert_ele(_Ctx,element(NSLocal,_A,_B),_Out):-not(atom(NSLocal)),!,throw_safe(not(atom(NSLocal))),!.
  251convert_ele(Ctx,element(NSLocal,A,B),Out):- concat_atom_safe([_NS,Local],':',NSLocal),!,convert_ele(Ctx,element(Local,A,B),Out),!.
  252convert_ele(Ctx,element(html:TAG,A,B),Out):-!,convert_ele(Ctx,element(TAG,A,B),Out),!.
  253convert_ele(_Ctx,element(br,[],[]),'\n').
  254convert_ele(_Ctx,element(p,[],[]),'\r\n').
  255convert_ele(Ctx,element(pre,[],B),BB):-!,convert_template(Ctx,B,BB).
  256
  257convert_ele(Ctx,element(catagory, A, B),Out):-convert_ele(Ctx,element(category, A, B),Out).
  258%%convert_ele(Ctx,element(Tag, A, B),BB):- member(Tag,[category,srai]), convert_template(Ctx,element(Tag, A, B),BB).
  259
  260
  261botGetSet(bot,bot,_NAME,_NUM).
  262botGetSet(get,user,_NAME,_NUM).
  263botGetSet(set,user,_NAME,0).
  264
  265% bot/get/set
  266convert_ele(Ctx,element(TAG, ALIST, VALUE),element(TAG,NEWLIST,VALUEO)):-
  267            botGetSet(TAG,TYPE,NAME,NUM),not(member(var=_,ALIST)),         
  268            append(ALIST,[type=TYPE,var=NAME],NEWLIST),
  269            nameOrValue(ALIST,VALUE,NORV,NUM), 
  270            convert_template(Ctx,NORV,NAME), 
  271            convert_template(Ctx,VALUE,VALUEO).
  272
  273% get_xxx/set_xxx
  274convert_ele(Ctx,element(VAR_ATOM, ALIST, V),element(get,[name=N|ALIST],VV)):-atom_concat_safe('get_',N,VAR_ATOM),convert_template(Ctx,V,VV).
  275convert_ele(Ctx,element(VAR_ATOM, ALIST, V),element(set,[name=N|ALIST],VV)):-atom_concat_safe('set_',N,VAR_ATOM),convert_template(Ctx,V,VV).
  276
  277% bot_xxx/botxxx
  278convert_ele(Ctx,element(BOT_ATOM, ALIST, V),element(bot,[name=N|ALIST],VV)):-atom_concat_safe('bot_',N,BOT_ATOM),convert_template(Ctx,V,VV).
  279convert_ele(Ctx,element(BOT_ATOM, ALIST, V),element(bot,[name=N|ALIST],VV)):-atom_concat_safe('bot',N,BOT_ATOM),lengthAtLeast(N,2),convert_template(Ctx,V,VV),!.
  280
  281% getXXX
  282convert_ele(Ctx,element(VAR_ATOM, ALIST, V),element(get,[name=N|ALIST],VV)):-atom_concat_safe('get',N,VAR_ATOM),lengthAtLeast(N,2),convert_template(Ctx,V,VV),!.
  283
  284% version/id/favfood/date/size
  285% HANDLE this in computeAnswer except for favfood maybe? for now favfood is still in computeAnswer
  286% convert_ele(Ctx,element(BOT_ATOM, ALIST, V),element(bot,[name=BOT_ATOM|ALIST],VV)):- globalAliceTagVar(BOT_ATOM),convert_template(Ctx,V,VV),!.
  287
  288% ===================================================================
  289% ===================================================================
  290
  291%DELAY convert_ele(Ctx,element(random, [], B),random(BB)):-convert_template(Ctx,B,BB).
  292%DELAY convert_ele(Ctx,element(li, Attrib, B),element(li, Attrib, BB)):-convert_template(Ctx,B,BB).
  293%DELAY convert_ele(Ctx,element(star, [], []),(*)).
  294convert_ele(_Ctx,element(a, [Target, Link], Name),A):-sformat(S,'<a ~q ~q>~w</a>',[Target, Link, Name]),string_to_atom(S,A).
  295convert_ele(_Ctx,element(a, [Link], Name),A):-sformat(S,'<a ~q>~w</a>',[Link, Name]),string_to_atom(S,A).
  296
  297%DELAY convert_ele(Ctx,element(get, [name=Var], []),get(Var)):-!.
  298convert_ele(_Ctx,element(learn,Attrs,MORE),element(learn,NewAttrs,MORE)):- Become = srcfile, append(Left,[N=V|Right],Attrs),pathAttrib(N),N\=Become,append(Left,[Become=V|Right],NewAttrs),!.
  299convert_ele(_Ctx,element(load, Attrs,MORE),element(load ,NewAttrs,MORE)):- Become = srcfile, append(Left,[N=V|Right],Attrs),pathAttrib(N),N\=Become,append(Left,[Become=V|Right],NewAttrs),!.
  300convert_ele(_Ctx,element(sr,ALIST,MORE),element(srai,ALIST,[element(star,ALIST,MORE)])):-!.
  301convert_ele(_Ctx,element(star,ALIST,MORE),star(pattern,XLAT2,MORE2)):-!,starIndex(star,pattern,ALIST,MORE,XLAT2,MORE2).
  302  starIndex(_Tag,_Star,ALIST,MORE,XLAT2,MORE2):-convert_attributes(Ctx,ALIST,XLAT2),convert_template(Ctx,MORE,MORE2),!.
  303
  304convert_ele(_Ctx,element(Tag,ALIST,MORE),star(Star,XLAT2,MORE2)):- starType(Tag,Star),!,starIndex(Tag,Star,ALIST,MORE,XLAT2,MORE2).
  305   starType(Tag,Star):-member(Tag=Star,[star=pattern,topicstar=topic,guardstar=guard,inputstar=pattern,thatstar=that,get_star=pattern]),!.
  306   starType(Tag,Star):-atom_concat_safe(Star,'_star',Tag),!.
  307   starType(Tag,Star):-atom_concat_safe(Star,'star',Tag),!.
  308
  309convert_ele(Ctx,element(Tag, ALIST , INNER_XML), RESULT):-
  310      transform_aiml_structure(Tag,NewTag,ALIST,NewProps,INNER_XML,NEWPATTERN),
  311      convert_ele(Ctx,element(NewTag, NewProps, NEWPATTERN),RESULT),!.
  312
  313convert_ele(Ctx,L,LO):-is_list(L),flatten(L,M),!,
  314	    (L==M -> LO=M ; convert_template(Ctx,M,LO)).
  315
  316%convert_ele(Ctx,A,B):-atom(A),atom_number(A,B).
  317
  318convert_ele(_Ctx,A,W):-atom(A),atomWSplit(A,B),!,convert_text(B,W),!.
  319
  320convert_ele(Ctx,element(A, B, C),INNER_XML):-tagType(A, immediate),!,
  321      convert_name(A,AA),
  322      convert_attributes(Ctx,B,BB),
  323      convert_template(Ctx,C,CC),!,
  324   (element(A, B, C) == element(AA, BB, CC) ->  INNER_XML=element(AA, BB, CC); convert_element(Ctx,element(AA, BB, CC),INNER_XML)),!.
  325
  326convert_ele(Ctx,element(A, B, C),INNER_XML):-
  327      convert_name(A,AA),
  328      convert_attributes(Ctx,B,BB),
  329      convert_template(Ctx,C,CC),!, 
  330   (element(A, B, C) == element(AA, BB, CC) ->  INNER_XML=element(AA, BB, CC); convert_element(Ctx,element(AA, BB, CC),INNER_XML)),!.
  331
  332convert_ele(Ctx,element(Tag, A, B),element(Tag, A, BB)):- member(Tag,[category]), convert_template(Ctx,B,BB).
  333
  334convert_ele(Ctx,element(Tag, A, B),element(Tag, A, BB)):- member(Tag,[srai]),atrace,convert_template(Ctx,B,BB).
  335
  336convert_ele(_Ctx,O,O).
  337
  338
  339convert_attributes(Ctx,A,AAA):- hotrace(prolog_must((convert_attributes0(Ctx,A,AA),list_to_set_safe(AA,AAA)))).
  340convert_attributes0(Ctx,[B|A],[BB|AA]):-convert_attribute(B,BB),convert_attributes0(Ctx,A,AA).
  341convert_attributes0(_Ctx,[],[]).
  342
  343convert_attribute(A=B,AA=BB):-convert_name(A,AA),convert_template(_Ctx,B,BB).
  344
  345convert_name(A,AAA):-convert_name0(A,AA), (A==AA -> AAA=AA ; convert_name(AA,AAA)),!.
  346
  347convert_name0(A,AA):-literal_atom_safe(A,AA).
  348convert_name0(var,name).
  349convert_name0(Attrib,srcfile):-pathAttrib(Attrib),!.
  350
  351% ===================================================================
  352% ===================================================================
  353
  354% ===============================================================================================
  355%  refomat type transformations
  356% ===============================================================================================
  357
  358isVerbatumTag(N):-memberchk(N,[call,precall,srcfile,srcdir,lineno,srcinfo]),!.
  359isVerbatumTag(N):-pathAttrib(N),!.
  360
  361
  362transformTagData(Ctx,[Name|S],Else,ValueI,ValueO):- member(N,[Name|S]),transformTagData0(Ctx,N,Else,ValueI,ValueO),prolog_must(N\==ValueO).
  363transformTagData(Ctx,[Name|S],Else,ValueI,ValueO):- member(N,[Name|S]),!,transformTagData1(Ctx,N,Else,ValueI,ValueO),prolog_must(N\==ValueO).
  364transformTagData(Ctx,Tag,Else,ValueI,ValueO):-transformTagData0(Ctx,Tag,Else,ValueI,ValueO),prolog_must(Tag\==ValueO).
  365transformTagData(Ctx,Tag,Else,ValueI,ValueO):-transformTagData1(Ctx,Tag,Else,ValueI,ValueO),prolog_must(Tag\==ValueO).
  366
  367% this was _Tag.. very bad!
  368tagStar(_TAG,Star,Star):-!.
  369
  370transformTagData0(_Ctx,TAG,_Default,[*],TAGSTAR):-tagStar(TAG,*,TAGSTAR),!.
  371transformTagData0(_Ctx,TAG,_Default,*,TAGSTAR):-tagStar(TAG,*,TAGSTAR),!.
  372transformTagData0(_Ctx,TAG,_Default,['_'],TAGSTAR):-tagStar(TAG,'_',TAGSTAR),!.
  373transformTagData0(_Ctx,TAG,_Default,'_',TAGSTAR):-tagStar(TAG,'_',TAGSTAR),!.
  374transformTagData0(Ctx,Tag,_Else,ValueI,ValueO):- ValueI=='$current_value', current_value(Ctx,Tag,ValueO),!.
  375transformTagData0(_Ctx,_N,_Else,gensym(Named),ValueO):-useCateID,atom(Named),gensym(Named,ValueO),!.
  376transformTagData0(_Ctx,N,Else,ValueO,ValueO):-isVerbatumTag(N),!, member(Else,['$current_value']),!.
  377transformTagData0(Ctx,TAG,_Default,PATTERN_IN,PATTERN_OUT):-isPatternTag(TAG),convert_pattern(Ctx,PATTERN_IN,PATTERN_OUT),!.
  378
  379transformTagData0(Ctx,TAG,_Default,PATTERN_IN,PATTERN_OUT):-
  380  isOutputTag(TAG),convert_template_pred(Ctx,=,PATTERN_IN,PATTERN_OUT),!,
  381  nop((traceIf((    
  382    member(element(THAT,_,_),PATTERN_IN),
  383    not(member(element(THAT,_,_),PATTERN_OUT)),
  384    not(member(THAT,[br,star,pattern,thatstar,topicstar,think,srai,sr]))
  385    )))),
  386  convert_template_pred(Ctx,=,PATTERN_IN,_PATTERN_OUT_UNUSED).
  387
  388transformTagData1(_Ctx,TAG,_Default,PATTERN_IN,PATTERN_OUT):- member(TAG,[userdict,graph]),literal_atom_safe(PATTERN_IN,PATTERN_OUT),!.
  389transformTagData1(_Ctx,TAG,_Default,PATTERN_IN,PATTERN_OUT):-infoTagLikeLineNumber(TAG),!,PATTERN_IN=PATTERN_OUT.
  390
  391transformTagData1(Ctx,_TAG,_Default,PATTERN_IN,PATTERN_OUT):- %%% debugFmt(transformTagData(TAG,Default,PATTERN_IN)), 
  392                 convert_template_pred(Ctx,literal_atom_safe,PATTERN_IN,PATTERN_OUT),!.
  393transformTagData1(Ctx,_N,_Default,R,RR):-convert_template(Ctx,R,RR),!. 
  394transformTagData1(_Ctx,_TAG,_Default,PATTERN,PATTERN):-!.
  395
  396% ===============================================================================================
  397% ===============================================================================================
  398
  399convert_pattern(Ctx,PATTERN_IN,PATTERN_OUT):- convert_template_pred(Ctx,matchable_literal_safe_non_special,PATTERN_IN,PATTERN_OUT),!.
  400
  401matchable_literal_safe_non_special(A,A):-not(atom(A)),!.
  402matchable_literal_safe_non_special(Atom,Atom):-atom_prefix(Atom,'#$'),!.
  403matchable_literal_safe_non_special(A,U):-literal_atom_safe(A,U).
  404
  405convert_template_pred(Ctx,Pred,PATTERN_IN,PATTERN_OUT):- convert_template(Ctx,PATTERN_IN,PATTERN_MID),!,
  406     prolog_must(map_tree_to_list(Pred,PATTERN_MID,PATTERN_OUT)),!.
  407
  408transform_aiml_structure(catagory,category,OldProps,OldProps,NEWPATTERN,NEWPATTERN).
  409transform_aiml_structure(alice,aiml,OldProps,OldProps,NEWPATTERN,NEWPATTERN).
  410transform_aiml_structure('name','bot',OldProps,[name=['name']|OldProps],NEWPATTERN,NEWPATTERN).
  411transform_aiml_structure(OldName,NewName,OldProps,NewProps,NEWPATTERN,NEWPATTERN):-
  412      specialIndex(OldName,NewName,AddProps),append(AddProps,OldProps,NewProps).
  413
  414specialIndex(justbeforethat,that,[index=(2:1)]).
  415specialIndex(justthat ,input,[index=2]).
  416specialIndex(beforethat,input,[index=3]).
  417
  418%%specialIndex(load,learn,[]).
  419specialIndex(set_female,set,[name=gender,value=female]).
  420
  421specialIndex(getname,name,[name=[name]]).
  422specialIndex(gettopic,name,[name=[name]]).
  423
  424specialIndex(personf,formatter,[type=url_encode]).
  425specialIndex(Name,formatter,[type=Type]):-formatterType(Name,Type),!.
  426
  427
  428formatterProc(Dict):-member(Dict,[formal,uppercase,lowercase,sentence,gossip,think,(format)]).
  429formatterType(TagName,TagName):-formatterProc(TagName).
  430formatterTypeMethod(TagName,Type,Method):-formatterType(TagName,Type),atom_concat(format_,Type,Method),!.
  431
  432
  433evaluatorTag(Tag):-member(Tag,[system,javascript,eval,
  434                                     cycquery,cycsystem,cycassert,
  435                                     fortunecookie,substitute,learn,aiml,genlMt,think,
  436                                     substitute,srai,testsuite,testcase,template,set]).
  437
  438
  439substitutionDictsName(pattern,input).
  440substitutionDictsName(N,N):-substitutionDicts(N).
  441
  442substitutionDicts(input).
  443substitutionDicts(output).
  444substitutionDicts(gender).
  445substitutionDicts(person).
  446substitutionDicts(person2).
  447substitutionDicts(person3).
  448%substitutionDicts(Dict):-evaluatorTag(Dict).
  449
  450
  451tagType(Tag,immediate):-evaluatorTag(Tag),!.
  452tagType(Tag,pushable):-cateFallback(LIST),member([Tag=_],LIST).
  453tagType(Tag,insideCate):-cateMember(Tag).
  454
  455tagType(Tag,requiredCate):-member(Tag,[pattern,template]).
  456tagType(Tag,optionalCate):-cateMember(Tag),not(tagType(Tag,requiredCate))