38
39:- module(swish_template_hint,
40 [ visible_predicate/3, 41 predicate_template/2, 42 visible_predicate_templates/3 43 ]). 44:- use_module(library(apply)). 45:- use_module(library(pldoc), []). 46:- use_module(library(pldoc/doc_man)). 47:- use_module(library(pldoc/doc_process)). 48:- use_module(library(pldoc/doc_wiki)). 49:- use_module(library(pldoc/doc_modes)). 50:- use_module(library(doc_http)). 51:- use_module(library(http/html_write)). 52:- use_module(library(memfile)). 53:- use_module(library(sgml)). 54:- use_module(library(lists)). 55:- use_module(library(pairs)). 56:- use_module(library(xpath)). 57:- use_module(library(sandbox)). 58:- use_module(library(option)). 59:- use_module(library(filesex)). 60:- use_module(library(error)). 61
62:- use_module(render). 63:- use_module(highlight).
76:- if(current_predicate(doc_enable/1)). 77:- initialization(doc_enable(true)). 78:- endif.
85:- dynamic
86 cached_templates/3. 87
88visible_predicate_templates(Module, Templates, Options) :-
89 cached_templates(Module, Options, Templates), !.
90visible_predicate_templates(Module, Templates, Options) :-
91 with_mutex(swish_template_hint,
92 visible_predicate_templates_sync(Module, Templates, Options)).
93
94visible_predicate_templates_sync(Module, Templates, Options) :-
95 cached_templates(Module, Options, Templates), !.
96visible_predicate_templates_sync(Module, Templates, Options) :-
97 findall(Templ,
98 ( visible_predicate(PI, Module, Options),
99 predicate_template(PI, Templ)
100 ),
101 Templates0),
102 assertz(cached_templates(Module, Options, Templates0)),
103 Templates0 = Templates.
104
105clean_template_cache :-
106 retractall(cached_templates(_,_,_)).
107
108:- initialization clean_template_cache.
120visible_predicate(PI, Module, Options) :-
121 option(from(FromList), Options), !,
122 must_be(list, FromList),
123 member(From, FromList),
124 must_be(ground, From),
125 visible_from(From, PI, Module, Options),
126 \+ no_template(PI).
127visible_predicate(PI, Module, Options) :-
128 PI = Name/Arity,
129 predicate_property(Module:Head, visible),
130 do_autoload(Module:Head, Options),
131 safe(Module:Head, Options),
132 functor(Head, Name, Arity),
133 \+ no_template(PI).
134
135no_template(use_module/1).
136no_template(use_module/2).
137no_template(use_rendering/1).
138no_template(use_rendering/2).
146visible_from(built_in, Name/Arity, _Module, Options) :- !,
147 predicate_property(system:Head, built_in),
148 functor(Head, Name, Arity),
149 \+ sub_atom(Name, 0, _, _, $),
150 safe(system:Head, Options).
151visible_from(Spec, Name/Arity, _Module, _Options) :-
152 compound(Spec),
153 functor(Spec, _, 1),
154 exists_source(Spec),
155 xref_public_list(Spec, -,
156 [ exports(Exports)
157 ]),
158 member(Name/Arity, Exports).
159
160
161do_autoload(Pred, Options) :-
162 option(autoload(false), Options, false), !,
163 Pred = M:Head,
164 functor(Head, Name, Arity),
165 ( current_predicate(M:Name/Arity)
166 -> \+ ( predicate_property(M:Head, imported_from(LoadModule)),
167 no_autocomplete_module(LoadModule)
168 )
169 ; '$find_library'(M, Name, Arity, LoadModule, _Library),
170 \+ no_autocomplete_module(LoadModule),
171 current_predicate(LoadModule:Name/Arity)
172 ).
173do_autoload(_, _).
174
175no_autocomplete_module(pce).
176no_autocomplete_module(pce_principal).
177no_autocomplete_module(pce_class_template).
178no_autocomplete_module(pce_dispatch).
179no_autocomplete_module(pce_expansion).
180no_autocomplete_module(pce_error).
181no_autocomplete_module(pce_compatibility_layer).
182no_autocomplete_module(backward_compatibility).
183no_autocomplete_module(settings).
184no_autocomplete_module(quintus).
185no_autocomplete_module(toplevel_variables).
186no_autocomplete_module('$qlf').
187no_autocomplete_module(pldoc).
188no_autocomplete_module(quasi_quotations).
189no_autocomplete_module(ssl).
190no_autocomplete_module(oset).
191no_autocomplete_module(prolog_colour).
192no_autocomplete_module(pengines_io).
193no_autocomplete_module(broadcast).
194no_autocomplete_module(sgml).
195no_autocomplete_module(swi_system_utilities).
196no_autocomplete_module(prolog_metainference).
197no_autocomplete_module(thread_pool).
204safe(Goal, Options) :-
205 option(safe(true), Options, true), !,
206 ( predicate_property(Goal, meta_predicate(_))
207 -> true
208 ; catch(safe_goal(Goal), _, fail)
209 ).
210safe(_, _).
227predicate_template(PI, Dict) :-
228 findall(Pair, predicate_info(PI, Pair), Pairs),
229 Pairs \== [],
230 dict_pairs(Dict, json, Pairs).
231
232predicate_info(PI, Pair) :-
233 ( man_predicate_info(PI, Pair)
234 *-> true
235 ; pldoc_predicate_info(PI, Pair)
236 ).
242man_predicate_info(PI, Name-Value) :-
243 pi_head(PI, Head),
244 strip_module(Head, _, PHead),
245 functor(PHead, PName, Arity),
246 phrase(man_page(PName/Arity,
247 [ no_manual(fail),
248 links(false),
249 navtree(false)
250 ]), HTML),
251 setup_call_cleanup(
252 new_memory_file(MF),
253 ( setup_call_cleanup(
254 open_memory_file(MF, write, Out),
255 print_html(Out, HTML),
256 close(Out)),
257 setup_call_cleanup(
258 open_memory_file(MF, read, In),
259 load_html(stream(In), DOM, [syntax_errors(quiet)]),
260 close(In))
261 ),
262 free_memory_file(MF)),
263 xpath_chk(DOM, //dt(@class=pubdef), DT),
264 xpath_chk(DT, a(text), ModeLine0),
265 normalize_space(string(ModeLine), ModeLine0),
266 ( atom_string(PName, PString),
267 Name-Value = name-PString
268 ; Name-Value = arity-Arity
269 ; Name-Value = (mode)-ModeLine
270 ; once(man_predicate_summary(PName/Arity, Summary)),
271 Name-Value = summary-Summary
272 ; predicate_property(system:PHead, iso),
273 Name-Value = iso-true
274 ; predicate_property(system:PHead, built_in),
275 Name-Value = type-built_in
276 ).
280pldoc_predicate_info(PI, Name-Value) :-
281 pi_head(PI, Head),
282 strip_module(Head, _, PHead),
283 functor(PHead, PName, Arity),
284 implementation_module(Head, Module),
285 doc_comment(PI, Pos, Summary, Comment), !,
286 is_structured_comment(Comment, Prefixes),
287 string_codes(Comment, CommentCodes),
288 indented_lines(CommentCodes, Prefixes, Lines),
289 process_modes(Lines, Module, Pos, Modes, _VarNames, _RestLines),
290 member(mode(Mode,Vars), Modes),
291 mode_head_det(Mode, ModeHead, Det),
292 m_same_name_arity(ModeHead, Head),
293 maplist(bind_var, Vars),
294 term_string(ModeHead, ModeLine,
295 [ quoted(true),
296 module(pldoc_modes),
297 numbervars(true),
298 spacing(next_argument)
299 ]),
300 ( atom_string(PName, PString),
301 Name-Value = name-PString
302 ; Name-Value = arity-Arity
303 ; Name-Value = (mode)-ModeLine
304 ; Name-Value = summary-Summary
305 ; Det \== unknown,
306 Name-Value = determinism-Det
307 ).
308
309
310bind_var(Name=Var) :- Var = '$VAR'(Name).
311
312mode_head_det(Head is Det, Head, Det) :- !.
313mode_head_det(Head, Head, unknown).
314
315pi_head(Var, _) :-
316 var(Var), !, instantiation_error(Var).
317pi_head(M0:T0, M:T) :- !,
318 strip_module(M0:T0, M, T1),
319 pi_head(T1, T).
320pi_head(Name/Arity, Head) :- !,
321 functor(Head, Name, Arity).
322pi_head(Name//DCGArity, Head) :-
323 Arity is DCGArity+2,
324 functor(Head, Name, Arity).
325
326implementation_module(Head, M) :-
327 predicate_property(Head, imported_from(M0)), !,
328 M = M0.
329implementation_module(Head, M) :-
330 strip_module(user:Head, M, _).
331
332m_same_name_arity(H1, H2) :-
333 strip_module(H1, _, P1),
334 strip_module(H2, _, P2),
335 functor(P1, Name, Arity),
336 functor(P2, Name, Arity).
337
338
339
348trill_template([ json{displayText: "prob_instanceOf(+Class, +Individual, -Prob).",
349 type: "directive",
350 template: "prob_instanceOf(${Class},${Individual},Prob).",
351 varTemplates: json{'TRILL-Query': Template}},
352
353 json{displayText: "prob_property_value(+Property, +Individual1, +Individual2, -Prob).",
354 type: "directive",
355 template: "prob_property_value(${Property},${Individual1},${Individual2},Prob).",
356 varTemplates: json{'TRILL-Query': Template}},
357
358 json{displayText: "prob_sub_class(+Class1, +Class2, -Prob).",
359 type: "directive",
360 template: "prob_sub_class(${Class1},${Class2},Prob).",
361 varTemplates: json{'TRILL-Query': Template}},
362
363 json{displayText: "prob_unsat(+ClassExpression, -Prob).",
364 type: "directive",
365 template: "prob_unsat(${ClassExpression},Prob).",
366 varTemplates: json{'TRILL-Query': Template}},
367
368 json{displayText: "prob_inconsistent_theory(-Prob).",
369 type: "directive",
370 template: "prob_inconsistent_theory(Prob).",
371 varTemplates: json{'TRILL-Query': Template}},
372
373 json{displayText: "instanceOf(+Class, +Individual, -Expl).",
374 type: "directive",
375 template: "instanceOf(${Class},${Individual},Expl).",
376 varTemplates: json{'TRILL-Query': Template}},
377
378 json{displayText: "property_value(+Property, +Individual1, +Individual2, -Expl).",
379 type: "directive",
380 template: "property_value(${Property},${Individual1},${Individual2},Expl).",
381 varTemplates: json{'TRILL-Query': Template}},
382
383 json{displayText: "sub_class(+Class1, +Class2, -Expl).",
384 type: "directive",
385 template: "sub_class(${Class1},${Class2},Expl).",
386 varTemplates: json{'TRILL-Query': Template}},
387
388 json{displayText: "unsat(+ClassExpression, -Expl).",
389 type: "directive",
390 template: "unsat(${ClassExpression},Expl).",
391 varTemplates: json{'TRILL-Query': Template}},
392
393 json{displayText: "inconsistent_theory(-Expl).",
394 type: "directive",
395 template: "inconsistent_theory(Expl).",
396 varTemplates: json{'TRILL-Query': Template}},
397
398 json{displayText: "instanceOf(+Class, +Individual, -Expl, +Options).",
399 type: "directive",
400 template: "instanceOf(${Class},${Individual},Expl,[${Options}]).",
401 varTemplates: json{'TRILL-Query': Template}},
402
403 json{displayText: "property_value(+Property, +Individual1, +Individual2, -Expl, +Options).",
404 type: "directive",
405 template: "property_value(${Property},${Individual1},${Individual2},Expl,[${Options}]).",
406 varTemplates: json{'TRILL-Query': Template}},
407
408 json{displayText: "sub_class(+Class1, +Class2, -Expl, +Options).",
409 type: "directive",
410 template: "sub_class(${Class1},${Class2},Expl,[${Options}]).",
411 varTemplates: json{'TRILL-Query': Template}},
412
413 json{displayText: "unsat(+ClassExpression, -Expl, +Options).",
414 type: "directive",
415 template: "unsat(${ClassExpression},Expl,[${Options}]).",
416 varTemplates: json{'TRILL-Query': Template}},
417
418 json{displayText: "inconsistent_theory(-Expl, +Options).",
419 type: "directive",
420 template: "inconsistent_theory(Expl,[${Options}]).",
421 varTemplates: json{'TRILL-Query': Template}},
422
423 json{displayText: "instanceOf(+Class, +Individual).",
424 type: "directive",
425 template: "instanceOf(${Class},${Individual}).",
426 varTemplates: json{'TRILL-Query': Template}},
427
428 json{displayText: "property_value(+Property, +Individual1, +Individual2).",
429 type: "directive",
430 template: "property_value(${Property},${Individual1},${Individual2}).",
431 varTemplates: json{'TRILL-Query': Template}},
432
433 json{displayText: "sub_class(+Class1, +Class2).",
434 type: "directive",
435 template: "sub_class(${Class1},${Class2}).",
436 varTemplates: json{'TRILL-Query': Template}},
437
438 json{displayText: "unsat(+ClassExpression).",
439 type: "directive",
440 template: "unsat(${ClassExpression}).",
441 varTemplates: json{'TRILL-Query': Template}},
442
443 json{displayText: "inconsistent_theory.",
444 type: "directive",
445 template: "inconsistent_theory.",
446 varTemplates: json{'TRILL-Query': Template}}
447 ]) :-
448 findall(json{displayText: Comment,
449 text: Name},
450 current_renderer(Name, Comment),
451 Template).
452
453
454
462rendering_template([ json{displayText: "use_rendering(+Renderer).",
463 type: "directive",
464 template: "use_rendering(${Renderer}).",
465 varTemplates: json{'Renderer': Template}},
466 json{displayText: "use_rendering(+Renderer, +Options).",
467 type: "directive",
468 template: "use_rendering(${Renderer}).",
469 varTemplates: json{'Renderer': Template}}
470 ]) :-
471 findall(json{displayText: Comment,
472 text: Name},
473 current_renderer(Name, Comment),
474 Template).
475
476
477
488library_template(json{displayText: "use_module(library(...))",
489 type: "directive",
490 template: "use_module(library(${Library})).",
491 varTemplates: json{'Library': Template}}, Options) :-
492 ( option(from(From), Options)
493 -> library_template_from(From, Template)
494 ; library_template(library, '.', Template)
495 ).
496
497
498:- dynamic
499 library_template_cache/3. 500
501library_template(Alias, SubDir, Values) :-
502 library_template_cache(Alias, SubDir, Values), !.
503library_template(Alias, SubDir, Values) :-
504 with_mutex(swish_template_hint,
505 ( library_template_cache(Alias, SubDir, Values)
506 -> true
507 ; library_template_no_cache(Alias, SubDir, Values),
508 asserta(library_template_cache(Alias, SubDir, Values))
509 )).
510
511library_template_no_cache(Alias, SubDir, Values) :-
512 library_files(Alias, SubDir, Files, Dirs),
513 maplist(library_sub_template(Alias, SubDir), Dirs, DirTemplates),
514 maplist(plain_file, Files, PlainFiles),
515 flatten([DirTemplates, PlainFiles], Values).
516
517library_sub_template(Alias, Dir0, Dir,
518 json{displayText: DirSlash,
519 template: DirTemplate,
520 varTemplates: VarTemplates
521 }) :-
522 directory_file_path(Dir0, Dir, Dir1),
523 library_template(Alias, Dir1, Templates),
524 Templates \== [], !,
525 string_concat(Dir, "/", DirSlash),
526 string_upper(Dir, UDir),
527 atom_concat(UDir, lib, TemplateVar),
528 format(string(DirTemplate), "~w/${~w}", [Dir, TemplateVar]),
529 VarTemplates = json{}.put(TemplateVar, Templates).
530library_sub_template(_,_,_,[]).
531
532plain_file(File, Plain) :-
533 file_name_extension(Plain, _Ext, File).
540library_files(Alias, SubDir, Files, Dirs) :-
541 findall(Type-Name, directory_entry(Alias, SubDir, Type, Name), Pairs),
542 keysort(Pairs, Sorted),
543 group_pairs_by_key(Sorted, Grouped),
544 group(directory, Grouped, Dirs),
545 group(prolog, Grouped, Files).
546
547group(Key, Grouped, List) :-
548 ( memberchk(Key-List0, Grouped)
549 -> sort(List0, List)
550 ; List = []
551 ).
552
553directory_entry(Alias, SubDir, Type, Name) :-
554 Spec =.. [Alias, SubDir],
555 absolute_file_name(Spec, Dir,
556 [ file_type(directory),
557 file_errors(fail),
558 solutions(all),
559 access(exist)
560 ]),
561 directory_files(Dir, All),
562 member(Name, All),
563 \+ sub_atom(Name, 0, _, _, '.'),
564 directory_file_path(Dir, Name, Path),
565 file_type(Path, Name, Type).
566
567file_type(_, 'INDEX.pl', _) :- !,
568 fail.
569file_type(Path, _, Type) :-
570 exists_directory(Path), !,
571 Type = directory.
572file_type(_, Name, Type) :-
573 file_name_extension(_, Ext, Name),
574 user:prolog_file_type(Ext, prolog),
575 \+ user:prolog_file_type(Ext, qlf),
576 Type = prolog.
583library_template_from(From, Template) :-
584 libs_from(From, Libs),
585 lib_template_from(Libs, Template).
586
587lib_template_from(Libs, Template) :-
588 dirs_plain(Libs, Dirs, Plain),
589 keysort(Dirs, Sorted),
590 group_pairs_by_key(Sorted, Grouped),
591 maplist(library_sub_template_from, Grouped, DirTemplates),
592 flatten([DirTemplates, Plain], Template).
593
594dirs_plain([], [], []).
595dirs_plain([[Plain]|T0], Dirs, [Plain|T]) :- !,
596 dirs_plain(T0, Dirs, T).
597dirs_plain([[Dir|Sub]|T0], [Dir-Sub|T], Plain) :-
598 dirs_plain(T0, T, Plain).
599
600libs_from([], []).
601libs_from([library(Lib)|T0], [Segments|T]) :- !,
602 phrase(segments(Lib), Segments),
603 libs_from(T0, T).
604libs_from([_|T0], T) :-
605 libs_from(T0, T).
606
607segments(A/B) --> !, segments(A), segments(B).
608segments(A) --> [A].
609
610segments_to_slash([One], One).
611segments_to_slash(List, Term/Last) :-
612 append(Prefix, [Last], List), !,
613 segments_to_slash(Prefix, Term).
614
615
616library_sub_template_from(Dir-Members,
617 json{displayText: DirSlash,
618 template: DirTemplate,
619 varTemplates: VarTemplates
620 }) :-
621 lib_template_from(Members, Templates),
622 string_concat(Dir, "/", DirSlash),
623 string_upper(Dir, UDir),
624 atom_concat(UDir, lib, TemplateVar),
625 format(string(DirTemplate), "~w/${~w}", [Dir, TemplateVar]),
626 VarTemplates = json{}.put(TemplateVar, Templates).
633imported_library(Module, Library) :-
634 setof(FromModule, imported_from(Module, FromModule), FromModules),
635 member(FromModule, FromModules),
636 module_property(FromModule, file(File)),
637 source_file_property(File, load_context(Module, _Pos, _Opts)),
638 file_name_on_path(File, Library).
639
640imported_from(Module, FromModule) :-
641 current_predicate(Module:Name/Arity),
642 functor(Head, Name, Arity),
643 predicate_property(Module:Head, imported_from(FromModule)).
644
645
646 649
650swish_templates(Template) :-
651 setof(From, visible_lib(swish, From), FromList),
652 swish_templates(Template, [from(FromList)]).
653
654swish_templates(Template, _Options) :-
655 trill_template(Template).
656swish_templates(Template, Options) :-
657 library_template(Template, Options).
658swish_templates(Template, _Options) :-
659 rendering_template(Template).
660swish_templates(Templates, Options) :-
661 visible_predicate_templates(swish, Templates, Options).
668visible_lib(Module, Library) :-
669 imported_library(Module, Lib),
670 ( Lib = library(Name)
671 -> \+ no_autocomplete_module(Name),
672 atomic_list_concat(Segments, /, Name),
673 segments_to_slash(Segments, Path),
674 Library = library(Path)
675 ; Library = Lib
676 ).
677visible_lib(_, Lib) :-
678 visible_lib(Lib).
679
680visible_lib(built_in).
681visible_lib(library(apply)).
682visible_lib(library(aggregate)).
683visible_lib(library(assoc)).
684visible_lib(library(base32)).
685visible_lib(library(base64)).
686visible_lib(library(charsio)).
687visible_lib(library(clpb)).
688visible_lib(library(clpfd)).
689visible_lib(library(codesio)).
690visible_lib(library(coinduction)).
691visible_lib(library(date)).
692visible_lib(library(debug)).
693visible_lib(library(error)).
694visible_lib(library(dif)).
695visible_lib(library(gensym)).
696visible_lib(library(heaps)).
697visible_lib(library(lists)).
698visible_lib(library(occurs)).
699visible_lib(library(option)).
700visible_lib(library(ordsets)).
701visible_lib(library(pairs)).
702visible_lib(library(random)).
703visible_lib(library(rbtrees)).
704visible_lib(library(statistics)).
705visible_lib(library(sort)).
706visible_lib(library(terms)).
707visible_lib(library(ugraph)).
708visible_lib(library(utf8)).
709visible_lib(library(varnumbers)).
710visible_lib(library(when)).
711
714
715
716
725swish_config:config(templates, Templates) :-
726 findall(Templ, swish_templates(Templ), Templates0),
727 flatten(Templates0, Templates)
Generate template hints for CondeMirror
Provide templates for the Prolog template-hinting functionality of the SWISH editor.