1:- module(ajaxify, [ajaxify//2,
2 ajaxify_broadcast//3,
3 ajaxify_contents//2]).
8:- use_module(library(http/html_write)). 9:- use_module(library(http/html_head)). 10:- use_module(weblog(resources/resources)). 11:- use_module(library(http/http_dispatch)). 12:- use_module(library(http/http_wrapper)). 13:- use_module(library(http/js_write)). 14:- use_module(library(http/http_parameters)). 15 16 17:- html_meta ajaxify(1, html, ?, ?).
arguments for Generator
id(ID)
required - binds this handler to a specific ID.
this will also be the id of the div
note that this is a global namespace, so
mypage_mything is recommended
listen_to(Name)
listen to all, ID, and anything
that matches Name
timer(Speed)
call this ajaxify every Speed millisec
In the event of an error, the contents of #error will be appended with the error message
38ajaxify(Generator, HTML) --> 39 { 40 call(Generator, id(ID)), 41 ajax_path_name(Generator, AjaxPath), 42 ensure_ajax_handler_exists(Generator, AjaxPath, HTML) 43 }, 44 html(div(id(ID), [&(nbsp)])), 45 html_requires(ajaxify_base), 46 register_listener(load, Generator), 47 register_listener(all, Generator), 48 generator_register(Generator), 49 timer_register(Generator), 50 register_listener(ID, Generator). 51 52:- html_meta ajaxify_broadcast(+, html). 53 54 55ajaxify_broadcast(Name, return, HTML) --> 56 { 57 outer_id(HTML, ID, OHTML), 58 ground(ID), % make sure we really have it 59 atomic_concat('#', ID, PID) 60 }, 61 html(OHTML), 62 html(\js_script( 63 {|javascript(PID, Name)|| $(PID).keyup(event, function() { if ( event.which == 13 ) { ajaxify.talk(Name); event.preventDefault(); } }); |} )).
77outer_id(input(A, C), ID, input(A, C)) :- 78 outer_id([input(A, C)], ID, [input(A, C)]). 79outer_id([input(A, C) | T], ID, [input(A, C) | T]) :- 80 is_list(A), 81 member(id(ID), A). 82outer_id([input(A, C) | T], ID, [input(A, C) | T]) :- 83 is_list(A), 84 member(id=ID , A). 85outer_id([input(A, C) | T], ID, [input([id(ID) | A], C) | T]) :- 86 is_list(A), 87 \+ memberchk(id(_) , A), 88 \+ memberchk(id=_ , A), 89 ground(ID). 90outer_id([input(A, C) | T], ID, [input([id(ID) , A], C) | T]) :- 91 \+ is_list(A), 92 A \= id(_), 93 ground(ID). 94 95register_listener(Name, Generator) --> 96 { 97 call(Generator, id(ID)), 98 ajax_path_name(Generator, AjaxPath) 99 }, 100 html(\js_script( 101 {|javascript(Name, ID, AjaxPath)|| 102 ajaxify.listen(Name, ID, AjaxPath); 103 |} 104 )). 105 106generator_register(Generator) --> 107 { 108 findall(X, call(Generator, listen_to(X)), List) 109 }, 110 generator_register_(Generator, List). 111 112generator_register_(_, []) --> []. 113generator_register_(Generator, [H|T]) --> 114 register_listener(H, Generator), 115 generator_register_(T, Generator). 116 117timer_register(Generator) --> 118 { 119 call(Generator, timer(Speed)), 120 !, 121 ( Speed > 99 ; 122 throw(error(bad_idea(too_fast_ajax), 123 context(ajaxify/4, 'Timer ajax faster than 100msec')))), 124 call(Generator, id(ID)), 125 ajax_path_name(Generator, AjaxPath) 126 }, 127 html(\js_script( 128 {|javascript(Speed, ID, AjaxPath)|| 129 ajaxify.tick(Speed, ID, AjaxPath); 130 |} 131 )). 132timer_register(_) -->[]. 133 134 135ajax_path_name(Generator, AjaxPath) :- 136 call(Generator, id(ID)), 137 http_current_request(Request), 138 member(path(Path), Request), 139 atomic_list_concat([Path, '/ajax/', ID], AjaxPath). 140 141:- html_meta ensure_ajax_handler_exists(1, +, html). 142 143ensure_ajax_handler_exists(_, AjaxPath, _) :- 144 http_dispatch:handler(AjaxPath, _, _, _),!. 145ensure_ajax_handler_exists(Generator, AjaxPath, HTML) :- 146 http_handler(AjaxPath, ajax_wrapper(Generator, HTML), []). 147 148:- html_meta ajax_wrapper(1, html, +). 149 150ajax_wrapper(Generator, HTML, _Request) :- 151 format('Content-type: text/html~n'), 152 call(Generator, id(ID)), 153 format('X-Clear: 1~n'), 154 format('X-Id: ~w~n~n', [ID]), 155 phrase(html(HTML), Tokens), 156 print_html(Tokens). 157 158%% ajaxify_contents(+Message, +Contents, ?A, ?B) is det 159% 160% add contents of an element to ajaxify 161% calls 162% 163% @arg Message when you send this message 164% @arg Contents add this element to the query string, with id the 165% element name 166% 167ajaxify_contents(Message, Contents) --> 168 html(\js_script( 169 {|javascript(Message, Contents)
Turn any html generation into ajax
*/