35
36:- module(swish_template_hint,
37 [ visible_predicate/3, 38 predicate_template/2, 39 visible_predicate_templates/3 40 ]). 41:- use_module(library(apply)). 42:- use_module(library(pldoc), []). 43:- use_module(library(pldoc/doc_man)). 44:- use_module(library(pldoc/doc_process)). 45:- use_module(library(pldoc/doc_wiki)). 46:- use_module(library(pldoc/doc_modes)). 47:- use_module(library(doc_http)). 48:- use_module(library(http/html_write)). 49:- use_module(library(memfile)). 50:- use_module(library(sgml)). 51:- use_module(library(lists)). 52:- use_module(library(pairs)). 53:- use_module(library(xpath)). 54:- use_module(library(sandbox)). 55:- use_module(library(option)). 56:- use_module(library(filesex)). 57:- use_module(library(error)). 58
59:- use_module(render). 60:- use_module(highlight). 61
72
73:- if(current_predicate(doc_enable/1)). 74:- initialization(doc_enable(true)). 75:- endif. 76
81
82:- dynamic
83 cached_templates/3. 84
85visible_predicate_templates(Module, Templates, Options) :-
86 cached_templates(Module, Options, Templates), !.
87visible_predicate_templates(Module, Templates, Options) :-
88 with_mutex(swish_template_hint,
89 visible_predicate_templates_sync(Module, Templates, Options)).
90
91visible_predicate_templates_sync(Module, Templates, Options) :-
92 cached_templates(Module, Options, Templates), !.
93visible_predicate_templates_sync(Module, Templates, Options) :-
94 findall(Templ,
95 ( visible_predicate(PI, Module, Options),
96 predicate_template(PI, Templ)
97 ),
98 Templates0),
99 assertz(cached_templates(Module, Options, Templates0)),
100 Templates0 = Templates.
101
102clean_template_cache :-
103 retractall(cached_templates(_,_,_)).
104
105:- initialization clean_template_cache. 106
116
117visible_predicate(PI, Module, Options) :-
118 option(from(FromList), Options), !,
119 must_be(list, FromList),
120 member(From, FromList),
121 must_be(ground, From),
122 visible_from(From, PI, Module, Options),
123 \+ no_template(PI).
124visible_predicate(PI, Module, Options) :-
125 PI = Name/Arity,
126 predicate_property(Module:Head, visible),
127 autoload(Module:Head, Options),
128 safe(Module:Head, Options),
129 functor(Head, Name, Arity),
130 \+ no_template(PI).
131
132no_template(use_module/1).
133no_template(use_module/2).
134no_template(use_rendering/1).
135no_template(use_rendering/2).
136
142
143visible_from(built_in, Name/Arity, _Module, Options) :- !,
144 predicate_property(system:Head, built_in),
145 functor(Head, Name, Arity),
146 \+ sub_atom(Name, 0, _, _, $),
147 safe(system:Head, Options).
148visible_from(Spec, Name/Arity, _Module, _Options) :-
149 compound(Spec),
150 functor(Spec, _, 1),
151 exists_source(Spec),
152 xref_public_list(Spec, -,
153 [ exports(Exports)
154 ]),
155 member(Name/Arity, Exports).
156
157
158autoload(Pred, Options) :-
159 option(autoload(false), Options, false), !,
160 Pred = M:Head,
161 functor(Head, Name, Arity),
162 ( current_predicate(M:Name/Arity)
163 -> \+ ( predicate_property(M:Head, imported_from(LoadModule)),
164 no_autocomplete_module(LoadModule)
165 )
166 ; '$find_library'(M, Name, Arity, LoadModule, _Library),
167 \+ no_autocomplete_module(LoadModule),
168 current_predicate(LoadModule:Name/Arity)
169 ).
170autoload(_, _).
171
172no_autocomplete_module(pce).
173no_autocomplete_module(pce_principal).
174no_autocomplete_module(pce_class_template).
175no_autocomplete_module(pce_dispatch).
176no_autocomplete_module(pce_expansion).
177no_autocomplete_module(pce_error).
178no_autocomplete_module(pce_compatibility_layer).
179no_autocomplete_module(backward_compatibility).
180no_autocomplete_module(settings).
181no_autocomplete_module(quintus).
182no_autocomplete_module(toplevel_variables).
183no_autocomplete_module('$qlf').
184no_autocomplete_module(pldoc).
185no_autocomplete_module(quasi_quotations).
186no_autocomplete_module(ssl).
187no_autocomplete_module(oset).
188no_autocomplete_module(prolog_colour).
189no_autocomplete_module(pengines_io).
190no_autocomplete_module(broadcast).
191no_autocomplete_module(sgml).
192no_autocomplete_module(swi_system_utilities).
193no_autocomplete_module(prolog_metainference).
194no_autocomplete_module(thread_pool).
195
200
201safe(Goal, Options) :-
202 option(safe(true), Options, true), !,
203 ( predicate_property(Goal, meta_predicate(_))
204 -> true
205 ; catch(safe_goal(Goal), _, fail)
206 ).
207safe(_, _).
208
223
224predicate_template(PI, Dict) :-
225 findall(Pair, predicate_info(PI, Pair), Pairs),
226 Pairs \== [],
227 dict_pairs(Dict, json, Pairs).
228
229predicate_info(PI, Pair) :-
230 ( man_predicate_info(PI, Pair)
231 *-> true
232 ; pldoc_predicate_info(PI, Pair)
233 ).
234
238
239man_predicate_info(PI, Name-Value) :-
240 pi_head(PI, Head),
241 strip_module(Head, _, PHead),
242 functor(PHead, PName, Arity),
243 phrase(man_page(PName/Arity,
244 [ no_manual(fail),
245 links(false),
246 navtree(false)
247 ]), HTML),
248 setup_call_cleanup(
249 new_memory_file(MF),
250 ( setup_call_cleanup(
251 open_memory_file(MF, write, Out),
252 print_html(Out, HTML),
253 close(Out)),
254 setup_call_cleanup(
255 open_memory_file(MF, read, In),
256 load_html(stream(In), DOM, [syntax_errors(quiet)]),
257 close(In))
258 ),
259 free_memory_file(MF)),
260 xpath_chk(DOM, //dt(@class=pubdef), DT),
261 xpath_chk(DT, a(text), ModeLine0),
262 normalize_space(string(ModeLine), ModeLine0),
263 ( atom_string(PName, PString),
264 Name-Value = name-PString
265 ; Name-Value = arity-Arity
266 ; Name-Value = (mode)-ModeLine
267 ; once(man_predicate_summary(PName/Arity, Summary)),
268 Name-Value = summary-Summary
269 ; predicate_property(system:PHead, iso),
270 Name-Value = iso-true
271 ; predicate_property(system:PHead, built_in),
272 Name-Value = type-built_in
273 ).
274
276
277pldoc_predicate_info(PI, Name-Value) :-
278 pi_head(PI, Head),
279 strip_module(Head, _, PHead),
280 functor(PHead, PName, Arity),
281 implementation_module(Head, Module),
282 doc_comment(PI, Pos, Summary, Comment), !,
283 is_structured_comment(Comment, Prefixes),
284 string_codes(Comment, CommentCodes),
285 indented_lines(CommentCodes, Prefixes, Lines),
286 process_modes(Lines, Module, Pos, Modes, _VarNames, _RestLines),
287 member(mode(Mode,Vars), Modes),
288 mode_head_det(Mode, ModeHead, Det),
289 m_same_name_arity(ModeHead, Head),
290 maplist(bind_var, Vars),
291 term_string(ModeHead, ModeLine,
292 [ quoted(true),
293 module(pldoc_modes),
294 numbervars(true),
295 spacing(next_argument)
296 ]),
297 ( atom_string(PName, PString),
298 Name-Value = name-PString
299 ; Name-Value = arity-Arity
300 ; Name-Value = (mode)-ModeLine
301 ; Name-Value = summary-Summary
302 ; Det \== unknown,
303 Name-Value = determinism-Det
304 ).
305
306
307bind_var(Name=Var) :- Var = '$VAR'(Name).
308
309mode_head_det(Head is Det, Head, Det) :- !.
310mode_head_det(Head, Head, unknown).
311
312pi_head(Var, _) :-
313 var(Var), !, instantiation_error(Var).
314pi_head(M0:T0, M:T) :- !,
315 strip_module(M0:T0, M, T1),
316 pi_head(T1, T).
317pi_head(Name/Arity, Head) :- !,
318 functor(Head, Name, Arity).
319pi_head(Name//DCGArity, Head) :-
320 Arity is DCGArity+2,
321 functor(Head, Name, Arity).
322
323implementation_module(Head, M) :-
324 predicate_property(Head, imported_from(M0)), !,
325 M = M0.
326implementation_module(Head, M) :-
327 strip_module(user:Head, M, _).
328
329m_same_name_arity(H1, H2) :-
330 strip_module(H1, _, P1),
331 strip_module(H2, _, P2),
332 functor(P1, Name, Arity),
333 functor(P2, Name, Arity).
334
335
336 339
343
344rendering_template([ json{displayText: "use_rendering(+Renderer).",
345 type: "directive",
346 template: "use_rendering(${Renderer}).",
347 varTemplates: json{'Renderer': Template}},
348 json{displayText: "use_rendering(+Renderer, +Options).",
349 type: "directive",
350 template: "use_rendering(${Renderer}).",
351 varTemplates: json{'Renderer': Template}}
352 ]) :-
353 findall(json{displayText: Comment,
354 text: Name},
355 current_renderer(Name, Comment),
356 Template).
357
358
359 362
369
370library_template(json{displayText: "use_module(library(...))",
371 type: "directive",
372 template: "use_module(library(${Library})).",
373 varTemplates: json{'Library': Template}}, Options) :-
374 ( option(from(From), Options)
375 -> library_template_from(From, Template)
376 ; library_template(library, '.', Template)
377 ).
378
379
380:- dynamic
381 library_template_cache/3. 382
383library_template(Alias, SubDir, Values) :-
384 library_template_cache(Alias, SubDir, Values), !.
385library_template(Alias, SubDir, Values) :-
386 with_mutex(swish_template_hint,
387 ( library_template_cache(Alias, SubDir, Values)
388 -> true
389 ; library_template_no_cache(Alias, SubDir, Values),
390 asserta(library_template_cache(Alias, SubDir, Values))
391 )).
392
393library_template_no_cache(Alias, SubDir, Values) :-
394 library_files(Alias, SubDir, Files, Dirs),
395 maplist(library_sub_template(Alias, SubDir), Dirs, DirTemplates),
396 maplist(plain_file, Files, PlainFiles),
397 flatten([DirTemplates, PlainFiles], Values).
398
399library_sub_template(Alias, Dir0, Dir,
400 json{displayText: DirSlash,
401 template: DirTemplate,
402 varTemplates: VarTemplates
403 }) :-
404 directory_file_path(Dir0, Dir, Dir1),
405 library_template(Alias, Dir1, Templates),
406 Templates \== [], !,
407 string_concat(Dir, "/", DirSlash),
408 string_upper(Dir, UDir),
409 atom_concat(UDir, lib, TemplateVar),
410 format(string(DirTemplate), "~w/${~w}", [Dir, TemplateVar]),
411 VarTemplates = json{}.put(TemplateVar, Templates).
412library_sub_template(_,_,_,[]).
413
414plain_file(File, Plain) :-
415 file_name_extension(Plain, _Ext, File).
416
421
422library_files(Alias, SubDir, Files, Dirs) :-
423 findall(Type-Name, directory_entry(Alias, SubDir, Type, Name), Pairs),
424 keysort(Pairs, Sorted),
425 group_pairs_by_key(Sorted, Grouped),
426 group(directory, Grouped, Dirs),
427 group(prolog, Grouped, Files).
428
429group(Key, Grouped, List) :-
430 ( memberchk(Key-List0, Grouped)
431 -> sort(List0, List)
432 ; List = []
433 ).
434
435directory_entry(Alias, SubDir, Type, Name) :-
436 Spec =.. [Alias, SubDir],
437 absolute_file_name(Spec, Dir,
438 [ file_type(directory),
439 file_errors(fail),
440 solutions(all),
441 access(exist)
442 ]),
443 directory_files(Dir, All),
444 member(Name, All),
445 \+ sub_atom(Name, 0, _, _, '.'),
446 directory_file_path(Dir, Name, Path),
447 file_type(Path, Name, Type).
448
449file_type(_, 'INDEX.pl', _) :- !,
450 fail.
451file_type(Path, _, Type) :-
452 exists_directory(Path), !,
453 Type = directory.
454file_type(_, Name, Type) :-
455 file_name_extension(_, Ext, Name),
456 user:prolog_file_type(Ext, prolog),
457 \+ user:prolog_file_type(Ext, qlf),
458 Type = prolog.
459
464
465library_template_from(From, Template) :-
466 libs_from(From, Libs),
467 lib_template_from(Libs, Template).
468
469lib_template_from(Libs, Template) :-
470 dirs_plain(Libs, Dirs, Plain),
471 keysort(Dirs, Sorted),
472 group_pairs_by_key(Sorted, Grouped),
473 maplist(library_sub_template_from, Grouped, DirTemplates),
474 flatten([DirTemplates, Plain], Template).
475
476dirs_plain([], [], []).
477dirs_plain([[Plain]|T0], Dirs, [Plain|T]) :- !,
478 dirs_plain(T0, Dirs, T).
479dirs_plain([[Dir|Sub]|T0], [Dir-Sub|T], Plain) :-
480 dirs_plain(T0, T, Plain).
481
482libs_from([], []).
483libs_from([library(Lib)|T0], [Segments|T]) :- !,
484 phrase(segments(Lib), Segments),
485 libs_from(T0, T).
486libs_from([_|T0], T) :-
487 libs_from(T0, T).
488
489segments(A/B) --> !, segments(A), segments(B).
490segments(A) --> [A].
491
492segments_to_slash([One], One).
493segments_to_slash(List, Term/Last) :-
494 append(Prefix, [Last], List), !,
495 segments_to_slash(Prefix, Term).
496
497
498library_sub_template_from(Dir-Members,
499 json{displayText: DirSlash,
500 template: DirTemplate,
501 varTemplates: VarTemplates
502 }) :-
503 lib_template_from(Members, Templates),
504 string_concat(Dir, "/", DirSlash),
505 string_upper(Dir, UDir),
506 atom_concat(UDir, lib, TemplateVar),
507 format(string(DirTemplate), "~w/${~w}", [Dir, TemplateVar]),
508 VarTemplates = json{}.put(TemplateVar, Templates).
509
510
514
515imported_library(Module, Library) :-
516 setof(FromModule, imported_from(Module, FromModule), FromModules),
517 member(FromModule, FromModules),
518 module_property(FromModule, file(File)),
519 source_file_property(File, load_context(Module, _Pos, _Opts)),
520 file_name_on_path(File, Library).
521
522imported_from(Module, FromModule) :-
523 current_predicate(Module:Name/Arity),
524 functor(Head, Name, Arity),
525 predicate_property(Module:Head, imported_from(FromModule)).
526
527
528 531
532swish_templates(Template) :-
533 setof(From, visible_lib(swish, From), FromList),
534 swish_templates(Template, [from(FromList)]).
535
536swish_templates(Template, Options) :-
537 library_template(Template, Options).
538swish_templates(Template, _Options) :-
539 rendering_template(Template).
540swish_templates(Templates, Options) :-
541 visible_predicate_templates(swish, Templates, Options).
542
547
548visible_lib(Module, Library) :-
549 imported_library(Module, Lib),
550 ( Lib = library(Name)
551 -> \+ no_autocomplete_module(Name),
552 atomic_list_concat(Segments, /, Name),
553 segments_to_slash(Segments, Path),
554 Library = library(Path)
555 ; Library = Lib
556 ).
557visible_lib(_, Lib) :-
558 visible_lib(Lib).
559
560visible_lib(built_in).
561visible_lib(library(apply)).
562visible_lib(library(aggregate)).
563visible_lib(library(assoc)).
564visible_lib(library(base32)).
565visible_lib(library(base64)).
566visible_lib(library(charsio)).
567visible_lib(library(clpb)).
568visible_lib(library(clpfd)).
569visible_lib(library(codesio)).
570visible_lib(library(coinduction)).
571visible_lib(library(date)).
572visible_lib(library(debug)).
573visible_lib(library(error)).
574visible_lib(library(dif)).
575visible_lib(library(gensym)).
576visible_lib(library(heaps)).
577visible_lib(library(lists)).
578visible_lib(library(occurs)).
579visible_lib(library(option)).
580visible_lib(library(ordsets)).
581visible_lib(library(pairs)).
582visible_lib(library(random)).
583visible_lib(library(rbtrees)).
584visible_lib(library(statistics)).
585visible_lib(library(sort)).
586visible_lib(library(terms)).
587visible_lib(library(ugraph)).
588visible_lib(library(utf8)).
589visible_lib(library(varnumbers)).
590visible_lib(library(when)).
591
594
595
596 599
604
605swish_config:config(templates, Templates) :-
606 findall(Templ, swish_templates(Templ), Templates0),
607 flatten(Templates0, Templates)