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
   11%:-module()
   12%:-include('logicmoo_utils_header.pl'). %<?
   13%:- style_check(-singleton).
   14%%:- style_check(-discontiguous).
   15/*
   16:- if((current_prolog_flag(version,MMmmPP),MMmmPP<70000)).
   17:- style_check(-atom).
   18:- style_check(-string).
   19:- endif.
   20*/

   21
   22:-discontiguous(convert_ele/3).
   23
   24:-ensure_loaded('logicmoo_module_aiml_graphmaster.pl').
   25:-ensure_loaded('logicmoo_module_aiml_convertor.pl').
   26:-ensure_loaded('logicmoo_module_aiml_cxt_path.pl').
   27
   28% =================================================================================
   29% Entity Loading
   30% =================================================================================
   31
   32graph_or_file(_Ctx,_ATTRIBS, [], []):-!.
   33graph_or_file(Ctx,ATTRIBS, [Filename], XML):-atomic(Filename),!,graph_or_file(Ctx,ATTRIBS, Filename, XML),!.
   34
   35graph_or_file(Ctx,ATTRIBS,Filename,XML):-graph_or_file_or_dir(Ctx,ATTRIBS,Filename,XML),!.
   36graph_or_file(Ctx,ATTRIBS, Filename, XML):- atom(Filename),member(Quote-Pair,['\''-'\'','"'-'"','<'-'>','('-')']),
   37     atomic_list_concat_aiml([Quote,Mid,Pair],Filename),!,atrace,graph_or_file(Ctx,ATTRIBS, Mid, XML).
   38graph_or_file(Ctx,ATTRIBS, Filename, XML):- 
   39     getCurrentFileDir(Ctx, ATTRIBS, CurrentDir),join_path(CurrentDir,Filename,Name),os_to_prolog_filename(Name,NameO),atrace,
   40     prolog_must(graph_or_file_or_dir(Ctx,[currentDir=CurrentDir|ATTRIBS],NameO,XML)),!.
   41graph_or_file(Ctx,ATTRIBS, Filename, XML):- os_to_prolog_filename(Filename,NameO),!, prolog_must(graph_or_file_or_dir(Ctx,ATTRIBS,NameO,XML)),!.
   42
   43graph_or_file(_Ctx,ATTRIBS, Filename, [nosuchfile(Filename,ATTRIBS)]):-atrace.
   44
   45
   46graph_or_file_or_dir(Ctx,ATTRIBS, Filename, XML):- Filename=[A,B|_C],atom(A),atom(B),
   47                    joinAtoms(Filename,'',FileAtom),!,
   48                    prolog_must(graph_or_file_or_dir(Ctx,ATTRIBS, FileAtom, XML)),!.
   49
   50graph_or_file_or_dir(_Ctx,ATTRIBS, Filename,[element(aiml, [srcfile=AbsoluteFilename|ATTRIBS], XML)]):- os_to_prolog_filename(Filename,AFName),
   51               exists_file_safe(AFName),global_pathname(AFName,AbsoluteFilename),!,
   52               dmsg(load_structure(AbsoluteFilename)),
   53               load_structure(AFName,XML,[dialect(xml),space(remove)]),!.
   54
   55graph_or_file_or_dir(Ctx,ATTRIBS, F, [element(aiml,DIRTRIBS,OUT)]):- DIRTRIBS = [srcdir=F|ATTRIBS],
   56      os_to_prolog_filename(F,ADName),
   57      exists_directory_safe(ADName),
   58      aiml_files(ADName,Files),!,
   59      findall(X, ((member(FF,Files), 
   60                   graph_or_file_or_dir(Ctx,[srcfile=FF|DIRTRIBS],FF,X))), OUT),!.
   61
   62
   63getCurrentFile(Ctx,ATTRIBS,CurrentFile):- atrace,attributeValue(Ctx,ATTRIBS,[srcfile,currentFile],CurrentFile,'$failure'),!.
   64getCurrentFile(Ctx,_ATTRIBS,CurrentFile):-
   65            prolog_must(current_value(Ctx,proof,Proof)),
   66            nonvar(Proof),
   67            current_value(Proof,lastArg,CurrentFile1),current_value(CurrentFile1,lastArg,CurrentFile2),
   68            current_value(CurrentFile2,arg(1),CurrentFile3),!,
   69            prolog_must(atom(CurrentFile3)),
   70            absolute_file_name(CurrentFile3,CurrentFile),!.
   71
   72            
   73
   74getCurrentFileDir(Ctx,ATTRIBS,CurrentFile):- attributeValue(Ctx,ATTRIBS,[currentDir],CurrentFile,'$failure'),!.
   75getCurrentFileDir(Ctx,ATTRIBS,Dir):- prolog_must((getCurrentFile(Ctx, ATTRIBS, CurrentFile),atom(CurrentFile),
   76      file_directory_name(CurrentFile,Dir0),absolute_file_name(Dir0,Dir))).
   77
   78getCurrentFileDir(_Ctx,_ATTRIBS,Dir):- local_directory_search_combined(Dir).
   79
   80
   81% =================================================================================
   82% AIML Loading
   83% =================================================================================
   84reloadAimlFiles:-withCurrentContext(reloadAimlFiles).
   85reloadAimlFiles(Ctx):-forall(retract(loaded_aiml_file(A,P,_)),assert(pending_aiml_file(A,P))),do_pending_loads(Ctx).
   86
   87%%load_aiml_files:- aimlCateSig(CateSig),retractall(CateSig),fail.
   88%load_aiml_files:-once(load_aiml_files('test_suite/*.aiml')),fail.
   89%%load_aiml_files:-once(load_aiml_files(Ctx,'*.aiml')),fail.
   90%load_aiml_files:-aimlCateSig(CateSig),pp_listing(CateSig).
   91load_aiml_files.
   92
   93%%tell(f5),load_aiml_files('part5/*.aiml'),told.
   94
   95load_aiml_files(Files):-currentContext(load_aiml_files,Ctx),with_no_gc((prolog_must(load_aiml_files(Ctx,Files)),!,prolog_must(do_pending_loads(Ctx)))).
   96
   97% Detect between content vs filename
   98load_aiml_files(Ctx,element(Tag,Attribs,ContentIn)):- !, 
   99  prolog_must((load_aiml_structure(Ctx,element(Tag,Attribs,ContentIn)),!,do_pending_loads(Ctx))).
  100load_aiml_files(Ctx,File):- 
  101 withAttributes(Ctx,[withCategory=[writeqnl,assert_cate_in_load]],
  102   prolog_must(with_files(load_single_aiml_file(Ctx),File))),!,
  103     do_pending_loads(Ctx).
  104
  105
  106translate_aiml_files(Files):-currentContext(translate_aiml_files,Ctx),translate_aiml_files(Ctx,Files),!.
  107
  108translate_aiml_files(Ctx,File):- \+ (is_list(File);atom(File)),!,translate_aiml_structure(Ctx,File),!.
  109translate_aiml_files(Ctx,File):-with_files(translate_single_aiml_file(Ctx),File),!.
  110
  111
  112with_files_list(Verb,[File|Rest]):- maplist_safe(Verb,[File|Rest]),!,do_pending_loads.
  113
  114denotesAimlDir('aiml/').
  115denotesAimlDir('../aiml/').
  116denotesAimlDir('/aiml/').
  117
  118with_files(Verb,List):-is_list(List),!,maplist(with_files(Verb),List).
  119with_files(Verb,File):-compound(File),!, global_pathname(File,FILES), File \= FILES,with_files(Verb,FILES),!.
  120with_files(Verb,File):-exists_directory_safe(File),!,prolog_must(atomic(File)),aiml_files(File,Files),!,with_files_list(Verb,Files),!.
  121with_files(Verb,File):-exists_file_safe(File),!,with_files_list(Verb,[File]).
  122with_files(Verb,File):-file_name_extension(File,'aiml',Aiml), exists_file_safe(Aiml),!,with_files(Verb,[File]).
  123with_files(Verb,File):-expand_file_name(File,FILES),FILES\==[],!,with_files_list(Verb,FILES),!.
  124with_files(Verb,File):- denotesAimlDir(DenotesAimlDir),atom_concat(DenotesAimlDir,Rest,File),!,with_files(Verb,aiml(Rest)).
  125%with_files(Verb,File):-atom(File),sub_atom(_File,Before,_Len,_After,'*'),!,with_files(Verb,aiml(File)).
  126with_files(Verb,File):-!,with_files(Verb,aiml(File)).
  127%%with_files(Verb,File):-prolog_must(call(Verb,File)).
  128%%with_files(Verb,File):-throw_safe(error(existence_error(source_sink, File),functor(Verb,F,A),context(F/A, 'No such file or directory'))).
  129
  130aiml_files(File,Files):-atom(File),sub_atom(File,_Before,_Len,_After,'*'),!,expand_file_name(File,Files),!.
  131aiml_files(File,Files):-atom_concat_safe(WithOutSlashes,'/',File),!,aiml_files(WithOutSlashes,Files).
  132aiml_files(File,Files):-exists_directory_safe(File), %absolute_file_name(File,_FileDir),
  133      atom_concat_safe(File,'/*.aiml',Mask),aiml_files(Mask,Files),!.
  134
  135
  136aimlOption(rebuild_Aiml_Files,false).
  137
  138load_single_aiml_file(Ctx,F0):- global_pathname(F0,File),F0\==File,!,load_single_aiml_file(Ctx,File).
  139load_single_aiml_file(Ctx,F0):-
  140  prolog_mustEach((
  141   global_pathname(F0,File),
  142   cateForFile(Ctx,File,FileMatch),!,
  143   atom_concat_safe(File,'.tmp.pl',PLNAME),
  144   load_single_aiml_file(Ctx,File,PLNAME,FileMatch),!)).
  145
  146%%load_single_aiml_file(_Ctx,File,PLNAME,_FileMatch):- loaded_aiml_file(File,PLNAME,_Time),!.
  147load_single_aiml_file(Ctx,File,PLNAME,FileMatch):-
  148   translate_single_aiml_file(Ctx,File,PLNAME,FileMatch),!,
  149   assertz(pending_aiml_file(File,PLNAME)),!.
 sgml_parser_defs(PARSER_DEFAULTS, PARSER_CALLBACKS)
  153sgml_parser_defs(
  154  [defaults(false), space(remove),/*number(integer),*/ qualify_attributes(false),
  155         %call(decl, on_decl),
  156         %call(pi, on_pi),call(xmlns, on_xmlns),call(urlns, xmlns),
  157         %%call(error,xml_error),
  158         dialect(xml)
  159         ],
  160         [max_errors(0),call(begin, on_begin),call(end, on_end)]).
  161
  162
  163% ?- string_to_structure('<?xml version="1.0" encoding="ISO-8859-1"?>\n<aiml><p>hi</p></aiml>',X).
  164
  165% ?- string_to_structure('<category><pattern>_ PLANETS</pattern></category>',X).
  166
  167
  168tls :- string_to_structure('<aiml><p>hi</p></aiml>',X),wdmsg(X).
  169tls2 :- string_to_structure('<?xml version="1.0" encoding="ISO-8859-1"?>\n<aiml><p>hi</p></aiml>\n\n',X),wdmsg(X).
  170
  171string_to_structure(String,XMLSTRUCTURESIN):- fail, sformat(Strin0,'<pre>~s</pre>',[String]),string_to_structure0(Strin0,XMLSTRUCTURES),!,
  172   trace,
  173   prolog_must([element(pre,[],XMLSTRUCTURESIN)]=XMLSTRUCTURES).
  174
  175
  176string_to_structure(String,XMLSTRUCTURES):- string_to_structure0(String,XMLSTRUCTURES),!.
  177string_to_structure0(String,XMLSTRUCTURES):- 
  178     %%sgml_parser_defs(PARSER_DEFAULTS,_PARSER_CALLBACKS),
  179     PARSER_DEFAULTS = [defaults(false), space(remove),/*number(integer),*/ qualify_attributes(false),dialect(xml)],
  180     string_to_structure0(String,PARSER_DEFAULTS,XMLSTRUCTURES),!.
  181
  182string_to_structure(String,ParserDefaults0,XMLSTRUCTURES):-string_to_structure0(String,ParserDefaults0,XMLSTRUCTURES).
  183
  184string_to_structure0(String,ParserDefaults0,XMLSTRUCTURESIN):- atom_concat(' ',Str,String),!,
  185  string_to_structure0(Str,ParserDefaults0,XMLSTRUCTURESIN).
  186string_to_structure0(String,ParserDefaults0,['@'|XMLSTRUCTURESIN]):- atom_concat('@',Str,String),!,  
  187  string_to_structure0(Str,ParserDefaults0,XMLSTRUCTURESIN).
  188
  189string_to_structure0(String,ParserDefaults0,XMLSTRUCTURESIN):- \+ atom_concat('<',_,String),!,
  190  atomic_list_concat(['<?xml version="1.0" encoding="ISO-8859-1"?>\n<aiml>',String,'</aiml>'],Str),
  191  string_to_structure0(Str,ParserDefaults0,[element(aiml, [],XMLSTRUCTURESIN)]).
  192
  193string_to_structure0(String,ParserDefaults0,XMLSTRUCTURESIN):-
  194  string_to_structure1(String,ParserDefaults0,XMLSTRUCTURESIN),
  195  ignore(append(XMLSTRUCTURESIN,[],_)).
  196
  197
  198string_to_structure1(String,ParserDefaults0,XMLSTRUCTURESIN):-
  199        setup_call_cleanup(((string_to_stream(String,In),new_sgml_parser(Parser, []))),
  200          prolog_must((                     
  201           atom_length(String,Len),
  202           append(ParserDefaults0,[],PARSER_DEFAULTS),
  203           maplist_safe(set_sgml_parser(Parser),PARSER_DEFAULTS),
  204           string_parse_structure(Len, Parser, user:PARSER_DEFAULTS, XMLSTRUCTURES, In)
  205           )),
  206       (free_sgml_parser(Parser),close(In))),!,prolog_must(XMLSTRUCTURESIN=XMLSTRUCTURES).
  207
  208string_parse_structure(Len,Parser, M:Options, Document, In) :-
  209	notrace((catch(call(call,string_parse_structure_opts_547(Parser),In,M,Options,Options2),_,string_parse_structure_opts(Parser,In,M,Options,Options2)))),
  210        % notrace((string_parse_structure_opts(Parser,In,M,Options,Options2))),
  211	sgml:sgml_parse(Parser,
  212		   [ document(Document),
  213		     source(In),
  214                     parse(input),
  215                     content_length(Len)
  216		   | Options2
  217		   ]).
  218
  219/*
  220string_parse_structure_opts_547(Parser, _In, _M, Options,Options2):-
  221	sgml:set_parser_options(Parser, Options, Options1),
  222	Options2=Options1.
  223*/

  224
  225string_parse_structure_opts(Parser,In,M,Options,Options2):-
  226	sgml:set_parser_options(Options, Parser, In, Options1),
  227        sgml:parser_meta_options(Options1, M, Options2).
  228
  229
  230
  231fileToLineInfoElements(Ctx,File,XMLSTRUCTURES):-
  232    atom_concat(File,'.term',Elis),
  233     (file_newer(Elis,File) ->  
  234      termFileContents(Ctx,Elis,XMLSTRUCTURES) ;
  235       fileToLineInfoElements0(Ctx,File,XMLSTRUCTURES)).
  236
  237
  238termFileContents(_Ctx,File,termFileContents(File)):-!. %%,atrace.
  239
  240termFileContents(_Ctx,File,element(aiml,[],XMLSTRUCTURES)):-
  241   setup_call_cleanup((open(File, read, In, [])), 
  242      findall(Elem,((repeat,read(In,Elem),((Elem\=end_of_file)->true;!))),XMLSTRUCTURES), close(In)),!
  242.
  243
  244
  245
  246% gather line numbers
  247fileToLineInfoElements0(Ctx,F0,XMLSTRUCTURES):-
  248   global_pathname(F0,File),
  249       retractall(lineInfoElement(File,_,_,_)),
  250        setup_call_cleanup((open(File, read, In, [type(binary)]),new_sgml_parser(Parser, [])),
  251
  252          prolog_must((           
  253           sgml_parser_defs(PARSER_DEFAULTS,PARSER_CALLBACKS),
  254           maplist_safe(set_sgml_parser(Parser),[file(File)|PARSER_DEFAULTS]),
  256           sgml_parse(Parser,[source(In)|PARSER_CALLBACKS]))
  256)
  256,
  257
  258        (free_sgml_parser(Parser),close(In)))
  258,!,
  259
  260
  261        fileToLineInfoElements2(Ctx,File,XMLSTRUCTURES)
  261.
  262
  263
  264% gather line contents
  265fileToLineInfoElements2(Ctx,File,XMLSTRUCTURES):-!,
  266  sgml_parser_defs(PARSER_DEFAULTS,_PARSER_CALLBACKS),
  267  setup_call_cleanup(open(File, read, In, [type(binary)]),(load_structure(In,Whole, [file(File)|PARSER_DEFAULTS]),!,
  268   load_inner_aiml_w_lineno(File,[],[],[],Ctx,Whole,XMLSTRUCTURES)),close(In)),!.
  269
  270load_inner_aiml_w_lineno(_SrcFile,_OuterTag,_Parent,_Attributes,_Ctx,Atom,Atom):-(atomic(Atom);var(Atom)),!.
  271load_inner_aiml_w_lineno(SrcFile,OuterTag,Parent,Attributes,Ctx,[H|T],LL):-!,
  272      maplist_safe(load_inner_aiml_w_lineno(SrcFile,OuterTag,Parent,Attributes,Ctx),[H|T],LL),!.
  273
  274% offset
  275load_inner_aiml_w_lineno(SrcFile,[OuterTag|PREV],Parent,Attributes,Ctx,element(Tag,Attribs,ContentIn),element(Tag,NewAttribs,ContentOut)):-
  276   Context=[Tag,OuterTag|_],
  277   MATCH = lineInfoElement(SrcFile,Line:Offset, Context, element(Tag, Attribs, no_content_yet)),
  278   MATCH,!,
  279   ignore(Line = nonfile),
  280   ignore(Offset = nonfile),
  281   appendAttributes(Ctx,Attributes,Attribs,RightAttribs),
  283   Src = nosrc,
  284   appendAttributes(Ctx,[srcfile=SrcFile:Line-Offset,srcinfo=Src],RightAttribs,NewAttribs),
  285   ignore(retract(MATCH)),
  286   (member(Tag,[aiml,topic]) ->  NextAttribs = NewAttribs ; NextAttribs = []),
  287   maplist_safe(load_inner_aiml_w_lineno(SrcFile,[Tag,OuterTag|PREV],Parent,NextAttribs,Ctx),ContentIn,ContentOut),!
  287.
  288
  289load_inner_aiml_w_lineno(SrcFile,MORE,Parent,Attributes,Ctx,element(Tag,Attribs,ContentIn),element(Tag,RightAttribs,ContentOut)):-
  290   appendAttributes(Ctx,Attributes,Attribs,RightAttribs),
  291   load_inner_aiml_w_lineno(SrcFile,[Tag|MORE],Parent,[],Ctx,ContentIn,ContentOut),!.
  292
  293load_inner_aiml_w_lineno(SrcFile,OuterTag,Parent,Attributes,_Ctx,L,L):-
  294   aiml_error(load_inner_aiml_w_lineno(SrcFile,OuterTag,Parent,Attributes,L)).
  295
  296
  297addAttribsToXML(Attribs,element(Tag,Pre,Content),element(Tag,Post,Content)):-appendAttributes(_Ctx,Pre,Attribs,Post),!.
  298addAttribsToXML(Attribs,[H|T],OUT):-maplist_safe(addAttribsToXML(Attribs),[H|T],OUT),!.
  299addAttribsToXML(Attribs,OUT,OUT):-!,debugFmt(addAttribsToXML(Attribs,OUT,OUT)),!.
  300
  301
  302:-thread_local(in_aiml_tag/1).
  303:-thread_local(inLineNum/0).
  304
  305skipOver(_).
  306
  307on_end('aiml', _) :- !,
  308        ignore(retract(in_aiml_tag(_))).
  309
  310on_begin('aiml', Attribs, _) :- !,
  311        asserta(in_aiml_tag(Attribs)).
  312
  313
  314on_begin(Tag, Attr, Parser) :- skipOver(not(inLineNum)),
  315        get_sgml_parser(Parser,context(Context)), Context=[Tag,aiml|_],
  316        skipOver(debugFmt(on_begin(Tag, Attr, Context))),
  317        skipOver(retract(in_aiml_tag(AimlAttr))),
  318       % skipOver(sgml_parser_defs(PARSER_DEFAULTS, PARSER_CALLBACKS)),
  319        get_sgml_parser(Parser,line(Line)),
  320        get_sgml_parser(Parser,charpos(Offset)),
  321        get_sgml_parser(Parser,file(File)),
  322        global_pathname(File,Pathname),
  323      %  get_sgml_parser(Parser,source(Stream)),
  324        skipOver(asserta(inLineNum)),
  325%        load_structure(Stream,Content,[line(Line)|PARSER_DEFAULTS]),!,
  326 %      skipOver( sgml_parse(Parser,[ document(Content),parse(input)])),
  327        NEW = lineInfoElement(Pathname,Line:Offset, Context, element(Tag, Attr, no_content_yet)),
  328        %%debugFmt(NEW),
  329        skipOver(ignore(retract(inLineNum))),
  330        skipOver(asserta(in_aiml_tag(AimlAttr))),
  331        assertz(NEW),!.
  332
  333on_begin(_Tag, _Attr, _Parser) :-!. %%get_sgml_parser(Parser,context(Context)),!. %%,debugFmt(on_begin_Context(Tag, Attr, Context)).
  334
  335%%on_begin_ctx(TAG, URL, Parser, Context) :-!, debugFmt(on_begin_ctx(URL, TAG, Parser,Context)),!.
  336on_begin_ctx(_TAG, _URL, _Parser, _Context) :- !. %%, debugFmt(on_begin_ctx(URL, TAG, Parser,Context)),!.
  337
  338
  339
  340:- thread_local
  341        xmlns/3.
  342
  343on_xmlns(rdf, URL, _Parser) :- !,debugFmt(on_xmlns(URL, rdf)),asserta(xmlns(URL, rdf, _)).
  344on_xmlns(TAG, URL, _Parser) :- sub_atom(URL, _, _, _, 'rdf-syntax'), !,
  345        debugFmt('rdf-syntax'(URL, TAG)),
  346        immediateCall(_Ctx,asserta(xmlns(URL, rdf, _))).
  347on_xmlns(TAG, URL, _Parser) :- debugFmt(on_xmlns(URL, TAG)).
  348
  349on_decl(URL, _Parser) :- debugFmt(on_decl(URL)).
  350on_pi(URL, _Parser) :- debugFmt(on_pi(URL)).
  351
  352with_no_gc(G):- call(G).
  353%with_no_gc(G):- locally(set_prolog_flag(gc,false),G).
  354
  355
  356xml_error(TAG, URL, Parser) :- !, debugFmt(xml_error(URL, TAG, Parser)).
  357% ============================================
  358% Loading content
  359% ============================================
  360
  361load_aiml_structure_lineno(Attributes,Ctx,L):-maplist_safe(load_inner_aiml_lineno(Attributes,Ctx),L),!.
 offset
  364load_inner_aiml_lineno(Attributes,Ctx,element(Tag,Attribs,ContentIn)):-
  365   appendAttributes(Ctx,Attributes,Attribs,RightAttribs),
  366   prolog_must(attributeValue(Ctx,RightAttribs,[srcfile,srcdir],File,'$error')),
  367   MATCH = lineInfoElement(File,Line:Offset, Context, element(Tag, Attribs, no_content_yet)),
  368   ignore(MATCH),
  369   Context=[_Tag0,aiml|_More],
  370   ignore(Line = nonfile),
  371   ignore(Offset = nonfile),
  372   NewAttribs  = [srcfile=File,lineno=Line:Offset|RightAttribs],
  373   ignore(retract(MATCH)),
  374   load_aiml_structure(Ctx,element(Tag,NewAttribs,ContentIn)),!.
  375
  376   /*
  377
  378   load_inner_aiml_lineno(Attributes,Ctx,element(Tag,Attribs,ContentIn)):-
  379   prolog_must(current_value(Ctx,srcfile,File)),
  380   retract((lineInfoElement(File0,Line0:Offset0,graph, element(_Tag0, _Attr0, _Content0)))),
  381   prolog_must(call(OLD)),
  382
  383   MATCH = lineInfoElement(File,Line:Offset,Context, element(Tag, Attribs, _ContentIn)),!,
  384   prolog_must((call(MATCH),!,not(not((Line:Offset)==(Line0:Offset0))),retract(OLD),
  385   load_aiml_structure(Ctx,element(Tag,[srcinfo=File0:Line0-Offset0|Attribs],ContentIn)),
  386        NEW = lineInfoElement(File,Line:Offset,Attributes, element(Tag, Attribs, ContentIn)),
  387        assertz(NEW))),!.
  388
  389   */

  390
  391addGenltMT(X,Y):-debugFmt(addGenltMT(X,Y)).
  392
  393
  394%load end_of_file
  395load_aiml_structure(_Ctx,end_of_file):-!.
  396
  397%load termFileContents
  398load_aiml_structure(Ctx,termFileContents(File)):- !,
  399 inThreadJoin((
  400  setup_call_cleanup((open(File, read, In, [])), 
  401     ((repeat,
  402       read(In,Elem),
  403         once(load_aiml_structure(Ctx,Elem)),Elem==end_of_file)),
  404      close(In)),!,expireCaches,statistics)).
  405
  406%catagory (mispelling?)
  407load_aiml_structure(Ctx,element(catagory,ALIST,LIST)):-!,with_no_gc(load_aiml_structure(Ctx,element(category,ALIST,LIST))),!.
  408
  409% aiml
  410load_aiml_structure(Ctx,element(aiml,ALIST,LIST)):-
  411    replaceAttribute(Ctx,name,graph,ALIST,ATTRIBS),!,
  412 defaultCatePredicatesS(Defaults),
  413  with_no_gc((withAttributes(Ctx,Defaults,
  414        %withAttributes(Ctx,ATTRIBS,load_aiml_structure_lineno(ATTRIBS,Ctx,LIST)),!.
  415     withAttributes(Ctx,ATTRIBS,maplist_safe(load_aiml_structure(Ctx),LIST))))),!.
  416
  417
  418%genlMt (mispelling?)
  419load_aiml_structure(Ctx,element(genlMt,ALIST,LIST)):-!,atrace,
  420   attributeValue(Ctx,ALIST,[to],To,'$error'),
  421   current_value(Ctx,graph,Else),
  422   attributeValue(Ctx,ALIST,[from],From,'$value'(Else)),
  423   prolog_must(LIST=[]),
  424   addGenltMT(From,To).
  425
  426
  427
  428% \n\n\n
  429load_aiml_structure(Ctx,O):-atomic(O),!,debugFmt(load_aiml_structure(Ctx,O)),!.
  430
  431
  432% topic/category/flags/that
  433load_aiml_structure(Ctx,element(Tag,ALIST,INNER_XML)):- member(Tag,[topic,category,flags,that]),!,
  434     replaceAttribute(Ctx,name,Tag,ALIST,ATTRIBS),
  435         withAttributes(Ctx,ATTRIBS, 
  436           load_aiml_cate_element(Ctx,ATTRIBS,
  437              element(Tag,ALIST,INNER_XML))),!.
  438
  439% substitute,learn,aiml,genlMt,srai,think,system,javascript,eval,template
  440load_aiml_structure(Ctx,element(A,B,C)):-
  441   convert_name(A,Tag),tagType(Tag,immediate),
  442   convert_attributes(Ctx,B,ALIST),
  443   convert_template(Ctx,C,LIST),
  444   replaceAttribute(Ctx,name,Tag,ALIST,ATTRIBS),
  445      withAttributes(Ctx,
  446        ATTRIBS,
  447          catch(aiml_call(Ctx,element(Tag,ALIST,LIST)),E,debugFmt(aiml_throw(element(Tag,ATTRIBS,LIST)=E)))),!.
  448
  449/*
  450
  451% error of pattern
  452load_aiml_structure(Ctx,element(Tag,ALIST,INNER_XML)):- cateMember(Tag), aiml_error(element(Tag,ALIST,INNER_XML)),
  453     replaceAttribute(Ctx,name,Tag,ALIST,ATTRIBS),
  454         withAttributes(Ctx,ATTRIBS, pushCateElement(Ctx,ATTRIBS,element(Tag,ALIST,INNER_XML))),!.
  455
  456*/

  457
  458load_aiml_structure(_Ctx,element(Tag,ALIST,LIST)):- member(Tag,[meta]),!,debugFmt(ignoring(element(Tag,ALIST,LIST))),!.
  459
  460% special dictionaries
  461load_aiml_structure(Ctx,element(Tag,ALIST,LIST)):-
  462   hotrace(load_dict_structure(Ctx,element(Tag,ALIST,LIST))),!
  462.
  463
  464/*
  465% ============================================
  466% Rewrite or Error loading
  467% ============================================
  468
  469hide_load_aiml_structure(Ctx,element(Tag,ALIST,PATTERN)):-
  470     convert_element(Ctx,element(Tag,ALIST,PATTERN),NEW),
  471     load_aiml_structure_diff(Ctx,element(Tag,ALIST,PATTERN),NEW),!.
  472
  473
  474load_aiml_structure_diff(Ctx,BEFORE,AFTER):- BEFORE\==AFTER, load_aiml_structure(Ctx,AFTER),!.
  475%%load_aiml_structure_diff(Ctx,BEFORE,AFTER):- aiml_error(load_aiml_structure(Ctx,BEFORE)),!.
  476
  477*/

  478
  479% <aiml>
  480load_aiml_structure(Ctx,[A|B]):-!,prolog_must(maplist_safe(load_aiml_structure(Ctx),[A|B])),!.
  481
  482load_aiml_structure(Ctx,X):- aiml_error(missing_load_aiml_structure(Ctx,X)).
  483
  484% ============================================
  485% special dictionaries
  486% ============================================
  487dictionaryTags(Tag):-dictionaryOuterTags(Tag);dictionaryItemTags(Tag);dictionaryTypeTags(Tag,_).
  488
  489dictionaryOuterTags(Tag):- member(Tag,[predicates,vars,properties,bots,bot]).
  490dictionaryItemTags(Tag):- member(Tag,[predicate,property,var,item,set,entry]).
  491
  492% Bot properties are predicates that cannot be changed during the runtime life of the bot,
  493% but which can be included in AIML patterns for matching.
  494dictionaryTypeTags(Tag,[bot,default]):-member(Tag,[properties]).
  495dictionaryTypeTags(Tag,[bot]):-member(Tag,[bots,bot,entry]).
  496% Default predicates can be thought of as your bot's "assumptions" about new users.
  497dictionaryTypeTags(Tag,default):-member(Tag,[predicate,predicates]).
  498dictionaryTypeTags(Tag,user):-member(Tag,[var,vars,set]).
  499
  500obtainDictionaryName(Ctx,_Tag,ALIST,Dict):- dictVarName(N), peekNameValue(Ctx,ALIST,N,Dict,'$failure'),!.
  501obtainDictionaryName(_Ctx,Tag,_ALIST,Dict):- dictionaryTypeTags(Tag,Dict),!.
  502obtainDictionaryName(Ctx,_Tag,ALIST,Dict):- peekNameValue(Ctx,ALIST,[dictionary,name],Dict,'$error'),!.
  503
  504
  505:-discontiguous(load_dict_structure/2).
  506% user/bot dictionaries (outers-only)
  507load_dict_structure(Ctx,element(Tag,ALIST,LIST)):-
  508   member(Tag,[predicates,vars,properties]),
  509   replaceAttribute(Ctx,name,dictionary,ALIST,ATTRIBS),
  510   obtainDictionaryName(Ctx,Tag,ATTRIBS,Dict),  
  511   withAttributes(Ctx,[dictionary=Dict|ATTRIBS],
  512    prolog_must((
  513     current_value(Ctx,dictionary,_Dict),
  514      maplist_safe(load_dict_structure(Ctx),LIST)))).
  515
  516% user/bot predicatates (inners-only)
  517load_dict_structure(Ctx,element(Tag,ALIST,LIST)):-member(Tag,[predicate]),
  518   current_value(Ctx,dictionary,Dict),
  519     attributeValue(Ctx,ALIST,[name,var],Name,'$error'),
  520     attributeValue(Ctx,ALIST,[default],Default,''),
  521     attributeValue(Ctx,ALIST,[value,default],Value,LIST),
  522     attributeValue(Ctx,ALIST,['set-return'],SetReturn,value),
  523  prolog_must((
  524     load_dict_structure(Ctx,dict(Dict,Name,Value)),
  525     load_dict_structure(Ctx,dict(defaultValue(Dict),Name,Default)),
  526     load_dict_structure(Ctx,dict(setReturn(Dict),Name,SetReturn)))),!.
  527
  528% user/bot dictionaries name/values
  529load_dict_structure(Ctx,element(Tag,ALIST,LIST)):-member(Tag,[property,var,item,set]),
  530   current_value(Ctx,dictionary,Dict),
  531   prolog_must((
  532     attributeValue(Ctx,ALIST,[name,var],Name,'$error'),
  533     attributeValue(Ctx,ALIST,[value,default],Value,LIST),
  534     load_dict_structure(Ctx,dict(Dict,Name,Value)))),!.
  535
  536
  537
  538% special substitution dictionaries
  539load_dict_structure(Ctx,element(substitutions,ALIST,LIST)):-
  540   prolog_must((
  541      replaceAttribute(Ctx,name,graph,[dictionary=substitutions(input)|ALIST],ATTRIBS),
  542     withAttributes(Ctx,ATTRIBS,
  543     maplist_safe(load_substs(Ctx),LIST)))).
  544
  545
  546load_substs(Ctx,element(Tag,ALIST,LIST)):- substitutionDictsName(Tag,Dict),
  547   prolog_must((
  548      replaceAttribute(Ctx,name,graph,[dictionary=substitutions(Dict)|ALIST],ATTRIBS),
  549     withAttributes(Ctx,ATTRIBS,
  550     maplist_safe(load_substs(Ctx),LIST)))).
  551
  552load_substs(Ctx,element(Tag,ATTRIBS,LIST)):-member(Tag,[substitution,substitute]),!,
  553   prolog_must((
  554      peekNameValue(Ctx,_,dictionary,substitutions(Catalog),'$error'),
  555      attributeValue(Ctx,element(substitute,ATTRIBS,LIST),[old,find,name,before],Find,'$error'),
  556      attributeValue(Ctx,element(substitute,ATTRIBS,LIST),[new,replace,value,after],Replace,'$error'),
  557      prolog_must(load_dict_structure(Ctx,dict(substitutions(Catalog),Find,Replace))))),!.
  558
  559% substitutions
  560load_dict_structure(Ctx,element(substitute,ATTRIBS,LIST)):- load_substs(Ctx,element(substitute,ATTRIBS,LIST)),!.
  561load_dict_structure(Ctx,element(substitution,ATTRIBS,LIST)):- load_substs(Ctx,element(substitute,ATTRIBS,LIST)),!.
  562
  563% detect substitutions
  564load_dict_structure(Ctx,dict(substitutions(Dict),Find,Replace)):-!,
  565   prolog_must(load_dict_structure(Ctx,substitute(Dict,Find,Replace))),!.
  566
  567load_dict_structure(Ctx,substitute(SubstsNameI,Find,Replace)):-!,
  568  prolog_must((
  569      convert_dictname(Ctx,SubstsNameI,SubstsName),
  570      convert_substs(Find,FindM),
  571      %%%convert_text
  572      convert_replacement(Ctx,Replace,ReplaceM),
  573      addReplacement(Ctx,SubstsName,FindM,ReplaceM))),!.
  574
  575% actual assertions
  576load_dict_structure(Ctx,dict(IDict,Name,Value)):-
  577     %%%debugFmt(dict(Dict,Name,Value)),
  578      convert_dictname(Ctx,IDict,Dict),
  579      setAliceMem(Ctx,Dict,Name,Value),!.
  580
  581
  582convert_dictname(_Ctx,A,A):-var(A),!.
  583convert_dictname(_Ctx,you,D):-!,literal_atom(bot,D),!.
  584convert_dictname(_Ctx,A,D):-atom(A),!,literal_atom(A,D),!.
  585convert_dictname(Ctx,[A],D):-convert_dictname(Ctx,A,D),!.
  586convert_dictname(Ctx,A,D):-unresultifyL(Ctx,A,D),!.
  587convert_dictname(Ctx,A,D):-convert_dictname0(Ctx,A,D),nop(traceIf((A\==D,A\==[D]))).
  588
  589convert_dictname0(_Ctx,A,A):-var(A),!.
  590convert_dictname0(Ctx,A,D):-unresultifyL(Ctx,A,AD),A\==AD,!,convert_dictname0(Ctx,AD,D).
  591convert_dictname0(Ctx,[A],D):-nonvar(A),!,convert_dictname0(Ctx,A,D).
  592convert_dictname0(_Ctx,A,D):-atom(A),!,convert_name(A,D).
  593convert_dictname0(_Ctx,A,D):-compound(A),functor(A,F,1),A=..[F,AA],convert_name(AA,DD),D=..[F,DD],!.
  594convert_dictname0(_Ctx,A,A).
  595
  596
  597:-dynamic(replace_t/5).
  598:-dynamic(response_t/5).
  599
  600convert_replacement(Ctx,Replace,ReplaceMM):-convert_template(Ctx,Replace,ReplaceM),listify(ReplaceM,ReplaceMM),!.
  601
  602% ===============================================================================================
  603%  UTILS
  604% ===============================================================================================
  605
  606ignore_aiml(VAR):-var(VAR),!,aiml_error(ignore_aiml_var(VAR)).
  607ignore_aiml([]):-!.
  608ignore_aiml(''):-!.
  609ignore_aiml(A):-atom(A),!,atom_codes(A,C),!,clean_codes(C,D),!,D=[].
  610ignore_aiml([A|B]):-ignore_aiml(A),!,ignore_aiml(B),!.
  611
  612/* commenting since proably not used
  613
  614aiml_classify([],[]).
  615aiml_classify(Find,[atom]):-atomic(Find).
  616aiml_classify([H|INNER_XML],Out):-
  617      classifySingle(H,Class),
  618      aiml_classify(INNER_XML,More),
  619      sort([Class|More],OutM),!,
  620      classify2(OutM,Out).
  621aiml_classify(_T,[unk]).
  622
  623classify2([in,out|Resp],[out|Resp]).
  624classify2(Out,Out).
  625
  626classifySingle('_',var('_')).
  627classifySingle(*,var('*')).
  628classifySingle(Atom,in):-is_literal(Atom).
  629classifySingle(Atom,out):-atom(Atom).
  630classifySingle(Atom,spec(File)):-compound(Atom),functor(Atom,File,_).
  631classifySingle(_Atom,unknown).
  632
  633*/

  634
  635varize(Find,Replace,FindO,ReplaceO):-
  636      subst((Find,Replace),'_','$VAR'(0),(FindM,ReplaceM)),
  637      subst((FindM,ReplaceM),'*','$VAR'(0),(FindO,ReplaceO)),!.
  638
  639
  640% ===============================================================================================
  641%  Load Categories
  642% ===============================================================================================
  643
  644innerTagLikeThat(That):-hotrace(innerTagLike(That,prepattern)).
  645
  646innerTagLike(That,Like):-hotrace((innerTagPriority(That,Atts),memberchk(Like,Atts))).
  647
  648
  649infoTagLikeLineNumber(X):-member(X,[lineno,srcdir,srcfile,srcinfo]).
  650
  651isPatternTag(Tag):-member(Tag,[that,pattern,request,response,topic,flags,guard]).
  652
  653isOutputTag(Tag):-member(Tag,[template,call]).
  654isOutputTag(Tag):-innerTagLike(Tag,postpattern).
  655
  656each_category(_Ctx,_ATTRIBS,_TAGS,element(MUST_CAT,_ALIST,_NOCATEGORIES)):- not(MUST_CAT = category),throw_safe(each_category(MUST_CAT )).
  657
  658% category tag contains pre-<pattern> which must be proccessed pre-template just like <that>
  659each_category(Ctx,ATTRIBS,TAGS,element(TAG,ALIST,NOCATEGORIES)):- innerTagLikeThat(That), member(element(That,WA,WP), NOCATEGORIES),!,
  660   takeout(element(That,WA,WP),NOCATEGORIES,NOPATTERNS),
  661   each_category(Ctx,ATTRIBS,[element(That,WA,WP)|TAGS],element(TAG,ALIST,NOPATTERNS)),!.
  662
  663each_category(Ctx,ATTRIBS,NOPATTERNS,element(TAG,ALIST,PATTERN)):-
  664  prolog_must((
  665   replaceAttribute(Ctx,name,TAG,ALIST,PATTRIBS),
  666   appendAttributes(Ctx,PATTRIBS,ATTRIBS,NEWATTRIBS),
  667   gatherEach(Ctx,[TAG=PATTERN|NEWATTRIBS],NOPATTERNS,Results),!,
  668   prolog_must(dumpListHere(Ctx,Results)))),!.
  669
  670load_aiml_cate_element(Ctx,ATTRIBS,element(Tag,ALIST,INNER_XML)):-loader_verb(Ctx,ATTRIBS,LoaderVerbs),
  671    load_aiml_cate_element2(Ctx,LoaderVerbs,ATTRIBS,element(Tag,ALIST,INNER_XML)).
  674load_aiml_cate_element2(Ctx,LoaderVerbs,ATTRIBS,element(Tag,ALIST,INNER_XML)):- fail, %%TODO: unfail this
  675   immediateCall(Ctx,load_aiml_cate_element_now(LoaderVerbs,ATTRIBS,element(Tag,ALIST,INNER_XML))),!.
  678load_aiml_cate_element2(Ctx,LoaderVerbs,ATTRIBS,element(Tag,ALIST,INNER_XML)):- %trace,
  679   prolog_must(pushCateElement(Ctx,[withCategory=LoaderVerbs|ATTRIBS],element(Tag,[withCategory=LoaderVerbs|ALIST],INNER_XML))),!.
  680
  681load_aiml_cate_element_now(LoaderVerbs,ATTRIBS,element(Tag,ALIST,INNER_XML)):-
  682  currentContext(load_aiml_cate_element_now,Ctx),
  683   prolog_must(pushCateElement(Ctx,[withCategory=LoaderVerbs|ATTRIBS],element(Tag,ALIST,INNER_XML))).
  684
  685%catagory
  686pushCateElement(Ctx,ATTRIBS,element(catagory, A, B)):- !,pushCateElement(Ctx,ATTRIBS,element(category, A, B)),!.
  687
  688% <topic> has non<category>s
  689pushCateElement(Ctx,INATTRIBS,element(Tag,ATTRIBS,INNER_XML)):- member(Tag,[topic,flag]),member(element(INNER,_,_),INNER_XML),INNER \= category,!,
  690 prolog_must((
  691   unify_partition(element(category,_,_),INNER_XML,ALLCATEGORIES,NONCATE),
  692   %findall(element(category,ALIST,LIST),member(element(category,ALIST,LIST),INNER_XML),ALLCATEGORIES),
  693   %takeout(element(category,_,_),INNER_XML,NONCATE),
  694   appendAttributes(Ctx,ATTRIBS,INATTRIBS,OUTATTRIBS),
  695   maplist_safe(each_category(Ctx,OUTATTRIBS,NONCATE),ALLCATEGORIES))).
  696
  697% flag/topic
  698pushCateElement(Ctx,INATTRIBS,element(Tag,ALIST,INNER_XML)):- member(Tag,[topic,flag]),!,
  699  prolog_must((
  700  replaceAttribute(Ctx,name,Tag,ALIST,ATTRIBS),
  701  appendAttributes(Ctx,ATTRIBS,INATTRIBS,OUTATTRIBS),
  702  withAttributes(Ctx,OUTATTRIBS,
  703     maplist_safe(pushCateElement(Ctx,OUTATTRIBS),INNER_XML)))).
  704
  705% remove <patterns>s from <category>s
  706pushCateElement(Ctx,INATTRIBS,element(Tag,ATTRIBS,INNER_XML)):- member(Tag,[outerctx,category]),!,
  707 prolog_must((
  708   member(element(pattern,_,_),INNER_XML),
  709   unify_partition(element(pattern,_,_),INNER_XML,ALLPATTERNS,NOPATTERNS),
  710   %findall(element(pattern,ALIST,LIST),member(element(pattern,ALIST,LIST),INNER_XML),ALLPATTERNS),
  711   %takeout(element(pattern,_,_),INNER_XML,NOPATTERNS),
  712   appendAttributes(Ctx,ATTRIBS,INATTRIBS,OUTATTRIBS),
  713   maplist_safe(each_pattern(Ctx,OUTATTRIBS,NOPATTERNS),ALLPATTERNS))),!.
  714
  715% error
  716pushCateElement(Ctx,ATTRIBS,M):-debugFmt('FAILURE'(pushCateElement(Ctx,ATTRIBS,M))),atrace.
  717
  718unify_partition(Mask, List, Included, Excluded):- my_partition(\=(Mask), List, Excluded , Included),!.
  719%%unify_partition(Mask, +List, ?Included, ?Excluded)
  720
  721:- meta_predicate(my_partition(1,+,-,-)).
  722my_partition(Pred, List, Included, Excluded) :-
  723    my_partition_(List, Pred, Included, Excluded).
  724my_partition_([], _, [], []).
  725my_partition_([H|T], Pred, Incl, Excl) :-
  726    (   call(Pred, H)
  727    ->  Incl=[H|I],
  728        my_partition_(T, Pred, I, Excl)
  729    ;   Excl=[H|E],
  730        my_partition_(T, Pred, Incl, E)
  731    ).
  732
  733
  734
  735each_pattern(Ctx,ATTRIBS,TAGS,element(TAG,ALIST,PATTERN)):- innerTagLikeThat(That), member(element(That,WA,WP), PATTERN),!,
  736   prolog_must((
  737   takeout(element(That,WA,WP),PATTERN,NOPATTERNS),
  738   each_pattern(Ctx,ATTRIBS,[element(That,WA,WP)|TAGS],element(TAG,ALIST,NOPATTERNS)))),!.
  739
  740each_pattern(Ctx,ATTRIBS,NOPATTERNS,element(TAG,ALIST,PATTERNA)):-
  741  prolog_must((
  742   convert_text(PATTERNA,PATTERN),
  743   replaceAttribute(Ctx,name,TAG,ALIST,PATTRIBS),
  744   appendAttributes(Ctx,PATTRIBS,ATTRIBS,NEWATTRIBS),
  745   gatherEach(Ctx,[TAG=PATTERN|NEWATTRIBS],NOPATTERNS,Results),
  746   prolog_must(dumpListHere(Ctx,Results)))),!.
  747
  748dumpListHere(Ctx,DumpListHere):-
  749   prolog_must((
  750    %%debugFmt(DumpListHere),
  751    loader_verb(Ctx,DumpListHere,Verbs),
  752    prolog_must(nonvar(Verbs)),
  753    %%%current_value(Ctx,withCategory,Verbs),
  754    assertCate(Ctx,DumpListHere,Verbs))).
  755
  756loader_verb(Ctx,DumpListHere,Verbs):-debugOnError(peekNameValue(Ctx,DumpListHere,withCategory,Verbs,'$failure')),!.
  757loader_verb(_Ctx,DumpListHere,Verbs):-lastMember(withCategory=Verbs,DumpListHere),nonvar(Verbs),!.
  758loader_verb(Ctx,DumpListHere,Verbs):-prolog_must((peekNameValue(Ctx,DumpListHere,withCategory,Verbs,'$first'(['$current_value','$value'([assert_cate_in_load])])))),prolog_must(isValid(Verbs)).
  759loader_verb(Ctx,DumpListHere,Verbs):-atrace,prolog_must((peekNameValue(Ctx,DumpListHere,withCategory,Verbs,'$first'(['$current_value','$value'([assert_cate_in_load])])))),!.
  760
  761%%dumpListHere([]):-debugFmt(dumpListHere).
  762%%dumpListHere([R|Results]):-debugFmt(R),dumpListHere(Results),!.
  763
  764gatherEach(Ctx,NEWATTRIBS,NOPATTERNS,RESULTS):-
  765   gatherEach0(Ctx,NEWATTRIBS,NOPATTERNS,RESULTS),
  766   nop(debugFmt(gatherEach0(Ctx,NEWATTRIBS,NOPATTERNS,RESULTS))),!.
  767
  768
  769removeAlwaysFromTag(that,pattern).
  770
  771gatherEach0(_Ctx,NEWATTRIBS,[],NEWATTRIBS):-!.
  772
  773gatherEach0(Ctx,NEWATTRIBS,[element(TAG,ALIST,PATTERN)|NOPATTERNS],RESULTS):-  
  774   removeAlwaysFromTag(That,TAG),
  775      innerTagLikeThat(That), member(element(That,WA,WP), PATTERN),!,
  776      takeout(element(That,WA,WP),PATTERN,NOTHAT),!,
  777      prolog_must(removeAlwaysFromTag(TAG,That)),
  778      gatherEach0(Ctx,NEWATTRIBS,[element(That,WA,WP),element(TAG,ALIST,NOTHAT)|NOPATTERNS],RESULTS),!.
  779
  780gatherEach0(Ctx,NEWATTRIBS,[element(TAG,ALIST,PATTERN_IN)|NOPATTERNS],[TAG=PATTERN_OUT|Result]):-
  781      transformTagData(Ctx,TAG,'$current_value',PATTERN_IN,PATTERN_OUT),!,
  782      gatherEach0(Ctx,NEWATTRIBS,NOPATTERNS,ResultM),!,
  783      appendAttributes(Ctx,ALIST,ResultM,Result),!.
  784
  785
  786each_template(Ctx,M):-debugFmt('FAILURE'(each_template(Ctx,M))),atrace.
  787each_that(Ctx,M):-debugFmt('FAILURE'(each_that(Ctx,M))),atrace