34
35:- module(swish_search,
36 [ search_box//1, 37 match/3 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:- use_module(library(apply)). 49:- use_module(library(filesex)). 50
51:- use_module(config). 52
53:- multifile
54 typeahead/4.
68:- http_handler(swish(typeahead), typeahead, [id(swish_typeahead)]).
74search_box(_Options) -->
75 html(form([class('navbar-form'), role(search)],
76 div(class('input-group'),
77 [ input([ type(text),
78 class(['form-control', typeahead]),
79 placeholder('Search'),
80 'data-search-in'([source,store_content,files,predicates]),
81 title('Searches code, documentation and files'),
82 id('search')
83 ]),
84 div(class('input-group-btn'),
85 button([ class([btn, 'btn-default']),
86 type(submit)],
87 i(class([glyphicon, 'glyphicon-search']),
88 [])))
89 ]))).
98typeahead(Request) :-
99 http_parameters(Request,
100 [ q(Query, [default('')]),
101 set(Set, [default(predicates)]),
102 match(Match, [default(sow)]),
103 avatar(Avatar, [optional(true)]),
104 display_name(Name, [optional(true)])
105 ]),
106 include(ground,
107 [ match-Match,
108 avatar-Avatar,
109 display_name-Name
110 ], OptPairs),
111 dict_pairs(Options, #, OptPairs),
112 findall(Result, typeahead(Set, Query, Result, Options), Results),
113 reply_json_dict(Results).
129:- multifile
130 swish_config:source_alias/2. 131
132typeahead(predicates, Query, Template, _) :-
133 swish_config(templates, Templates),
134 member(Template, Templates),
135 _{name:Name, arity:_} :< Template,
136 sub_atom(Name, 0, _, _, Query).
137typeahead(sources, Query, Hit, Options) :-
138 source_file(Path),
139 ( file_alias_path(Alias, Dir),
140 once(swish_config:source_alias(Alias, _)),
141 atom_concat(Dir, File, Path)
142 -> true
143 ),
144 file_name_extension(Base, Ext, File),
145 ( sub_atom(File, 0, _, _, Query)
146 -> Hit = hit{alias:Alias, file:Base, ext:Ext, query:Query}
147 ; Hit = hit{alias:Alias, file:Base, ext:Ext,
148 query:Query, line:LineNo, text:Line},
149 limit(5, search_file(Path, Query, LineNo, Line, Options))
150 ).
151typeahead(sources, Query, hit{alias:Alias, file:Base, ext:Ext,
152 query:Query, line:LineNo, text:Line}, Options) :-
153 swish_config:source_alias(Alias, AliasOptions),
154 option(search(Pattern), AliasOptions),
155 DirSpec =.. [Alias,.],
156 absolute_file_name(DirSpec, Dir,
157 [ access(read),
158 file_type(directory),
159 solutions(all),
160 file_errors(fail)
161 ]),
162 directory_file_path(Dir, Pattern, FilePattern),
163 expand_file_name(FilePattern, Files),
164 atom_concat(Dir, /, DirSlash),
165 member(Path, Files),
166 \+ source_file(Path), 167 atom_concat(DirSlash, File, Path),
168 file_name_extension(Base, Ext, File),
169 limit(5, search_file(Path, Query, LineNo, Line, Options)).
170
171search_file(Path, Query, LineNo, Line, Options) :-
172 debug(swish(search), 'Searching ~q for ~q (~q)', [Path, Query, Options]),
173 setup_call_cleanup(
174 open(Path, read, In),
175 read_string(In, _, String),
176 close(In)),
177 split_string(String, "\n", "\r", Lines),
178 nth1(LineNo, Lines, Line),
179 match(Line, Query, Options).
185match(Text, Query, Options) :-
186 sub_string(Text, Start, _, _, Query),
187 ( Options.get(match) == sow
188 -> sow(Text, Start), !
189 ; Options.get(match) == sol
190 -> !, Start == 0
191 ; !
192 ).
193
194sow(_, 0) :- !.
195sow(Text, Offset) :-
196 Pre is Offset-1,
197 sub_atom(Text, Pre, 1, _, Before),
198 sub_atom(Text, Offset, 1, _, Start),
199 ( \+ char_type(Before, csym),
200 char_type(Start, csym)
201 ; Before == '_',
202 char_type(Start, csym)
203 ; char_type(Start, upper),
204 char_type(Before, lower)
205 ), !
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?