View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@cs.vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2009-2013, VU University Amsterdam
    7
    8    This program is free software; you can redistribute it and/or
    9    modify it under the terms of the GNU General Public License
   10    as published by the Free Software Foundation; either version 2
   11    of the License, or (at your option) any later version.
   12
   13    This program is distributed in the hope that it will be useful,
   14    but WITHOUT ANY WARRANTY; without even the implied warranty of
   15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   16    GNU General Public License for more details.
   17
   18    You should have received a copy of the GNU General Public
   19    License along with this library; if not, write to the Free Software
   20    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   21
   22    As a special exception, if you link this library with other files,
   23    compiled with a Free Software compiler, to produce an executable, this
   24    library does not by itself cause the resulting executable to be covered
   25    by the GNU General Public License. This exception does not however
   26    invalidate any other reasons why the executable file might be covered by
   27    the GNU General Public License.
   28*/
   29
   30:- module(plweb_autocomplete,
   31	  [
   32	  ]).   33:- use_module(library(http/http_dispatch)).   34:- use_module(library(http/http_parameters)).   35:- use_module(library(http/http_json)).   36:- use_module(library(http/html_head)).   37:- use_module(library(http/html_write)).   38:- use_module(library(http/js_write)).   39:- use_module(library(pldoc/doc_html)).   40:- use_module(library(semweb/rdf_db)).   41:- use_module(library(broadcast)).   42:- use_module(library(lists)).   43:- use_module(library(option)).   44:- use_module(library(apply)).

SWI-Prolog website autocompletion support

This module provides the handler for =/autocomplete/ac_predicate=, which implements autocompletion for the website. This handler is called from searchbox_script//1 in page.pl. */

   53:- multifile
   54	prolog:doc_search_field//1,
   55	prolog:ac_object/3,			% +How, +Search, -Name-Object
   56	prolog:doc_object_href/2,		% +Object, -HREF
   57	prolog:doc_object_label_class/3,	% +Object, -Label, -Class
   58	prolog:ac_object_attributes/2.		% +Object, -Attributes
   59
   60:- http_handler(root(autocomplete/ac_predicate), ac_predicate,
   61		[spawn(complete)]).   62
   63max_results_displayed(100).
 prolog:doc_search_field(+Options) is det
Emit the manual-search field. This is a hook into PlDoc to override the PlDoc search field. In theory, all searches on the website should now be using the search box as defined in page.pl. See searchbox_script//1.
   72prolog:doc_search_field(Options) -->
   73	{ option(id(Id), Options),
   74	  http_link_to_id(ac_predicate, [], URL)
   75	},
   76	html_requires(jquery_ui),
   77	html([ input([ id('submit-for'),
   78		       type(submit),
   79		       value('Search'),
   80		       style('float:right')
   81		     ]),
   82	       div([ id('search-container'),
   83		     style('overflow:hidden')
   84		   ],
   85		   input([ style('width:100%; min-width:20em')
   86			 | Options
   87			 ]))
   88	     ]),
   89	js_script({|javascript(Id, URL)||
   90$(function() {
   91  $("#"+Id).autocomplete({
   92    minLength: 1,
   93    delay: 0.3,
   94    source: URL,
   95    focus: function(event,ui) {
   96      $("#"+Id).val(ui.item.label);
   97      return false;
   98    },
   99    select: function(event,ui) {
  100      $("#"+Id).val(ui.item.label);
  101      window.location.href = ui.item.href;
  102      return false;
  103    }
  104  })
  105  .data("ui-autocomplete")._renderItem = function(ul,item) {
  106    var label = String(item.label).replace(
  107		new RegExp(this.term),
  108		"<span class=\"acmatch\">$&</span>");
  109    var tag = item.tag ? " <i>["+item.tag+"]</i>" : "";
  110    return $("<li>")
  111      .append("<a class=\""+item.class+"\">"+label+tag+"</a>")
  112      .appendTo(ul)
  113  };
  114});
  115		   |}).
 ac_predicate(+Request)
HTTP handler to reply autocompletion
  123ac_predicate(Request) :-
  124	http_parameters(Request,
  125			[ term(Query, [])
  126			]),
  127	max_results_displayed(Max),
  128	autocompletions(Query, Max, _Count, Completions),
  129	reply_json(Completions).
  130
  131autocompletions(Query, Max, Count, Completions)  :-
  132	autocompletions_by(name, Query, BNC, ByName),
  133	(   BNC > Max
  134	->  first_results(Max, ByName, Completions),
  135	    Count = BNC
  136	;   autocompletions_by(token, Query, BTC, ByToken),
  137	    ord_subtract(ByToken, ByName, NewByToken),
  138	    append(ByName, NewByToken, All),
  139	    Count is min(Max, BNC+BTC),
  140	    first_results(Max, All, Completions)
  141	).
  142
  143autocompletions_by(How, Query, Count, Completions) :-
  144	findall(C, ac_object(How, Query, C), Completions0),
  145	sort(Completions0, Completions),
  146	length(Completions, Count).
  147
  148first_results(Max, Completions, Results) :-
  149	first_n(Max, Completions, FirstN),
  150	maplist(obj_result, FirstN, Results).
  151
  152obj_result(Name-Obj, json([ label=Label,
  153			    class=Type,
  154			    href=Href
  155			  | Extra
  156			  ])) :-
  157	obj_name(Name-Obj, Label, Type),
  158	(   prolog:doc_object_href(Obj, Href)
  159	->  true
  160	;   object_href(Obj, Href)
  161	),
  162	obj_tag(Obj, Extra).
  163
  164obj_tag(Object, Extra) :-
  165	prolog:ac_object_attributes(Object, Extra), !.
  166obj_tag(Name/Arity, Extra) :-
  167	current_predicate(system:Name/Arity),
  168	functor(Head, Name, Arity),
  169	predicate_property(system:Head, iso), !,
  170	Extra = [tag=iso].
  171obj_tag(f(_Func/_Arity), [tag=function]) :- !.
  172obj_tag(section(_), [tag=section]) :- !.
  173obj_tag(wiki(_), [tag=wiki]) :- !.
  174obj_tag(_, []).
 obj_name(+Object, -Label, -Class) is det
Provide the (autocomplete) label for Object and its class. The class may be used to style the hit in www/css/plweb.css.
To be done
- : There are a lot of similar things around in the code.
  184obj_name(Label-section(_), Label, section) :- !.
  185obj_name(Label-wiki(_), Label, section) :- !.
  186obj_name(_Name-Obj, Label, Class) :-
  187	obj_name2(Obj, Label, Class).
  188
  189obj_name2(Object, Label, Class) :-
  190	prolog:doc_object_label_class(Object, Label, Class), !.
  191obj_name2(c(Function), Name, cfunc) :- !,
  192	atom_concat(Function, '()', Name).
  193obj_name2(f(Func/Arity), Name, function) :- !,
  194	format(atom(Name), '~w/~w', [Func, Arity]).
  195obj_name2(_:Term, Name, pred) :- !,
  196	format(atom(Name), '~w', [Term]).
  197obj_name2(Name/Arity, Label, Class) :-
  198	current_predicate(system:Name/Arity),
  199	functor(Head, Name, Arity),
  200	predicate_property(system:Head, built_in), !,
  201	format(atom(Label), '~w/~w', [Name, Arity]),
  202	Class = builtin.
  203obj_name2(Term, Name, pred) :-
  204	format(atom(Name), '~w', [Term]).
  205
  206first_n(0, _, []) :- !.
  207first_n(_, [], []) :- !.
  208first_n(N, [H|T0], [H|T]) :-
  209	N2 is N - 1,
  210	first_n(N2, T0, T).
  211
  212
  213		 /*******************************
  214		 *	  PREFIX DATABASE	*
  215		 *******************************/
  216
  217ac_object(name, Prefix, Name-Obj) :-
  218	prefix_index(ByName, _ByToken),
  219	rdf_keys_in_literal_map(ByName, prefix(Prefix), Keys),
  220	member(Name, Keys),
  221	name_object(Name, Obj, _Category).
  222ac_object(token, Prefix, Name-Obj) :-
  223	prefix_index(_ByName, ByToken),
  224	rdf_keys_in_literal_map(ByToken, prefix(Prefix), Keys),
  225	member(Token, Keys),
  226	rdf_find_literal_map(ByToken, [Token], Names),
  227	member(Name, Names),
  228	name_object(Name, Obj, _Category).
  229ac_object(MatchHow, Term, Match) :-
  230	prolog:ac_object(MatchHow, Term, Match).
  231
  232
  233:- dynamic
  234	prefix_map/2,			% name-map, token-map
  235	name_object/3,
  236	token_map_up_to_date/0.  237
  238prefix_index(ByName, ByToken) :-
  239	prefix_map(ByName, ByToken),
  240	token_map_up_to_date, !.
  241prefix_index(ByName, ByToken) :-
  242	with_mutex(autocomplete,
  243		   create_prefix_index(ByName, ByToken)).
  244
  245create_prefix_index(ByName, ByToken) :-
  246	prefix_map(ByName, ByToken),
  247	token_map_up_to_date, !.
  248create_prefix_index(ByName, ByToken) :-
  249	(   prefix_map(ByName, ByToken)
  250	->  true
  251	;   rdf_new_literal_map(ByName),
  252	    rdf_new_literal_map(ByToken),
  253	    assertz(prefix_map(ByName, ByToken))
  254	),
  255	fill_token_map,
  256	assertz(token_map_up_to_date).
 update_autocompletion_map
Assert that the token map is out of data.
  262:- listen(modified(wiki(_)), update_autocompletion_map).  263
  264update_autocompletion_map :-
  265	retractall(token_map_up_to_date).
 fill_token_map is det
Examine the objects that are suitable for autocompletion, building:
  276fill_token_map :-
  277	prefix_map(ByName, ByToken),
  278	rdf_reset_literal_map(ByName),
  279	rdf_reset_literal_map(ByToken),
  280	retractall(name_object(_,_,_)),
  281	(   documented(Obj0, Category, Summary),
  282	    completion_target(Obj0, Summary, Obj, Name),
  283	    assertz(name_object(Name, Obj, Category)),
  284	    rdf_insert_literal_map(ByName, Name, Name),
  285	    forall(sub_token(Name, Token),
  286		   rdf_insert_literal_map(ByToken, Token, Name)),
  287	    fail
  288	;   true
  289	),
  290	keep_best_doc.
  291
  292documented(Obj, Category, Summary) :-
  293	prolog:doc_object_summary(Obj, Category, _Section, Summary).
 keep_best_doc is det
Filter the documentation objects found in name_object/3, removing `inferior' objects.
  300keep_best_doc :-
  301	(   name_object(Name, Obj, Category),
  302	    name_object(Name, Obj2, Category2),
  303	    same_object(Obj, Obj2),
  304	    better_category(Category2, Category),
  305	    retract(name_object(Name, Obj, Category)),
  306	    fail
  307	;   true
  308	).
  309
  310same_object(_:Name/Arity, Name/Arity).
  311same_object(Name/Arity, _:Name/Arity).
  312same_object(_:Name//Arity, Name//Arity).
  313same_object(Name//Arity, _:Name//Arity).
  314
  315better_category(manual, _) :- !.
  316better_category(packages, _) :- !.
 completion_target(+Object0, +Summary, -Object, -Name) is semidet
True when we can do completion on Object based on Name.
  323completion_target(section(_,_,Id,_), SummaryS, section(Id), Summary) :- !,
  324	\+ sub_atom(Id, 0, _, _, 'sec:summary'),
  325	atom_string(Summary, SummaryS).		% literal maps do not use strings
  326completion_target(wiki(Location), SummaryS, wiki(Location), Summary) :- !,
  327	(   atom_string(Summary, SummaryS)	% literal maps do not use strings
  328	;   file_base_name(Location, Base),
  329	    file_name_extension(Summary, _, Base)
  330	).
  331completion_target(Object, _, Object, Name) :-
  332	completion_target(Object, Name).
  333
  334completion_target(Name/_,   Name).
  335completion_target(Name//_,  Name).
  336completion_target(M:Name/A, Name) :-
  337	integer(A), atom(Name),
  338	functor(Head, Name, A),
  339	predicate_property(M:Head, exported).
  340completion_target(M:Name//DA, Name) :-
  341	integer(DA), atom(Name),
  342	A is DA+2,
  343	functor(Head, Name, A),
  344	predicate_property(M:Head, exported).
  345completion_target(f(Name/_),Name).
  346completion_target(c(Name),  Name).
 sub_token(+Label, -Token) is nondet
  350sub_token(Label, Token) :-
  351	catch(tokenize_atom(Label, [_|Tokens]), _, fail),
  352	member(Token, Tokens),
  353	atom(Token),
  354	downcase_atom(Token, Lower),
  355	\+ stop_token(Lower).
  356
  357stop_token('_').
  358stop_token('(').
  359stop_token(')').
  360stop_token(':').
  361stop_token(a).
  362stop_token(the)