View source with formatted comments or as raw
    1/*  Part of ClioPatria
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2010 University of Amsterdam
    7			VU University Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(autocomplete_predicates,
   37	  [
   38	  ]).   39:- use_module(library(http/http_dispatch)).   40:- use_module(library(http/http_path)).   41:- use_module(library(http/http_parameters)).   42:- use_module(library(http/http_json)).   43:- use_module(library(http/html_head)).   44:- use_module(library(http/html_write)).   45:- use_module(library(http/yui_resources)).   46:- use_module(library(pldoc/doc_html)).   47:- use_module(library(semweb/rdf_db)).   48:- use_module(library(lists)).   49:- use_module(library(option)).   50:- use_module(library(apply)).   51:- use_module(library(occurs)).   52
   53:- multifile
   54	prolog:doc_search_field//1.   55
   56:- http_handler(root(autocomplete/ac_predicate), ac_predicate, []).   57
   58max_results_displayed(100).
   59
   60%	prolog:doc_search_field(+Options) is det.
   61
   62prolog:doc_search_field(Options) -->
   63	{ select_option(size(W), Options, Options1),
   64	  atomic_concat(W, ex, Wem),
   65	  max_results_displayed(Max)
   66	},
   67	autocomplete(ac_predicate,
   68		     [ query_delay(0.3),
   69		       auto_highlight(false),
   70		       max_results_displayed(Max),
   71		       width(Wem)
   72		     | Options1
   73		     ]).
   74
   75%%	autocomplete(+HandlerID, +Options)// is det.
   76%
   77%	Insert a YUI autocomplete widget that obtains its alternatives
   78%	from HandlerID.  The following Options are supported:
   79%
   80%	    * width(+Width)
   81%	    Specify the width of the box.  Width must satisfy the CSS
   82%	    length syntax.
   83%
   84%	    * query_delay(+Seconds)
   85%	    Wait until no more keys are typed for Seconds before sending
   86%	    the query to the server.
   87
   88autocomplete(Handler, Options) -->
   89	{ http_location_by_id(Handler, Path),
   90	  atom_concat(Handler, '_complete', CompleteID),
   91	  atom_concat(Handler, '_input', InputID),
   92	  atom_concat(Handler, '_container', ContainerID),
   93	  select_option(width(Width), Options, Options1, '25em'),
   94	  select_option(name(Name), Options1, Options2, predicate),
   95	  select_option(value(Value), Options2, Options3, '')
   96	},
   97	html([ \html_requires(yui('autocomplete/autocomplete.js')),
   98	       \html_requires(yui('autocomplete/assets/skins/sam/autocomplete.css')),
   99	       div(id(CompleteID),
  100		   [ input([ id(InputID),
  101			     name(Name),
  102			     value(Value),
  103			     type(text)
  104			   ]),
  105		     div(id(ContainerID), [])
  106		   ]),
  107	       style(type('text/css'),
  108		     [ '#', CompleteID, '\n',
  109		       '{ width:~w; padding-bottom:0em; display:inline-block; vertical-align:top}'-[Width]
  110		     ]),
  111	       \autocomplete_script(Path, InputID, ContainerID, Options3)
  112	     ]).
  113
  114autocomplete_script(HandlerID, Input, Container, Options) -->
  115	{ http_absolute_location(HandlerID, Path, [])
  116	},
  117	html(script(type('text/javascript'), \[
  118'{ \n',
  119'  var oDS = new YAHOO.util.XHRDataSource("~w");\n'-[Path],
  120'  oDS.responseType = YAHOO.util.XHRDataSource.TYPE_JSON;\n',
  121'  oDS.responseSchema = { resultsList:"results",
  122			  fields:["label","type","href"]
  123			};\n',
  124'  oDS.maxCacheEntries = 5;\n',
  125'  var oAC = new YAHOO.widget.AutoComplete("~w", "~w", oDS);\n'-[Input, Container],
  126'  oAC.resultTypeList = false;\n',
  127'  oAC.formatResult = function(oResultData, sQuery, sResultMatch) {
  128     var into = "<span class=\\"acmatch\\">"+sQuery+"</span>";
  129     var sLabel = oResultData.label.replace(sQuery, into);
  130     return "<span class=\\"" + oResultData.type + "\\">" + sLabel + "</span>";
  131   };\n',
  132'  oAC.itemSelectEvent.subscribe(function(sType, aArgs) {
  133     var oData = aArgs[2];
  134     window.location.href = oData.href;
  135   });\n',
  136\ac_options(Options),
  137'}\n'
  138					     ])).
  139ac_options([]) -->
  140	[].
  141ac_options([H|T]) -->
  142	ac_option(H),
  143	ac_options(T).
  144
  145ac_option(query_delay(Time)) --> !,
  146	html([ '  oAC.queryDelay = ~w;\n'-[Time] ]).
  147ac_option(auto_highlight(Bool)) --> !,
  148	html([ '  oAC.autoHighlight = ~w;\n'-[Bool] ]).
  149ac_option(max_results_displayed(Max)) -->
  150	html([ '  oAC.maxResultsDisplayed = ~w;\n'-[Max] ]).
  151ac_option(O) -->
  152	{ domain_error(yui_autocomplete_option, O) }.
  153
  154%%	ac_predicate(+Request)
  155%
  156%	HTTP handler for completing a predicate-name.   The  output is a
  157%	JSON object that describes possible completions.
  158
  159ac_predicate(Request) :-
  160	max_results_displayed(DefMax),
  161	http_parameters(Request,
  162			[ query(Query, [ description('Typed string') ]),
  163			  maxResultsDisplayed(Max,
  164					      [ integer, default(DefMax),
  165						description('Max number of results to show')
  166					      ])
  167			]),
  168	autocompletions(Query, Max, Count, Completions),
  169	reply_json(json([ query = json([ count=Count
  170				       ]),
  171			  results = Completions
  172			])).
  173
  174autocompletions(Query, Max, Count, Completions)  :-
  175	autocompletions(name, Query, Max, BNC, ByName),
  176	(   BNC > Max
  177	->  Completions = ByName,
  178	    Count = BNC
  179	;   TMax is Max-BNC,
  180	    autocompletions(token, Query, TMax, BTC, ByToken),
  181	    append(ByName, ByToken, Completions),
  182	    Count is BNC+BTC
  183	).
  184
  185autocompletions(How, Query, Max, Count, Completions) :-
  186	findall(C, ac_object(How, Query, C), Completions0),
  187	sort(Completions0, Completions1),
  188	length(Completions1, Count),
  189	first_n(Max, Completions1, Completions2),
  190	maplist(obj_result, Completions2, Completions).
  191
  192obj_result(_Name-Obj, json([ label=Label,
  193			     type=Type,
  194			     href=Href
  195			   ])) :-
  196	obj_name(Obj, Label, Type),
  197	object_href(Obj, Href).
  198
  199obj_name(c(Function), Name, cfunc) :- !,
  200	atom_concat(Function, '()', Name).
  201obj_name(M:Term, Name, Class) :- !,
  202	predicate_class(M:Term, Class),
  203	format(atom(Name), '<span class="ac-module">~w</span>:~w', [M,Term]).
  204obj_name(Term, Name, 'ac-builtin') :-
  205	format(atom(Name), '~w', [Term]).
  206
  207predicate_class(Head, built_in) :-
  208	predicate_property(Head, 'ac-builtin'), !.
  209predicate_class(Head, exported) :-
  210	predicate_property(Head, 'ac-exported'), !.
  211predicate_class(Head, hook) :-
  212	predicate_property(Head, 'ac-multifile'), !.
  213predicate_class(_, 'ac-private').
  214
  215
  216first_n(0, _, []) :- !.
  217first_n(_, [], []) :- !.
  218first_n(N, [H|T0], [H|T]) :-
  219	N2 is N - 1,
  220	first_n(N2, T0, T).
  221
  222
  223		 /*******************************
  224		 *	  PREFIX DATABASE	*
  225		 *******************************/
  226
  227ac_object(name, Prefix, Name-Obj) :-
  228	prefix_index(ByName, _ByToken),
  229	rdf_keys_in_literal_map(ByName, prefix(Prefix), Keys),
  230	member(Name, Keys),
  231	name_object(Name, Obj, _Category).
  232ac_object(token, Prefix, Name-Obj) :-
  233	prefix_index(_ByName, ByToken),
  234	rdf_keys_in_literal_map(ByToken, prefix(Prefix), Keys),
  235	member(Token, Keys),
  236	rdf_find_literal_map(ByToken, [Token], Names),
  237	member(Name, Names),
  238	name_object(Name, Obj, _Category).
  239
  240
  241:- dynamic
  242	prefix_map/2,			% name-map, token-map
  243	name_object/3.  244
  245prefix_index(ByName, ByToken) :-
  246	prefix_map(ByName, ByToken), !.
  247prefix_index(ByName, ByToken) :-
  248	rdf_new_literal_map(ByName),
  249	rdf_new_literal_map(ByToken),
  250	assertz(prefix_map(ByName, ByToken)),
  251	fill_token_map.
  252
  253fill_token_map :-
  254	prefix_map(ByName, ByToken),
  255	rdf_reset_literal_map(ByName),
  256	rdf_reset_literal_map(ByToken),
  257	retractall(name_object(_,_,_)),
  258	(   documented(Obj, Category),
  259	    completion_target(Obj, Name),
  260	    assertz(name_object(Name, Obj, Category)),
  261	    rdf_insert_literal_map(ByName, Name, Name),
  262	    forall(start_inside_token(Name, Token),
  263		   rdf_insert_literal_map(ByToken, Token, Name)),
  264	    fail
  265	;   true
  266	),
  267	keep_best_doc.
  268
  269documented(Obj, Category) :-
  270	prolog:doc_object_summary(Obj, Category, _Section, _Summary).
  271
  272keep_best_doc :-
  273	(   name_object(Name, Obj, Category),
  274	    name_object(Name, Obj2, Category2),
  275	    same_object(Obj, Obj2),
  276	    better_category(Category2, Category),
  277	    retract(name_object(Name, Obj, Category)),
  278	    fail
  279	;   true
  280	).
  281
  282same_object(_:Name/Arity, Name/Arity).
  283same_object(Name/Arity, _:Name/Arity).
  284
  285better_category(manual, _) :- !.
  286better_category(packages, _) :- !.
  287
  288
  289completion_target(Name/_,    Name).
  290completion_target(Name//_,   Name).
  291completion_target(_:Name/_,  Name).
  292completion_target(_:Name//_, Name).
  293%completion_target(c(Name),  Name).
  294
  295start_inside_token(Token, Inside) :-
  296	sub_atom(Token, _, _, L, '_'),
  297	sub_atom(Token, _, L, 0, Inside)