View source with raw comments or as raw
    1/*  Part of SWISH
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2015-2018, VU University Amsterdam
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(swish_search,
   36	  [ search_box//1,		% +Options
   37	    match/3			% +Line, +Query, +Options
   38	  ]).   39:- use_module(library(lists)).   40:- use_module(library(http/html_write)).   41:- use_module(library(http/http_dispatch)).   42:- use_module(library(http/http_parameters)).   43:- use_module(library(http/http_json)).   44:- use_module(library(prolog_source)).   45:- use_module(library(option)).   46:- use_module(library(debug)).   47:- use_module(library(solution_sequences)).   48
   49:- use_module(config).   50
   51:- multifile
   52	typeahead/4.			% +Set, +Query, -Match, +Options

SWISH search from the navigation bar

This library supports both typeahead of the search box and the actual search from the server side. What do we want to search for?

   66:- http_handler(swish(typeahead), typeahead, [id(swish_typeahead)]).
 search_box(+Options)//
Render a Bootstrap search box.
   72search_box(_Options) -->
   73	html(form([class('navbar-form'), role(search)],
   74		  div(class('input-group'),
   75		      [ input([ type(text),
   76				class(['form-control', typeahead]),
   77				placeholder('Search'),
   78				'data-search-in'([source,files,predicates]),
   79				title('Searches code, documentation and files'),
   80				id('search')
   81			      ]),
   82			div(class('input-group-btn'),
   83			    button([ class([btn, 'btn-default']),
   84				     type(submit)],
   85				   i(class([glyphicon, 'glyphicon-search']),
   86				     [])))
   87		      ]))).
 typeahead(+Request)
Support the search typeahead widget. The handler returns a JSON array of matches. Each match is an object that contains at least a label.
   96typeahead(Request) :-
   97	http_parameters(Request,
   98			[ q(Query,     [default('')]),
   99			  set(Set,     [default(predicates)]),
  100			  match(Match, [default(sow)])
  101			]),
  102	findall(Result, typeahead(Set, Query, Result, _{match:Match}), Results),
  103	reply_json_dict(Results).
 typeahead(+Type, +Query, -Match, +Options:dict) is nondet
Find typeahead suggestions for a specific search category (Type). This oredicate is a multifile predicate, which allows for adding new search targets. The default implementation offers:
predicates
Searches for built-in and configured library predicates
sources
Searches all loaded source files.
To be done
- : Limit number of hits?
  119:- multifile
  120	swish_config:source_alias/2.  121
  122typeahead(predicates, Query, Template, _) :-
  123	swish_config(templates, Templates),
  124	member(Template, Templates),
  125	_{name:Name, arity:_} :< Template,
  126	sub_atom(Name, 0, _, _, Query).
  127typeahead(sources, Query, Hit, Options) :-
  128	source_file(Path),
  129	(   file_alias_path(Alias, Dir),
  130	    once(swish_config:source_alias(Alias, _)),
  131	    atom_concat(Dir, File, Path)
  132	->  true
  133	),
  134	file_name_extension(Base, Ext, File),
  135	(   sub_atom(File, 0, _, _, Query)
  136	->  Hit = hit{alias:Alias, file:Base, ext:Ext, query:Query}
  137	;   Hit = hit{alias:Alias, file:Base, ext:Ext,
  138		      query:Query, line:LineNo, text:Line},
  139	    limit(5, search_file(Path, Query, LineNo, Line, Options))
  140	).
  141typeahead(sources, Query, hit{alias:Alias, file:Base, ext:Ext,
  142			      query:Query, line:LineNo, text:Line}, Options) :-
  143	swish_config:source_alias(Alias, AliasOptions),
  144	option(search(Pattern), AliasOptions),
  145	DirSpec =.. [Alias,.],
  146	absolute_file_name(DirSpec, Dir,
  147			   [ access(read),
  148			     file_type(directory),
  149			     solutions(all),
  150			     file_errors(fail)
  151			   ]),
  152	directory_file_path(Dir, Pattern, FilePattern),
  153	expand_file_name(FilePattern, Files),
  154	atom_concat(Dir, /, DirSlash),
  155	member(Path, Files),
  156	\+ source_file(Path),		% already did this one above
  157	atom_concat(DirSlash, File, Path),
  158	file_name_extension(Base, Ext, File),
  159	limit(5, search_file(Path, Query, LineNo, Line, Options)).
  160
  161search_file(Path, Query, LineNo, Line, Options) :-
  162	debug(swish(search), 'Searching ~q for ~q (~q)', [Path, Query, Options]),
  163	setup_call_cleanup(
  164	    open(Path, read, In),
  165	    read_string(In, _, String),
  166	    close(In)),
  167	split_string(String, "\n", "\r", Lines),
  168	nth1(LineNo, Lines, Line),
  169	match(Line, Query, Options).
 match(+Line:string, +Query:string, +Options:dict) is semidet
True if Line matches Query, respecting Options.
  175match(Text, Query, Options) :-
  176	sub_string(Text, Start, _, _, Query),
  177	(   Options.get(match) == sow
  178	->  sow(Text, Start), !
  179	;   Options.get(match) == sol
  180	->  !, Start == 0
  181	;   !
  182	).
  183
  184sow(_, 0) :- !.
  185sow(Text, Offset) :-
  186	Pre is Offset-1,
  187	sub_atom(Text, Pre, 1, _, Before),
  188	sub_atom(Text, Offset, 1, _, Start),
  189	(   \+ char_type(Before, csym),
  190	    char_type(Start, csym)
  191	;   Before == '_',
  192	    char_type(Start, csym)
  193	;   char_type(Start, upper),
  194	    char_type(Before, lower)
  195	), !