35
36:- module(cp_simple_search,
37 [ simple_search_form//0,
38 simple_search_form//1, 39 search_filter/2
40 ]). 41:- use_module(library(http/http_json)). 42:- use_module(library(http/http_parameters)). 43:- use_module(library(http/http_path)). 44:- use_module(library(http/http_dispatch)). 45:- use_module(library(http/http_wrapper)). 46:- use_module(library(http/html_write)). 47:- use_module(library(http/html_head)). 48
49:- use_module(library(semweb/rdf_db)). 50:- use_module(library(semweb/rdfs)). 51:- use_module(library(semweb/rdf_label)). 52
53:- use_module(library(option)). 54:- use_module(components(basics)). 55
56
57:- http_handler(api(ac_find_literal), ac_find_literal, []).
88simple_search_form -->
89 simple_search_form([]).
90
91simple_search_form(Options) -->
92 { option(label(Label), Options, 'Search'),
93 option(submit_handler(Search), Options, search)
94 },
95 html(form([ id(search_form),
96 action(location_by_id(Search))
97 ],
98 [ div([ \search_box([ name(q) | Options ]),
99 \filter(Options),
100 \select_handler(Options),
101 input([ type(submit),
102 value(Label)
103 ])
104 ])
105 ])).
106
107filter(Options) -->
108 { option(filter(Filter), Options),
109 !,
110 term_to_atom(Filter, FilterAtom)
111 },
112 hidden(filter, FilterAtom).
113filter(_) --> [].
114
115select_handler(Options) -->
116 { option(select_handler(Handler), Options) },
117 !,
118 hidden(handler, Handler).
119select_handler(_) --> [].
120
121
122max_results_displayed(100).
123
124search_box(Options) -->
125 { max_results_displayed(Max)
126 },
127 autocomplete(ac_find_literal,
128 [ query_delay(0.2),
129 auto_highlight(false),
130 max_results_displayed(Max),
131 width('30ex')
132 | Options
133 ]).
148autocomplete(Handler, Options) -->
149 { option(id(ID), Options, ac_find_literal),
150 atom_concat(ID, '_complete', CompleteID),
151 atom_concat(ID, '_input', InputID),
152 atom_concat(ID, '_container', ContainerID),
153 select_option(width(Width), Options, Options1, '25em'),
154 select_option(name(Name), Options1, Options2, predicate),
155 select_option(value(PValue), Options2, Options3, ''),
156 expand_value(PValue, Value)
157 },
158 html([ \html_requires(yui('autocomplete/autocomplete.js')),
159 \html_requires(yui('autocomplete/assets/skins/sam/autocomplete.css')),
160 div([ id(CompleteID),
161 class(ac_input)
162 ],
163 [ input([ id(InputID),
164 name(Name),
165 value(Value),
166 type(text)
167 ]),
168 div(id(ContainerID), [])
169 ]),
170 style(type('text/css'),
171 [ '#', CompleteID, '\n',
172 '{ width:~w; padding-bottom:0em; display:inline-block; vertical-align:top}'-[Width]
173 ]),
174 \autocomplete_script(Handler, InputID, ContainerID, Options3)
175 ]).
182expand_value(p(Name), Value) :-
183 !,
184 ( http_current_request(Request),
185 memberchk(search(Search), Request),
186 memberchk(Name=PValue, Search)
187 -> Value = PValue
188 ; Value = ''
189 ).
190expand_value(Value, Value).
191
192
193highlight -->
194 html(script(type('text/javascript'),
195\[
196 'function highlighMatches(str, query, cls)\n',
197 '{ var pat = new RegExp(query, "gi");
198 var sa = str.split(pat);
199 var ma = str.match(pat);
200 var i;
201 var out = sa[0];\n',
202
203 ' if ( !ma )
204 { return str;
205 }\n',
206
207 ' for(i=0; i<ma.length; )
208 { out += "<span class=\'"+cls+"\'>"+ma[i++]+"</span>";
209 out += sa[i];
210 }\n',
211
212 'return out;
213 }\n'
214 ])).
215
216autocomplete_script(HandlerID, Input, Container, Options) -->
217 { http_link_to_id(HandlerID, [], Path),
218 option(filter(Filter), Options, true),
219 term_to_atom(Filter, FilterAtom),
220 uri_query_components(QS, [filter(FilterAtom)])
221 },
222 highlight,
223 html(script(type('text/javascript'), \[
224'{ \n',
225' var oDS = new YAHOO.util.XHRDataSource("~w");\n'-[Path],
226' oDS.responseType = YAHOO.util.XHRDataSource.TYPE_JSON;\n',
227' oDS.responseSchema = { resultsList:"results",
228\t\t\t fields:["label","count","href"]
229\t\t\t};\n',
230' oDS.maxCacheEntries = 5;\n',
231' var oAC = new YAHOO.widget.AutoComplete("~w", "~w", oDS);\n'-[Input, Container],
232' oAC.resultTypeList = false;\n',
233' oAC.formatResult = function(oResultData, sQuery, sResultMatch) {
234 var sLabel = highlighMatches(oResultData.label, sQuery, "acmatch");
235 if ( oResultData.count > 1 ) {
236 sLabel += " <span class=\\"account\\">("+oResultData.count+")</span>";
237 }
238 return sLabel;
239 };\n',
240' oAC.itemSelectEvent.subscribe(function(sType, aArgs) {
241 var oData = aArgs[2];
242 window.location.href = oData.href;
243 });\n',
244' oAC.generateRequest = function(sQuery) {
245 return "?~w&query=" + sQuery ;
246 };\n'-[QS],
247 \ac_options(Options),
248'}\n'
249 ])).
250ac_options([]) -->
251 [].
252ac_options([H|T]) -->
253 ac_option(H),
254 ac_options(T).
255
256ac_option(query_delay(Time)) -->
257 !,
258 html([ ' oAC.queryDelay = ~w;\n'-[Time] ]).
259ac_option(auto_highlight(Bool)) -->
260 !,
261 html([ ' oAC.autoHighlight = ~w;\n'-[Bool] ]).
262ac_option(max_results_displayed(Max)) -->
263 !,
264 html([ ' oAC.maxResultsDisplayed = ~w;\n'-[Max] ]).
265ac_option(_) --> [].
273ac_find_literal(Request) :-
274 max_results_displayed(DefMax),
275 http_parameters(Request,
276 [ query(Query,
277 [ description('Prefix for literals to find')
278 ]),
279 filter(FilterAtom,
280 [ optional(true),
281 description('Filter on raw matches (a Prolog term)')
282 ]),
283 handler(Handler,
284 [ default(list_triples_with_literal),
285 description('Callback handler on selection')
286 ]),
287 maxResultsDisplayed(Max,
288 [ integer, default(DefMax),
289 description('Maximum number of results displayed')
290 ])
291 ]),
292 ( var(FilterAtom)
293 -> Filter = true
294 ; atom_to_term(FilterAtom, Filter0, []),
295 rdf_global_term(Filter0, Filter)
296 ),
297 autocompletions(Query, Filter, Handler, Max, Count, Completions),
298 reply_json(json([ query = json([ count=Count
299 ]),
300 results = Completions
301 ])).
302
303autocompletions(Query, Filter, Handler, Max, Count, Completions) :-
304 autocompletions(prefix(label), Query, Filter,
305 Handler, Max, BNC, ByName),
306 ( BNC > Max
307 -> Completions = ByName,
308 Count = BNC
309 ; TMax is Max-BNC,
310 autocompletions(prefix(other), Query, Filter,
311 Handler, TMax, BTC, ByToken),
312 append(ByName, ByToken, Completions),
313 Count is BNC+BTC
314 ).
315
316autocompletions(How, Query, Filter, Handler, Max, Count, Completions) :-
317 ac_objects(How, Query, Filter, Completions0),
318 length(Completions0, Count),
319 first_n(Max, Completions0, Completions1),
320 maplist(obj_result(Handler), Completions1, Completions).
321
322obj_result(Handler, Text-Count,
323 json([ label=Text,
324 count=Count,
325 href=Href
326 ])) :-
327 object_href(Handler, Text, Href).
328
329object_href(Handler, Text, Link) :-
330 !,
331 http_link_to_id(Handler, [ q=Text ], Link).
332
333first_n(0, _, []) :- !.
334first_n(_, [], []) :- !.
335first_n(N, [H|T0], [H|T]) :-
336 N2 is N - 1,
337 first_n(N2, T0, T).
344ac_objects(How, Query, Filter, Objects) :-
345 findall(Pair, ac_object(How, Query, Filter, Pair), Pairs),
346 keysort(Pairs, KSorted),
347 group_pairs_by_key(KSorted, Grouped),
348 maplist(hit_count, Grouped, Objects).
349
350hit_count(Text-Resources, Text-Count) :-
351 length(Resources, Count).
356ac_object(prefix(label), Query, Filter, Text-Resource) :-
357 ac_candidate(Query, Filter, Resource, P, Literal),
358 ( label_property(LP),
359 rdfs_subproperty_of(P, LP)
360 -> literal_text(Literal, Text)
361 ).
362ac_object(prefix(other), Query, Filter, Text-Resource) :-
363 ac_candidate(Query, Filter, Resource, P, Literal),
364 ( label_property(LP),
365 rdfs_subproperty_of(P, LP)
366 -> fail
367 ; literal_text(Literal, Text)
368 ).
369
370ac_candidate(Query, Filter, R, P, literal(Literal)) :-
371 ( sub_term(graph(Graph), Filter)
372 -> rdf(R, P, literal(prefix(Query), Literal), Graph)
373 ; rdf(R, P, literal(prefix(Query), Literal))
374 ),
375 search_filter(Filter, R).
386search_filter(true, _) :- !.
387search_filter(graph(_), _) :- !. 388search_filter(Filter, _) :-
389 domain_error(filter, Filter)
Simple literal search
*/