30
31:- module(app_isearch,
32 [ isearch_field//2, 33 isearch_page/2 34 ]). 35:- use_module(library(http/http_dispatch)). 36:- use_module(library(http/http_parameters)). 37:- use_module(library(http/html_write)). 38:- use_module(library(http/http_wrapper)). 39:- use_module(library(http/http_host)). 40:- use_module(library(http/http_path)). 41:- use_module(library(http/html_head)). 42:- use_module(library(http/json)). 43:- use_module(library(http/json_convert)). 44:- use_module(library(semweb/rdf_db)). 45:- use_module(library(semweb/rdfs)). 46:- use_module(library(semweb/rdf_litindex)). 47:- use_module(library(semweb/rdf_label)). 48:- use_module(library(semweb/rdf_description)). 49:- use_module(library(semweb/rdf_abstract)). 50:- use_module(library(settings)). 51:- use_module(library(apply)). 52:- use_module(library(http/cp_jquery)). 53
54:- use_module(library(search/facet)). 55:- use_module(components(label)). 56
57:- multifile
58 cliopatria:format_search_result//3, 59 cliopatria:search_pattern/3. 60
61:- rdf_meta
62 isearch_field(+,r,?,?),
63 cliopatria:facet_exclude_property(r). 64
72
73:- setting(search:target_class, uri, rdfs:'Resource',
74 'Default search target'). 75
77:- setting(search:show_disambiguations, boolean, true,
78 'Show terms matching the query as disambiguation suggestions'). 79:- setting(search:show_suggestions, boolean, false,
80 'Show terms as suggestions for further queries'). 81:- setting(search:show_relations, boolean, true,
82 'Show relations by which search results are found'). 83:- setting(search:show_facets, boolean, true,
84 'Show faceted filters in the search result page'). 85
87:- setting(search:result_limit, integer, 10,
88 'Maximum number of results shown'). 89:- setting(search:term_limit, integer, 5,
90 'Maximum number of items shown in the term disambiguation list'). 91:- setting(search:relation_limit, integer, 5,
92 'Maximum number of relations shown'). 93
95:- setting(search:pattern_literal, boolean, true,
96 'Find results by a direct literal property'). 97:- setting(search:pattern_resource, boolean, true,
98 'Find results by an object property from which the resource has a matching label'). 99
100:- http_handler(root(isearch), isearch_page([]), [id(isearch)]).
114isearch_page(Options, Request) :-
115 ( debugging(profile(isearch))
116 -> profile(isearch_page2(Options, Request))
117 ; isearch_page2(Options, Request)
118 ).
119
120isearch_page2(Options, Request) :-
121 setting(search:target_class, DefTargetClass),
122 setting(search:result_limit, DefaultLimit),
123
124 option(target_class(TargetClass), Options, DefTargetClass),
125
126 http_parameters(Request,
127 [ q(Keyword,
128 [ optional(true),
129 description('Search query')
130 ]),
131 class(Class,
132 [ default(TargetClass),
133 description('Target Class')
134 ]),
135 term(Terms,
136 [ zero_or_more,
137 description('Disambiguation term')
138 ]),
139 relation(Relations,
140 [ zero_or_more,
141 description('Limit results by specific relation')
142 ]),
143 filter(Filter,
144 [ default([]), json,
145 description('Filters on the result set')
146 ]),
147 offset(Offset,
148 [ default(0), integer,
149 description('Offset of the result list')
150 ]),
151 limit(Limit,
152 [ default(DefaultLimit), integer,
153 description('Limit on the number of results')
154 ])
155 ]),
156 ( var(Keyword)
157 -> html_start_page(Class)
158 ; QueryParams = query(Keyword,
159 Class, Terms, Relations, Filter,
160 Offset, Limit),
161
162 make_query(Keyword, Query, Options),
163
164 165 keyword_search_graph(Query, instance_of_class(Class),
166 AllResults, Graph),
167
168 169 restrict_by_terms(Terms, AllResults, Graph, ResultsWithTerm),
170
171 172 restrict_by_relations(Relations, ResultsWithTerm, Graph,
173 ResultsWithRelation),
174
175 176 filter_results_by_facet(ResultsWithRelation, Filter, Results),
177 compute_facets(Results, ResultsWithRelation, Filter, Facets),
178
179 length(ResultsWithRelation, NumberOfRelationResults),
180 length(Results, NumberOfResults),
181 list_offset(Results, Offset, OffsetResults),
182 list_limit(OffsetResults, Limit, LimitedResults, _),
183
184 graph_terms(Graph, MatchingTerms),
185 result_relations(ResultsWithTerm, Graph, MatchingRelations),
186 related_terms(Terms, Class, RelatedTerms),
187
188 html_result_page(QueryParams,
189 result(LimitedResults, NumberOfResults, NumberOfRelationResults),
190 Graph,
191 MatchingTerms, RelatedTerms,
192 MatchingRelations, Facets, Options)
193 ).
194
195compute_facets(Results, AllResults, Filter, Facets) :-
196 facets(Results, AllResults, Filter, ActiveFacets0, InactiveFacets0),
197 maplist(cleanup_facet, ActiveFacets0, ActiveFacets1),
198 maplist(cleanup_facet, InactiveFacets0, InactiveFacets1),
199 length(AllResults, Total),
200 map_list_to_pairs(facet_quality(Total), InactiveFacets1, Keyed),
201 keysort(Keyed, Sorted),
202 pairs_values(Sorted, InactiveFacets),
203 append(ActiveFacets1, InactiveFacets, Facets).
204
205cleanup_facet(Facet0, Facet) :-
206 facet_merge_sameas(Facet0, Facet1),
207 facet_join_single(Facet1, Facet).
215facet_quality(Total, Facet, Quality) :-
216 facet_balance(Facet, Balance),
217 facet_object_cardinality(Facet, Card),
218 facet_frequency(Facet, Total, Freq),
219 facet_weight(Facet, Weight),
220 Quality0 is Balance*Card*Freq*Weight,
221 ( debugging(facet)
222 -> Facet = facet(P, _, _),
223 rdf_display_label(P, Label),
224 debug(facet, '~p: ~w = ~w*~w*~w*~w~n',
225 [Label, Quality0, Balance, Card, Freq, Weight])
226 ; true
227 ),
228 Quality is 1-Quality0.
229
230
232
233:- json_object
234 prop(prop:atom, values:_),
235 literal(literal:atom),
236 literal(literal:_),
237 type(type:atom, text:_),
238 lang(lang:atom, text:atom).
244http:convert_parameter(json, Atom, Term) :-
245 atom_json_term(Atom, JSON, []),
246 json_to_prolog(JSON, Term).
252make_query(Keyword, Query, Options) :-
253 option(query_type(QueryType), Options, case),
254 make_query_type(QueryType, Keyword, Query).
255
256make_query_type(literal, Keyword, literal(Keyword)) :- !.
257make_query_type(QueryType, Keyword, Query) :-
258 tokenize_atom(Keyword, Words),
259 tokens_query(Words, QueryType, Query).
260
261tokens_query([Word], QueryType, Query) :- !,
262 token_query(Word, QueryType, Query).
263tokens_query(['"',Word,'"'|T], QueryType, Query) :- !,
264 ( T == []
265 -> Query = Word
266 ; Query = and(T, Q2),
267 tokens_query(T, QueryType, Q2)
268 ).
269tokens_query([H|T], QueryType, and(Q1,Q2)) :-
270 token_query(H, QueryType, Q1),
271 tokens_query(T, QueryType, Q2).
272
273token_query(Word, QueryType, Query) :-
274 Query =.. [QueryType, Word].
286keyword_search_graph(Query, Filter, Targets, Graph) :-
287 ( Query = literal(Text)
288 -> Literals = [Text]
289 ; rdf_find_literals(Query, Literals)
290 ),
291 findall(Target-G, keyword_graph(Literals, Filter, Target, G), TGPairs),
292 pairs_keys_values(TGPairs, Targets0, GraphList),
293 sort(Targets0, Targets1),
294 append(GraphList, Graph0),
295 sort(Graph0, Graph1),
296 merge_sameas_graph(Graph1, Graph2, [sameas_mapped(Map)]),
297 sort(Graph2, Graph),
298 maplist(map_over_assoc(Map), Targets1, Targets2),
299 sort(Targets2, Targets).
300
301map_over_assoc(Assoc, In, Out) :-
302 get_assoc(In, Assoc, Out), !.
303map_over_assoc(_, In, In).
304
305keyword_graph(Literals, Filter, Target, Graph) :-
306 member(L, Literals),
307 search_pattern(L, Target, Graph),
308 ( Filter = _:true
309 -> true
310 ; call(Filter, Target)
311 ).
319search_pattern(Label, Target,
320 [ rdf(TN, PN, literal(Value))
321 | More
322 ]) :-
323 setting(search:pattern_literal, true),
324 rdf(TN, PN, literal(exact(Label), Value)),
325 ( (rdf_is_bnode(TN)
326 ;rdf_equal(rdf:value, PN)
327 ),
328 rdf_has(Target, P, TN)
329 *-> More = [ rdf(Target, P, TN) ]
330 ; TN = Target,
331 More = []
332 ).
333search_pattern(Label, Target,
334 [ rdf(TN, PN, Term),
335 rdf(Term, LP, literal(Value))
336 | More
337 ]) :-
338 setting(search:pattern_resource, true),
339 rdf_has(Term, rdfs:label, literal(exact(Label), Value), LP),
340 rdf(TN, PN, Term),
341 ( rdf_is_bnode(TN),
342 rdf_has(Target, P, TN)
343 *-> More = [ rdf(Target, P, TN) ]
344 ; TN = Target,
345 More = []
346 ).
347search_pattern(Label, Target, Graph) :-
348 cliopatria:search_pattern(Label, Target, Graph).
358graph_terms(Graph, TermSet) :-
359 graph_terms_(Graph, Terms),
360 sort(Terms, TermSet).
361
362graph_terms_([], []).
363graph_terms_([rdf(S,P,L)|T], Terms) :-
364 ( rdf_is_literal(L),
365 rdfs_subproperty_of(P, rdfs:label),
366 \+ rdf_is_bnode(S)
367 -> Terms = [S|More],
368 graph_terms_(T, More)
369 ; graph_terms_(T, Terms)
370 ).
377restrict_by_terms([], Results, _, Results) :- !.
378restrict_by_terms(Terms, Results, Graph, TermResults) :-
379 sort(Terms, TermSet),
380 result_terms(Results, Graph, Result_Terms),
381 matches_term(Result_Terms, TermSet, TermResults).
382
383matches_term([], _, []).
384matches_term([R-TL|T0], Terms, Results) :-
385 ( ord_intersect(Terms, TL)
386 -> Results = [R|More],
387 matches_term(T0, Terms, More)
388 ; matches_term(T0, Terms, Results)
389 ).
390
391result_terms(Results, Graph, Result_Terms) :-
392 result_justifications(Results, Graph, TermJusts),
393 maplist(value_graph_terms, TermJusts, Result_Terms).
394
395value_graph_terms(R-G, R-T) :-
396 graph_terms(G, T).
403result_relations(Results, Graph, Relations) :-
404 map_list_to_pairs(=, Results, Pairs),
405 list_to_assoc(Pairs, ResultAssoc),
406 empty_assoc(R0),
407 result_relations(Graph, ResultAssoc, R0, R),
408 assoc_to_keys(R, Relations).
409
410result_relations([], _, R, R).
411result_relations([rdf(S,P,_)|T], Results, R0, R) :-
412 ( get_assoc(P, R0, _)
413 -> result_relations(T, Results, R0, R)
414 ; get_assoc(S, Results, _)
415 -> put_assoc(P, R0, true, R1),
416 result_relations(T, Results, R1, R)
417 ; result_relations(T, Results, R0, R)
418 ).
430restrict_by_relations([], AllResults, _, AllResults) :- !.
431restrict_by_relations(_, [], _, []) :- !.
432restrict_by_relations(Relations, [R0|R], [T0|T], Results) :-
433 cmp_subject(Diff, R0, T0),
434 rel_restrict(Diff, R0, R, T0, T, Relations, Results).
435
436rel_restrict(=, R0, R, T0, T, Relations, Result) :-
437 ( rel_in(T0, Relations)
438 -> Result = [R0|More],
439 restrict_by_relations(Relations, R, T, More)
440 ; T = [T1|TT]
441 -> cmp_subject(Diff, R0, T1),
442 rel_restrict(Diff, R0, R, T1, TT, Relations, Result)
443 ; Result = []
444 ).
445rel_restrict(>, R0, R, _, Graph, Relations, Result) :-
446 ( Graph = [T0|T]
447 -> cmp_subject(Diff, R0, T0),
448 rel_restrict(Diff, R0, R, T0, T, Relations, Result)
449 ; Result = []
450 ).
451rel_restrict(<, _, AllResults, T0, T, Relations, Result) :-
452 ( AllResults = [R0|R]
453 -> cmp_subject(Diff, R0, T0),
454 rel_restrict(Diff, R0, R, T0, T, Relations, Result)
455 ; Result = []
456 ).
457
458cmp_subject(Diff, R, rdf(S,_,_)) :-
459 compare(Diff, R, S).
460
461rel_in(rdf(_,P,_), Relations) :-
462 memberchk(P, Relations).
476result_justifications(Results, Graph, Pairs) :-
477 graph_subject_assoc(Graph, Assoc),
478 maplist(result_justification(Assoc), Results, Pairs).
479
480result_justification(SubjectAssoc, Result, Result-Graph) :-
481 result_justification(Result, SubjectAssoc, [], _, Graph, []).
482
483result_justification(Result, SubjectAssoc, S0, S, Graph, GT) :-
484 ( memberchk(Result, S0)
485 -> Graph = GT,
486 S = S0
487 ; get_assoc(Result, SubjectAssoc, POList)
488 -> po_result_just(POList, Result, SubjectAssoc,
489 [Result|S0], S, Graph, GT)
490 ; Graph = GT,
491 S = S0
492 ).
493
494po_result_just([], _, _, S, S, Graph, Graph).
495po_result_just([P-O|T], R, SubjectAssoc, S0, S, [rdf(R,P,O)|Graph], GT) :-
496 result_justification(O, SubjectAssoc, S0, S1, Graph, GT1),
497 po_result_just(T, R, SubjectAssoc, S1, S, GT1, GT).
498
499graph_subject_assoc(Graph, Assoc) :-
500 rdf_s_po_pairs(Graph, Pairs),
501 list_to_assoc(Pairs, Assoc).
510rdf_s_po_pairs([], []).
511rdf_s_po_pairs([rdf(S,P,O)|T], [S-[P-O|M]|Graph]) :-
512 same_s(S, T, M, T1),
513 rdf_s_po_pairs(T1, Graph).
514
515same_s(S, [rdf(S,P,O)|T], [P-O|M], Rest) :- !,
516 same_s(S, T, M, Rest).
517same_s(_, Graph, [], Graph).
525related_terms([], _, []) :- !.
526related_terms(_, _, []) :-
527 setting(search:show_suggestions, false),
528 !.
529related_terms(Terms, Class, RelatedTerms) :-
530 findall(P-RT, ( member(Term, Terms),
531 related_term(Term, Class, RT, P)
532 ),
533 RTs0),
534 sort(RTs0, RTs),
535 group_pairs_by_key(RTs, RelatedTerms).
536
537related_term(R, Class, Term, P) :-
538 related(R, Term, P),
539 atom(Term),
540 \+ equivalent_property(P),
541 has_target(Term, Class).
542
543has_target(Term, Class) :-
544 rdf(Target, _, Term),
545 instance_of_class(Class, Target).
546
547related(S, O, P) :-
548 rdf_eq(S, P0, V),
549 ( O = V,
550 P = P0
551 ; atom(V),
552 rdf_predicate_property(P0, rdf_object_branch_factor(BF)),
553 debug(related, '~w ~w', [P0, BF]),
554 BF < 10
555 -> rdf_eq(O, P0, V),
556 O \== S,
557 P = V
558 ).
559related(S, O, P) :-
560 rdf_eq(O, P, S),
561 rdf(P, owl:inverseOf, IP),
562 \+ rdf_eq(S, IP, O).
563
564rdf_eq(S, P, O) :-
565 rdf(S, P, O).
566
567:- rdf_meta
568 equivalent_property(r). 569
570equivalent_property(owl:sameAs).
571equivalent_property(skos:exactMatch).
578filter_results_by_facet(AllResults, [], AllResults) :- !.
579filter_results_by_facet(AllResults, Filter, Results) :-
580 facet_condition(Filter, AllResults, R, Goal),
581 findall(R, (member(R, AllResults), Goal), Results).
582
583
584
592html_start_page(Class) :-
593 reply_html_page(user(search),
594 title('Search'),
595 [ \html_requires(css('interactive_search.css')),
596 div([style('margin-top:10em')],
597 [ div([style('text-align:center')], \logo),
598 div([style('text-align:center;padding:0'), id(search)],
599 \isearch_field('', Class))])
600 ]).
609html_result_page(QueryObj, ResultObj, Graph, Terms, RelatedTerms, Relations, Facets, Options) :-
610 QueryObj = query(Keyword,
611 Class, SelectedTerms, SelectedRelations, Filter,
612 Offset, Limit),
613 ResultObj = result(Results, NumberOfResults, NumberOfRelationResults),
614 reply_html_page(user(isearch),
615 [ title(['Search results for ', Keyword])
616 ],
617 [ \html_requires(css('interactive_search.css')),
618 \html_requires(jquery),
619 \html_requires(js('json2.js')),
620 \html_header(Keyword, Class, Options),
621 div(id(main),
622 div(class('main-content'),
623 [ \html_term_list(Terms, RelatedTerms, SelectedTerms),
624 div(id(results),
625 [ div(class(header),
626 [ \html_filter_list(Filter),
627 \html_relation_list(Relations, SelectedRelations,
628 NumberOfRelationResults)
629 ]),
630 div(class(body),
631 ol(class('result-list'),
632 \html_result_list(Results, QueryObj, Graph))),
633 div(class(footer),
634 \html_paginator(NumberOfResults, Offset, Limit))
635 ]),
636 \html_facet_list(Facets)
637 ])),
638 script(type('text/javascript'),
639 [ \script_body_toggle,
640 \script_data(Keyword, Class, SelectedTerms, SelectedRelations, Filter),
641 \script_term_select(terms),
642 \script_relation_select(relations),
643 \script_facet_select(facets),
644 \script_suggestion_select(suggestions),
645 \script_filter_select(filters)
646 ])
647 ]).
648
(_Keyword, _Class, Options) -->
650 { option(header(false), Options) }, !.
651html_header(Keyword, Class, _Options) -->
652 html(div(id(header),
653 div(class('header-content'),
654 [ div(id(logo), \logo),
655 div(id(search),
656 \isearch_field(Keyword, Class))
657 ]))).
658
659html_term_list([], [], _) --> !,
660 html(div([id(left), class(column)],
661 div(class(body), ['']))).
662html_term_list(Terms, RelatedTerms, SelectedTerms) -->
663 html(div([id(left), class(column)],
664 [ div(class(toggle),
665 \toggle_link(ltoggle, lbody, '>', '>', '<')),
666 div([class(body), id(lbody)],
667 [ \html_term_list(Terms, SelectedTerms),
668 \html_related_term_list(RelatedTerms)
669 ])
670 ])).
671
672html_facet_list([]) --> !.
673html_facet_list(Facets) -->
674 html(div([id(right), class(column)],
675 [ div(class(toggle),
676 \toggle_link(rtoggle, rbody, '<', '<', '>')),
677 div([class(body), id(rbody)],
678 div(id(facets),
679 \html_facets(Facets, 0))
680 )
681 ])).
687logo -->
688 { http_location_by_id(isearch, Home)
689 },
690 html(a([class(isearch_logo), href(Home)], '')).
697isearch_field(Query, Class) -->
698 html(form([input([type(text), class(inp), name(q), value(Query)]),
699 input([type(hidden), name(class), value(Class)]),
700 input([type(submit), class(btn), value(search)])
701 ])).
707html_result_list([], _, _) --> !.
708html_result_list([R|Rs], Query, Graph) -->
709 html(li(class(r),
710 [ div(class('result-item'),
711 \result_item(R, Query, Graph)),
712 br(clear(all))
713 ])),
714 html_result_list(Rs, Query, Graph).
715
716
717result_item(R, Query, Graph) -->
718 cliopatria:format_search_result(R, Query, Graph), !.
719result_item(R, _Query, _Graph) -->
720 html([ div(class(thumbnail),
721 \result_image(R)),
722 div(class(text),
723 [ div(class(title), \rdf_link(R,
724 [ resource_format(label),
725 max_length(120)
726 ])),
727 div(class(subtitle), \result_subtitle(R)),
728 div(class(description), \result_description(R))
729 ])
730 ]).
731
732
733result_subtitle(R) -->
734 result_creator(R),
735 result_date(R).
736result_description(R) -->
737 { rdf_description(R, LitDesc),
738 literal_text(LitDesc, DescTxt),
739 truncate_atom(DescTxt, 200, Desc)
740 },
741 !,
742 html(Desc).
743result_description(_R) --> !.
744
745result_creator(R) -->
746 { rdf_has(R, dc:creator, C) }, !,
747 rdf_link(C).
748result_creator(_) --> [].
749
750result_date(R) -->
751 { rdf_has(R, dc:date, D), !,
752 literal_text(D, DateTxt)
753 },
754 html([' (', DateTxt, ')']).
755result_date(_) --> [].
756
757
758result_image(R) -->
759 { image_property(P),
760 rdf_has(Image, P, R),
761 ( image_suffix(Suffix)
762 -> true
763 ; Suffix = ''
764 )
765 },
766 !,
767 html(img(src(Image+Suffix), [])).
768result_image(_) --> !.
774html_paginator(Total, _Offset, Limit) -->
775 { Total < Limit },
776 !.
777html_paginator(Total, Offset, Limit) -->
778 { http_current_request(Request),
779 request_url_components(Request, URLComponents),
780 Pages is ceiling(Total/Limit),
781 ActivePage is floor(Offset/Limit),
782 ( ActivePage < 9
783 -> EndPage is min(10, Pages)
784 ; EndPage is min(10+ActivePage, Pages)
785 ),
786 StartPage is max(0, EndPage-20),
787 ( select(search(Search0), URLComponents, Cs)
788 -> delete(Search0, offset=_, Search),
789 parse_url(URL, [search(Search)|Cs])
790 ; parse_url(URL, URLComponents)
791 )
792 },
793 html(div(class(paginator),
794 [ \prev_page(ActivePage, Limit, URL),
795 \html_pages(StartPage, EndPage, Limit, URL, ActivePage),
796 \next_page(ActivePage, Pages, Limit, URL)
797 ])).
798
799prev_page(0, _, _) --> !.
800prev_page(Active, Limit, URL) -->
801 { Offset is (Active-1)*Limit,
802 First = 0
803 },
804 html([span(class(first), a(href(URL+'&offset='+First), '<<')),
805 span(class(prev), a(href(URL+'&offset='+Offset), '<'))]).
806
807next_page(_, 0, _, _) --> !.
808next_page(Active, Last, _, _) -->
809 { Active is Last-1 },
810 !.
811next_page(Active, Last, Limit, URL) -->
812 { Offset is (Active+1)*Limit,
813 LastOffset is (Last-1)*Limit
814 },
815 html([span(class(next), a(href(URL+'&offset='+Offset), '>')),
816 span(class(last), a(href(URL+'&offset='+LastOffset), '>>'))]).
817
818html_pages(N, N, _, _, _) --> !.
819html_pages(N, Pages, Limit, URL, ActivePage) -->
820 { N1 is N+1,
821 Offset is N*Limit,
822 ( N = ActivePage
823 -> Class = active
824 ; Class = ''
825 )
826 },
827 html(span(class(Class), a(href(URL+'&offset='+Offset), N1))),
828 html_pages(N1, Pages, Limit, URL, ActivePage).
834html_term_list([], _) --> !.
835html_term_list(Terms, Selected) -->
836 { setting(search:term_limit, Limit),
837 list_limit(Terms, Limit, TopN, Rest)
838 },
839 html(div(id(terms),
840 [ div(class(header), 'Did you mean?'),
841 div(class(items),
842 [ \resource_list(TopN, Selected),
843 \resource_rest_list(Rest, term, Selected)
844 ])
845 ])).
851html_relation_list([], _, NumberOfResults) --> !,
852 html(div(id(relations),
853 div(class('relations-header'),
854 [NumberOfResults, ' result found']))).
855html_relation_list(Relations, Selected, NumberOfResults) -->
856 { setting(search:relation_limit, Limit),
857 list_limit(Relations, Limit, TopN, Rest)
858 },
859 html(div(id(relations),
860 [ div(class('relations-header'),
861 [ NumberOfResults, ' result found by: ' ]),
862 div(class('relations-content'),
863 [ \resource_list(TopN, Selected),
864 \resource_rest_list(Rest, relation, Selected)
865 ])
866 ])).
872html_related_term_list(Pairs) -->
873 html(div(id('suggestions'),
874 \html_related_terms(Pairs, 0))).
875
876html_related_terms([], _) --> !.
877html_related_terms([P-Terms|T], N) -->
878 { N1 is N+1,
879 rdfs_label(P, Label),
880 list_limit(Terms, 3, TopN, Rest)
881 },
882 html(div(class(suggestion),
883 [ div(class(header), Label),
884 div([title(P), class(items)],
885 [ \resource_list(TopN, []),
886 \resource_rest_list(Rest, suggestions+N, [])
887 ])
888 ])),
889 html_related_terms(T, N1).
895html_facets([], _) --> !.
896html_facets([facet(P, ResultsByValue, Selected)|Fs], N) -->
897 { N1 is N+1,
898 pairs_sort_by_result_count(ResultsByValue, AllValues),
899 top_bottom(5, 5, AllValues, Values)
900 },
901 html(div(class(facet),
902 [ div(class(header), \rdf_link(P)),
903 div([title(P), class(items)],
904 \resource_list(Values, Selected))
905 ])),
906 html_facets(Fs, N1).
907
908top_bottom(MaxTop, MaxBottom, All, List) :-
909 length(All, Len),
910 ( Len =< MaxTop+MaxBottom
911 -> List = All
912 ; Skipped is Len-(MaxTop+MaxBottom),
913 top(MaxTop, All, Rest0, List, List1),
914 List1 = [Count-'__skipped'|List2],
915 skip(Skipped, 0, Count, Rest0, List2)
916 ).
917
918top(0, All, All, List, List) :- !.
919top(N, [H|T0], All, [H|T], List) :-
920 succ(N1, N),
921 top(N1, T0, All, T, List).
922
923skip(0, Count, Count, List, List).
924skip(N, C0, C, [C1-_|T], List) :-
925 C2 is C0+C1,
926 N2 is N-1,
927 skip(N2, C2, C, T, List).
928
929
930html_filter_list([]) --> !.
931html_filter_list(Filter) -->
932 html(div(id(filters),
933 \html_filter(Filter))).
934
935html_filter([]) --> !.
936html_filter([prop(P, Vs)|Ps]) -->
937 { rdfs_label(P, Label) },
938 html(div([title(P), class(filter)],
939 [ div(class(property), [Label, ': ']),
940 ul(class('resource-list'),
941 \property_values(Vs))
942 ])),
943 html_filter(Ps).
944
945property_values([]) --> !.
946property_values([V|Vs]) -->
947 { rdf_display_label(V, Label),
948 resource_attr(V, Attr),
949 http_absolute_location(icons('checkbox_selected.png'), Img, [])
950 },
951 html(li([title(Attr)],
952 div(class('value-inner'),
953 [ img([class(checkbox), src(Img)], []),
954 \resource_label(Label)
955 ]))),
956 property_values(Vs).
957
958remove_single_value_facet([], []) :- !.
959remove_single_value_facet([facet(_, [_], [])|Fs], Rest) :- !,
960 remove_single_value_facet(Fs, Rest).
961remove_single_value_facet([F|Fs], [F|Rest]) :-
962 remove_single_value_facet(Fs, Rest).
969resource_rest_list([], _, _) --> !.
970resource_rest_list(Rest, Id, Selected) -->
971 { ( member(S, Selected),
972 memberchk(_-S, Rest)
973 -> Display = block,
974 L1 = less, L2 = more
975 ; Display = none,
976 L1 = more, L2 = less
977 )
978 },
979 html([ul([id(Id+body),
980 class('resource-list toggle-body'),
981 style('display:'+Display)
982 ],
983 \resource_items(Rest, Selected)
984 ),
985 div(class('toggle-button'),
986 \toggle_link(Id+toggle, Id+body, L1, L2, L1))
987 ]).
993resource_list([], _) --> !.
994resource_list(Rs, Selected) -->
995 html(ul(class('resource-list'),
996 \resource_items(Rs, Selected))).
997
998resource_items([], _) --> !.
999resource_items([V|T], Selected) -->
1000 { resource_term_count(V, R, Count),
1001 resource_label(R, Label)
1002 },
1003 resource_item(R, Label, Count, Selected),
1004 resource_items(T, Selected).
1005
1006resource_label('__skipped',
1007 i(title('Skipped values'), '<skipped>')) :- !.
1008resource_label('__null',
1009 i(title('Results with no value on this facet'), '<no value>')) :- !.
1010resource_label('__single',
1011 i(title('Facet values that reference a single result'), '<unique object>')) :- !.
1012resource_label(R, Label) :-
1013 rdf_display_label(R, Label).
1014
1015resource_term_count(Count-R, R, Count) :- !.
1016resource_term_count(R, R, '').
1017
1018resource_item(R, Label, Count, Selected) -->
1019 { Selected = [],
1020 resource_attr(R, A)
1021 }, !,
1022 html(li(title(A),
1023 \resource_item_content(Label, Count)
1024 )).
1025resource_item(R, Label, Count, Selected) -->
1026 { memberchk(R, Selected),
1027 resource_attr(R, A), !,
1028 http_absolute_location(icons('checkbox_selected.png'), Img, [])
1029 },
1030 html(li([title(A), class(selected)],
1031 \resource_item_content(Label, Count, Img)
1032 )).
1033resource_item(R, Label, Count, _Selected) -->
1034 { http_absolute_location(icons('checkbox_unselected.png'), Img, []),
1035 resource_attr(R, A)
1036 },
1037 html(li(title(A),
1038 \resource_item_content(Label, Count, Img))).
1039
1040resource_attr(R, R) :- atom(R), !.
1041resource_attr(Lit, S) :-
1042 prolog_to_json(Lit, JSON),
1043 with_output_to(string(S),
1044 json_write(current_output, JSON, [])).
1045
1046resource_item_content(Label, Count) -->
1047 html([ div(class(count), Count),
1048 div(class('value-inner'),
1049 \resource_label(Label))
1050 ]).
1051resource_item_content(Label, Count, Img) -->
1052 html([ div(class(count), Count),
1053 div(class('value-inner'),
1054 [ img([class(checkbox), src(Img)], []),
1055 \resource_label(Label)
1056 ])
1057 ]).
1058
1059resource_label(FullLabel) -->
1060 { atom(FullLabel), !,
1061 truncate_atom(FullLabel, 75, Label)
1062 },
1063 html(span([title(FullLabel), class(label)], Label)).
1064resource_label(FullLabel) -->
1065 html(FullLabel).
1071toggle_link(ToggleId, BodyId, Label, Shown, Hidden) -->
1072 html(a([id(ToggleId), href('javascript:void(0)'),
1073 onClick('javascript:bodyToggle(\'#'+ToggleId+'\',\'#'+BodyId+'\',
1074 [\''+Shown+'\',\''+Hidden+'\']);')
1075 ], Label)).
1076
1077
1078 1081
1082script_data(Query, Class, Terms, Relations, Filter) -->
1083 { http_current_request(Request),
1084 memberchk(path(URL), Request),
1085 prolog_to_json(Filter, FilterJSON),
1086 Params = json([url(URL),
1087 q(Query),
1088 class(Class),
1089 terms(Terms),
1090 relations(Relations),
1091 filter(FilterJSON)
1092 ]),
1093 with_output_to(string(Data),
1094 json_write(current_output, Params, []))
1095 },
1096 html(\[
1097'var data = ',Data,';\n',
1098
1099'var isEqualLiteral = function(o1,o2) {\n',
1100' var l1 = o1.literal,
1101 l2 = o2.literal;
1102 if(l1&&l2) {\n',
1103' if(l1===l2) { return true; }
1104 else if(l1.text===l2.text) {
1105 if(l1.lang===l2.lang) { return true;}
1106 else if(l1.type===l2.type) { return true; }
1107 }
1108 }
1109}\n;',
1110
1111'var updateArray = function(a, e) {\n',
1112' for(var i=0; i<a.length; i++) {
1113 if(a[i]==e||isEqualLiteral(e, a[i])) {
1114 a.splice(i,1); return a;
1115 }
1116 }
1117 a.push(e);
1118 return a;\n',
1119'};\n',
1120'var updateFilter = function(a, p, v, replace) {\n',
1121' for(var i=0; i<a.length; i++) {\n',
1122' if(a[i].prop==p) {\n',
1123' if(replace) { a[i].values = [v] }
1124 else {
1125 var vs = updateArray(a[i].values, v);
1126 if(vs.length==0) { a.splice(i,1) }
1127 }
1128 return a;
1129 }\n',
1130' }\n',
1131' a.push({prop:p, values:[v]});
1132 return a;
1133};\n'
1134 ]).
1135
1136script_body_toggle -->
1137 html(\[
1138'function bodyToggle(toggle, container, labels) {\n',
1139' if($(container).css("display") === "none") {
1140 $(container).css("display", "block");
1141 $(toggle).html(labels[0]);
1142 }\n',
1143' else {
1144 $(container).css("display", "none");
1145 $(toggle).html(labels[1]);
1146 }',
1147'}\n'
1148 ]).
1149
1150script_term_select(Id) -->
1151 html(\[
1152'$("#',Id,'").delegate("li", "click", function(e) {\n',
1153' var terms = $(e.originalTarget).hasClass("checkbox") ?
1154 updateArray(data.terms, $(this).attr("title")) :
1155 $(this).attr("title"),
1156 params = jQuery.param({q:data.q,class:data.class,term:terms}, true);
1157 window.location.href = data.url+"?"+params;\n',
1158'})\n'
1159 ]).
1160
1161script_suggestion_select(Id) -->
1162 html(\[
1163'$("#',Id,'").delegate("li", "click", function(e) {\n',
1164' var query = $(this).find(".label").attr("title"),
1165 params = jQuery.param({q:query,class:data.class}, true);
1166 window.location.href = data.url+"?"+params;\n',
1167'})\n'
1168 ]).
1169
1170script_relation_select(Id) -->
1171 html(\[
1172'$("#',Id,'").delegate("li", "click", function(e) {\n',
1173' var relations = $(e.originalTarget).hasClass("checkbox") ?
1174 updateArray(data.relations, $(this).attr("title")) :
1175 $(this).attr("title"),
1176 params = jQuery.param({q:data.q,class:data.class,term:data.terms,filter:JSON.stringify(data.filter),relation:relations}, true);\n',
1177' window.location.href = data.url+"?"+params;\n',
1178'})\n'
1179 ]).
1180
1181script_facet_select(Id) -->
1182 html(\[
1183'$("#',Id,'").delegate("li", "click", function(e) {\n',
1184' var value = $(this).attr("title");
1185 try { value = JSON.parse(value) }
1186 catch(e) {}\n',
1187' var property = $(this).parent().parent().attr("title"),
1188 replace = $(e.originalTarget).hasClass("checkbox"),
1189 filter = updateFilter(data.filter, property, value, !replace),
1190 params = jQuery.param({q:data.q,class:data.class,term:data.terms,relation:data.relations,filter:JSON.stringify(filter)}, true);\n',
1191' window.location.href = data.url+"?"+params;\n',
1192'})\n'
1193 ]).
1194
1195script_filter_select(Id) -->
1196 html(\[
1197'$("#',Id,'").delegate("li", "click", function(e) {\n',
1198' var value = $(this).attr("title");
1199 try { value = JSON.parse(value) }
1200 catch(e) {}\n',
1201' var property = $(this).parent().parent().attr("title"),
1202 filter = updateFilter(data.filter, property, value),
1203 params = jQuery.param({q:data.q,class:data.class,term:data.terms,relation:data.relations,filter:JSON.stringify(filter)}, true);\n',
1204' window.location.href = data.url+"?"+params;\n',
1205'})\n'
1206 ]).
1207
1216request_url_components(Request, [ protocol(http),
1217 host(Host), port(Port),
1218 path(Path), search(Search)
1219 ]) :-
1220 http_current_host(Request, Host, Port,
1221 [ global(false)
1222 ]),
1223 ( option(x_redirected_path(Path), Request)
1224 -> true
1225 ; option(path(Path), Request, /)
1226 ),
1227 option(search(Search), Request, []).
1234pairs_sort_by_result_count(Grouped, Sorted) :-
1235 pairs_result_count(Grouped, Counted),
1236 keysort(Counted, Sorted0),
1237 reverse(Sorted0, Sorted).
1238
1239pairs_result_count([], []).
1240pairs_result_count([Key-Results|T], [Count-Key|Rest]) :-
1241 ( integer(Results)
1242 -> Count = Results
1243 ; length(Results, Count)
1244 ),
1245 pairs_result_count(T, Rest).
1252list_offset([], _, []) :- !.
1253list_offset(L, 0, L) :- !.
1254list_offset([_|T], N, Rest) :-
1255 N1 is N-1,
1256 list_offset(T, N1, Rest).
1262list_limit([], _, [], []) :- !.
1263list_limit(Rest, 0, [], Rest) :- !.
1264list_limit([H|T], N, [H|T1], Rest) :-
1265 N1 is N-1,
1266 list_limit(T, N1, T1, Rest).
1272instance_of_class(Class, S) :-
1273 ( var(Class)
1274 -> rdf_subject(S)
1275 ; rdf_equal(Class, rdfs:'Resource')
1276 -> rdf_subject(S)
1277 ; rdfs_individual_of(S, Class)
1278 ), !.
1279
1280 1283
1284:- multifile
1285 image_property/1,
1286 image_suffix/1. 1287
1288:- rdf_meta
1289 image_property(r). 1290
1291image_property('http://www.vraweb.org/vracore/vracore3#relation.depicts').
1292image_suffix('&resize100square').
1293
1294
1295