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)  2014-2016, 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_template_hint,
   36	  [ visible_predicate/3,	% ?PI, +Module, +Options
   37	    predicate_template/2,	% +PI, -TemplateDict
   38	    visible_predicate_templates/3 %  +Module, +Options, -Templates
   39	  ]).   40:- use_module(library(apply)).   41:- use_module(library(pldoc), []).   42:- use_module(library(pldoc/doc_man)).   43:- use_module(library(pldoc/doc_process)).   44:- use_module(library(pldoc/doc_wiki)).   45:- use_module(library(pldoc/doc_modes)).   46:- use_module(library(http/html_write)).   47:- use_module(library(memfile)).   48:- use_module(library(sgml)).   49:- use_module(library(lists)).   50:- use_module(library(pairs)).   51:- use_module(library(xpath)).   52:- use_module(library(sandbox)).   53:- use_module(library(option)).   54:- use_module(library(filesex)).   55:- use_module(library(error)).   56
   57:- use_module(render).

Generate template hints for CondeMirror

Provide templates for the Prolog template-hinting functionality of the SWISH editor.

To be done
- For which predicates should we generate templates? Should we provide templates on demand?
- What about safely?
- Dedicated template for the rendering support? */
 visible_predicate_templates(+Module, +Options, -Templates) is det
True when Templates is a JSON dict holding autocompletion templates for Module.
   75:- dynamic
   76	cached_templates/3.		% Module, Options, Templates
   77
   78visible_predicate_templates(Module, Templates, Options) :-
   79	cached_templates(Module, Options, Templates), !.
   80visible_predicate_templates(Module, Templates, Options) :-
   81	with_mutex(swish_template_hint,
   82		   visible_predicate_templates_sync(Module, Templates, Options)).
   83
   84visible_predicate_templates_sync(Module, Templates, Options) :-
   85	cached_templates(Module, Options, Templates), !.
   86visible_predicate_templates_sync(Module, Templates, Options) :-
   87	findall(Templ,
   88		(   visible_predicate(PI, Module, Options),
   89		    predicate_template(PI, Templ)
   90		),
   91		Templates0),
   92	assertz(cached_templates(Module, Options, Templates0)),
   93	Templates0 = Templates.
   94
   95clean_template_cache :-
   96	retractall(cached_templates(_,_,_)).
   97
   98:- initialization clean_template_cache.
 visible_predicate(?PI, +Module, +Options) is nondet
True when PI is a plain predicate indicator for a predicate that can be called in Module. Additional options:
safe(+Boolean)
If true, filter out unsafe predicates.
autoload(+Boolean)
Load autoloadable predicates.
  110visible_predicate(PI, Module, Options) :-
  111	option(from(FromList), Options), !,
  112	must_be(list, FromList),
  113	member(From, FromList),
  114	must_be(ground, From),
  115	visible_from(From, PI, Module, Options),
  116	\+ no_template(PI).
  117visible_predicate(PI, Module, Options) :-
  118	PI = Name/Arity,
  119	predicate_property(Module:Head, visible),
  120	autoload(Module:Head, Options),
  121	safe(Module:Head, Options),
  122	functor(Head, Name, Arity),
  123	\+ no_template(PI).
  124
  125no_template(use_module/1).
  126no_template(use_module/2).
  127no_template(use_rendering/1).
  128no_template(use_rendering/2).
 visible_from(+Spec, -PI, +Module, +Options) is nondet
Provide complates from a selected specification. Defined specifications are built_in or the specification of a file, e.g., library(lists).
  136visible_from(built_in, Name/Arity, _Module, Options) :- !,
  137	predicate_property(system:Head, built_in),
  138	functor(Head, Name, Arity),
  139	\+ sub_atom(Name, 0, _, _, $),
  140	safe(system:Head, Options).
  141visible_from(Spec, Name/Arity, _Module, _Options) :-
  142	compound(Spec),
  143	functor(Spec, _, 1),
  144	exists_source(Spec),
  145	xref_public_list(Spec, -,
  146			 [ exports(Exports)
  147			 ]),
  148	member(Name/Arity, Exports).
  149
  150
  151autoload(Pred, Options) :-
  152	option(autoload(false), Options, false), !,
  153	Pred = M:Head,
  154	functor(Head, Name, Arity),
  155	(   current_predicate(M:Name/Arity)
  156	->  \+ ( predicate_property(M:Head, imported_from(LoadModule)),
  157		 no_autocomplete_module(LoadModule)
  158	       )
  159	;   '$find_library'(M, Name, Arity, LoadModule, _Library),
  160	    \+ no_autocomplete_module(LoadModule),
  161	    current_predicate(LoadModule:Name/Arity)
  162	).
  163autoload(_, _).
  164
  165no_autocomplete_module(pce).
  166no_autocomplete_module(pce_principal).
  167no_autocomplete_module(pce_class_template).
  168no_autocomplete_module(pce_dispatch).
  169no_autocomplete_module(pce_expansion).
  170no_autocomplete_module(pce_error).
  171no_autocomplete_module(pce_compatibility_layer).
  172no_autocomplete_module(backward_compatibility).
  173no_autocomplete_module(settings).
  174no_autocomplete_module(quintus).
  175no_autocomplete_module(toplevel_variables).
  176no_autocomplete_module('$qlf').
  177no_autocomplete_module(pldoc).
  178no_autocomplete_module(quasi_quotations).
  179no_autocomplete_module(ssl).
  180no_autocomplete_module(oset).
  181no_autocomplete_module(prolog_colour).
  182no_autocomplete_module(pengines_io).
  183no_autocomplete_module(broadcast).
  184no_autocomplete_module(sgml).
  185no_autocomplete_module(swi_system_utilities).
  186no_autocomplete_module(prolog_metainference).
  187no_autocomplete_module(thread_pool).
 safe(+Goal, +Options) is semidet
True if Goal is sometimes safe. Note that meta-predicates are never immediately safe.
  194safe(Goal, Options) :-
  195	option(safe(true), Options, true), !,
  196	(   predicate_property(Goal, meta_predicate(_))
  197	->  true
  198	;   catch(safe_goal(Goal), _, fail)
  199	).
  200safe(_, _).
 predicate_template(:PI, -Template:json) is semidet
Arguments:
Template- is a dict holding the keys below. Only mode is guaranteed to be present.
mode
String holding the mode-line. Always present.
summary
Summary description.
iso
true if the predicate is an ISO predicate.
determinism
Determinism indicator (if known)
To be done
- Deal with locally redefined predicates, etc.
  217predicate_template(PI, Dict) :-
  218	findall(Pair, predicate_info(PI, Pair), Pairs),
  219	Pairs \== [],
  220	dict_pairs(Dict, json, Pairs).
  221
  222predicate_info(PI, Pair) :-
  223	(   man_predicate_info(PI, Pair)
  224	*-> true
  225	;   pldoc_predicate_info(PI, Pair)
  226	).
 man_predicate_info(+PI, -Pair) is nondet
Extract the mode line from the SWI-Prolog manual.
  232man_predicate_info(PI, Name-Value) :-
  233	pi_head(PI, Head),
  234	strip_module(Head, _, PHead),
  235	functor(PHead, PName, Arity),
  236	phrase(man_page(PName/Arity,
  237			[ no_manual(fail),
  238			  links(false),
  239			  navtree(false)
  240			]), HTML),
  241	setup_call_cleanup(
  242	    new_memory_file(MF),
  243	    ( setup_call_cleanup(
  244		  open_memory_file(MF, write, Out),
  245		  print_html(Out, HTML),
  246		  close(Out)),
  247	      setup_call_cleanup(
  248		  open_memory_file(MF, read, In),
  249		  load_html(stream(In), DOM, [syntax_errors(quiet)]),
  250		  close(In))
  251	    ),
  252	    free_memory_file(MF)),
  253	xpath_chk(DOM, //dt(@class=pubdef), DT),
  254	xpath_chk(DT, a(text), ModeLine0),
  255	normalize_space(string(ModeLine), ModeLine0),
  256	(   atom_string(PName, PString),
  257	    Name-Value = name-PString
  258	;   Name-Value = arity-Arity
  259	;   Name-Value = (mode)-ModeLine
  260	;   once(catch(predicate(PName, Arity, Summary, _, _), _, fail)),
  261	    Name-Value = summary-Summary
  262	;   predicate_property(system:PHead, iso),
  263	    Name-Value = iso-true
  264	;   predicate_property(system:PHead, built_in),
  265	    Name-Value = type-built_in
  266	).
 pldoc_predicate_info(+PI, -ModeLine) is semidet
  270pldoc_predicate_info(PI, Name-Value) :-
  271	pi_head(PI, Head),
  272	strip_module(Head, _, PHead),
  273	functor(PHead, PName, Arity),
  274	implementation_module(Head, Module),
  275	doc_comment(PI, Pos, Summary, Comment), !,
  276	is_structured_comment(Comment, Prefixes),
  277	string_codes(Comment, CommentCodes),
  278	indented_lines(CommentCodes, Prefixes, Lines),
  279	process_modes(Lines, Module, Pos, Modes, _VarNames, _RestLines),
  280	member(mode(Mode,Vars), Modes),
  281	mode_head_det(Mode, ModeHead, Det),
  282	m_same_name_arity(ModeHead, Head),
  283	maplist(bind_var, Vars),
  284	term_string(ModeHead, ModeLine,
  285		    [ quoted(true),
  286		      module(pldoc_modes),
  287		      numbervars(true),
  288		      spacing(next_argument)
  289		    ]),
  290	(   atom_string(PName, PString),
  291	    Name-Value = name-PString
  292	;   Name-Value = arity-Arity
  293	;   Name-Value = (mode)-ModeLine
  294	;   Name-Value = summary-Summary
  295	;   Det \== unknown,
  296	    Name-Value = determinism-Det
  297	).
  298
  299
  300bind_var(Name=Var) :- Var = '$VAR'(Name).
  301
  302mode_head_det(Head is Det, Head, Det) :- !.
  303mode_head_det(Head, Head, unknown).
  304
  305pi_head(Var, _) :-
  306	var(Var), !, instantiation_error(Var).
  307pi_head(M0:T0, M:T) :- !,
  308	strip_module(M0:T0, M, T1),
  309	pi_head(T1, T).
  310pi_head(Name/Arity, Head) :- !,
  311	functor(Head, Name, Arity).
  312pi_head(Name//DCGArity, Head) :-
  313	Arity is DCGArity+2,
  314	functor(Head, Name, Arity).
  315
  316implementation_module(Head, M) :-
  317	predicate_property(Head, imported_from(M0)), !,
  318	M = M0.
  319implementation_module(Head, M) :-
  320	strip_module(user:Head, M, _).
  321
  322m_same_name_arity(H1, H2) :-
  323	strip_module(H1, _, P1),
  324	strip_module(H2, _, P2),
  325	functor(P1, Name, Arity),
  326	functor(P2, Name, Arity).
  327
  328
  329		 /*******************************
  330		 *	     RENDERING		*
  331		 *******************************/
 rendering_template(-Template)
Create a template for the SWISH rendering modules.
  337rendering_template([ json{displayText:  "use_rendering(+Renderer).",
  338			  type:         "directive",
  339			  template:     "use_rendering(${Renderer}).",
  340			  varTemplates: json{'Renderer': Template}},
  341		     json{displayText:  "use_rendering(+Renderer, +Options).",
  342			  type:         "directive",
  343			  template:     "use_rendering(${Renderer}).",
  344			  varTemplates: json{'Renderer': Template}}
  345		   ]) :-
  346	findall(json{displayText: Comment,
  347		     text: Name},
  348		current_renderer(Name, Comment),
  349		Template).
  350
  351
  352		 /*******************************
  353		 *	      LIBRARY		*
  354		 *******************************/
 library_template(-Template, +Options) is det
Produce a template for selecting libraries. By default, this enumerates all Prolog files under the file alias library. If Options includes from(FromList), this is interpreted similar to visible_predicate/3.
  363library_template(json{displayText:  "use_module(library(...))",
  364		      type:         "directive",
  365		      template:     "use_module(library(${Library})).",
  366		      varTemplates: json{'Library': Template}}, Options) :-
  367	(   option(from(From), Options)
  368	->  library_template_from(From, Template)
  369	;   library_template(library, '.', Template)
  370	).
  371
  372
  373:- dynamic
  374	library_template_cache/3.  375
  376library_template(Alias, SubDir, Values) :-
  377	library_template_cache(Alias, SubDir, Values), !.
  378library_template(Alias, SubDir, Values) :-
  379	with_mutex(swish_template_hint,
  380		   (   library_template_cache(Alias, SubDir, Values)
  381		   ->  true
  382		   ;   library_template_no_cache(Alias, SubDir, Values),
  383		       asserta(library_template_cache(Alias, SubDir, Values))
  384		   )).
  385
  386library_template_no_cache(Alias, SubDir, Values) :-
  387	library_files(Alias, SubDir, Files, Dirs),
  388	maplist(library_sub_template(Alias, SubDir), Dirs, DirTemplates),
  389	maplist(plain_file, Files, PlainFiles),
  390	flatten([DirTemplates, PlainFiles], Values).
  391
  392library_sub_template(Alias, Dir0, Dir,
  393		     json{displayText: DirSlash,
  394			  template: DirTemplate,
  395			  varTemplates: VarTemplates
  396			 }) :-
  397	directory_file_path(Dir0, Dir, Dir1),
  398	library_template(Alias, Dir1, Templates),
  399	Templates \== [], !,
  400	string_concat(Dir, "/", DirSlash),
  401	string_upper(Dir, UDir),
  402	atom_concat(UDir, lib, TemplateVar),
  403	format(string(DirTemplate), "~w/${~w}", [Dir, TemplateVar]),
  404	VarTemplates = json{}.put(TemplateVar, Templates).
  405library_sub_template(_,_,_,[]).
  406
  407plain_file(File, Plain) :-
  408	file_name_extension(Plain, _Ext, File).
 library_files(+Alias, +SubDir, -Files, -Dirs)
True when Files is a list of files that can be loaded from Alias(SubDir) and Dirs is a list of sub directories of Files.
  415library_files(Alias, SubDir, Files, Dirs) :-
  416	findall(Type-Name, directory_entry(Alias, SubDir, Type, Name), Pairs),
  417	keysort(Pairs, Sorted),
  418	group_pairs_by_key(Sorted, Grouped),
  419	group(directory, Grouped, Dirs),
  420	group(prolog, Grouped, Files).
  421
  422group(Key, Grouped, List) :-
  423	(   memberchk(Key-List0, Grouped)
  424	->  sort(List0, List)
  425	;   List = []
  426	).
  427
  428directory_entry(Alias, SubDir, Type, Name) :-
  429	Spec =.. [Alias, SubDir],
  430	absolute_file_name(Spec, Dir,
  431			   [ file_type(directory),
  432			     file_errors(fail),
  433			     solutions(all),
  434			     access(exist)
  435			   ]),
  436	directory_files(Dir, All),
  437	member(Name, All),
  438	\+ sub_atom(Name, 0, _, _, '.'),
  439	directory_file_path(Dir, Name, Path),
  440	file_type(Path, Name, Type).
  441
  442file_type(_, 'INDEX.pl', _) :- !,
  443	fail.
  444file_type(Path, _, Type) :-
  445	exists_directory(Path), !,
  446	Type = directory.
  447file_type(_, Name, Type) :-
  448	file_name_extension(_, Ext, Name),
  449	user:prolog_file_type(Ext, prolog),
  450	\+ user:prolog_file_type(Ext, qlf),
  451	Type = prolog.
 library_template_from(+From:list, -Template) is det
As library_template/1, but build the completion list from a given set of libraries.
  458library_template_from(From, Template) :-
  459	libs_from(From, Libs),
  460	lib_template_from(Libs, Template).
  461
  462lib_template_from(Libs, Template) :-
  463	dirs_plain(Libs, Dirs, Plain),
  464	keysort(Dirs, Sorted),
  465	group_pairs_by_key(Sorted, Grouped),
  466	maplist(library_sub_template_from, Grouped, DirTemplates),
  467	flatten([DirTemplates, Plain], Template).
  468
  469dirs_plain([], [], []).
  470dirs_plain([[Plain]|T0], Dirs, [Plain|T]) :- !,
  471	dirs_plain(T0, Dirs, T).
  472dirs_plain([[Dir|Sub]|T0], [Dir-Sub|T], Plain) :-
  473	dirs_plain(T0, T, Plain).
  474
  475libs_from([], []).
  476libs_from([library(Lib)|T0], [Segments|T]) :- !,
  477	phrase(segments(Lib), Segments),
  478	libs_from(T0, T).
  479libs_from([_|T0], T) :-
  480	libs_from(T0, T).
  481
  482segments(A/B) --> !, segments(A), segments(B).
  483segments(A)   --> [A].
  484
  485segments_to_slash([One], One).
  486segments_to_slash(List, Term/Last) :-
  487	append(Prefix, [Last], List), !,
  488	segments_to_slash(Prefix, Term).
  489
  490
  491library_sub_template_from(Dir-Members,
  492			  json{displayText: DirSlash,
  493			       template: DirTemplate,
  494			       varTemplates: VarTemplates
  495			      }) :-
  496	lib_template_from(Members, Templates),
  497	string_concat(Dir, "/", DirSlash),
  498	string_upper(Dir, UDir),
  499	atom_concat(UDir, lib, TemplateVar),
  500	format(string(DirTemplate), "~w/${~w}", [Dir, TemplateVar]),
  501	VarTemplates = json{}.put(TemplateVar, Templates).
 imported_library(+Module, -Library) is nondet
True when Library is imported into Module.
  508imported_library(Module, Library) :-
  509	setof(FromModule, imported_from(Module, FromModule), FromModules),
  510	member(FromModule, FromModules),
  511	module_property(FromModule, file(File)),
  512	source_file_property(File, load_context(Module, _Pos, _Opts)),
  513	file_name_on_path(File, Library).
  514
  515imported_from(Module, FromModule) :-
  516	current_predicate(Module:Name/Arity),
  517	functor(Head, Name, Arity),
  518	predicate_property(Module:Head, imported_from(FromModule)).
  519
  520
  521		 /*******************************
  522		 *       COLLECT TEMPLATES	*
  523		 *******************************/
  524
  525swish_templates(Template) :-
  526	setof(From, visible_lib(swish, From), FromList),
  527	swish_templates(Template, [from(FromList)]).
  528
  529swish_templates(Template, Options) :-
  530	library_template(Template, Options).
  531swish_templates(Template, _Options) :-
  532	rendering_template(Template).
  533swish_templates(Templates, Options) :-
  534	visible_predicate_templates(swish, Templates, Options).
 visible_lib(+Module, -Lib) is nondet
Enumerate modules imported into Module and generally useful modules.
  541visible_lib(Module, Library) :-
  542	imported_library(Module, Lib),
  543	(   Lib = library(Name)
  544	->  \+ no_autocomplete_module(Name),
  545	    atomic_list_concat(Segments, /, Name),
  546	    segments_to_slash(Segments, Path),
  547	    Library = library(Path)
  548	;   Library = Lib
  549	).
  550visible_lib(_, Lib) :-
  551	visible_lib(Lib).
  552
  553visible_lib(built_in).
  554visible_lib(library(apply)).
  555visible_lib(library(aggregate)).
  556visible_lib(library(assoc)).
  557visible_lib(library(base32)).
  558visible_lib(library(base64)).
  559visible_lib(library(charsio)).
  560visible_lib(library(clpb)).
  561visible_lib(library(clpfd)).
  562visible_lib(library(codesio)).
  563visible_lib(library(coinduction)).
  564visible_lib(library(date)).
  565visible_lib(library(debug)).
  566visible_lib(library(error)).
  567visible_lib(library(dif)).
  568visible_lib(library(gensym)).
  569visible_lib(library(heaps)).
  570visible_lib(library(lists)).
  571visible_lib(library(occurs)).
  572visible_lib(library(option)).
  573visible_lib(library(ordsets)).
  574visible_lib(library(pairs)).
  575visible_lib(library(random)).
  576visible_lib(library(rbtrees)).
  577visible_lib(library(statistics)).
  578visible_lib(library(sort)).
  579visible_lib(library(terms)).
  580visible_lib(library(ugraph)).
  581visible_lib(library(utf8)).
  582visible_lib(library(varnumbers)).
  583visible_lib(library(when)).
  584
  585%visible_lib(library(semweb/rdf_db)).
  586%visible_lib(library(semweb/rdfs)).
  587
  588
  589		 /*******************************
  590		 *	    SWISH CONFIG	*
  591		 *******************************/
 swish_config:config(-Name, -Styles) is det
Provides the object config.swish.templates, a JSON object that provides the templates for hinting in CodeMirror.
  598swish_config:config(templates, Templates) :-
  599	findall(Templ, swish_templates(Templ), Templates0),
  600	flatten(Templates0, Templates)