1:- module(_,[
2 loaded_kp/1, all_kps_loaded/0, all_kps_loaded/1, kp_dir/1, taxkb_dir/1, kp_location/3, kp/1, must_succeed/2, must_succeed/1,
3 shouldMapModule/2, module_api_hack/1, moduleMapping/2, myDeclaredModule/1, system_predicate/1,
4 discover_kps_in_dir/1, discover_kps_in_dir/0, discover_kps_gitty/0, setup_kp_modules/0, load_kps/0,
5 load_gitty_files/1, load_gitty_files/0, save_gitty_files/1, save_gitty_files/0, delete_gitty_file/1, update_gitty_file/3,
6 xref_all/0, xref_clean/0, print_kp_predicates/0, print_kp_predicates/1, reset_errors/0, my_xref_defined/3, url_simple/2,
7 kp_predicate_mention/3, predicate_literal/2,load_named_file/3,
8 edit_kp/1, swish_editor_path/2, knowledgePagesGraph/1, knowledgePagesGraph/2]). 9
10:- use_module(library(prolog_xref)). 11:- use_module(library(broadcast)). 12
13:- multifile prolog:message//1. 14
15:- dynamic kp_dir/1, taxkb_dir/1. 16:- prolog_load_context(directory, D),
17 retractall(taxkb_dir(_)), assert(taxkb_dir(D)),
18 retractall(kp_dir(_)), atomic_list_concat([D,'/kb'], KD), assert(kp_dir(KD)),
19 print_message(informational,"KB directory is ~a"-[KD]).
28:- dynamic kp_location/4. 29kp_location(URL,File,InGitty) :- kp_location(URL,File,_,InGitty).
30
31kp(URL_) :-
32 (nonvar(URL_) -> atom_string(URL,URL_);URL=URL_),
33 kp_location(URL,_,_).
37discover_kps_in_dir(Dir) :-
38 retractall(kp_location(_,_,_,false)),
39 forall(directory_member(Dir,File,[extensions([pl])]), (
40 time_file(File,Modified),
41 open(File,read,In),
42 process_file(In,File,Modified,false)
43 )).
44
46discover_kps_in_dir :-
47 kp_dir(D), discover_kps_in_dir(D).
48
49process_file(In,File,Modified,InGitty) :-
50 must_be(boolean,InGitty),
51 setup_call_cleanup( true, (
52 process_terms(In, LastTerm),
53 54 (LastTerm=(:-module(Name,_)) -> (
55 ((kp_location(Name,PreviousFile,PreviousMod,InGitty), PreviousMod>=Modified) ->
56 print_message(warning,ignored_older_module(Name,PreviousFile,File)) ;
57 (
58 (kp_location(Name,PreviousFile,_,InGitty) ->
59 print_message(warning,using_newer_module(Name,PreviousFile,File))
60 ; true),
61 retractall(kp_location(Name,_,_,InGitty)),
62 assert(kp_location(Name,File,Modified,InGitty)),
63 64 (current_module(Name) -> load_named_file(File,Name,InGitty) ; true)
65 ))
66 ); true)
67 ), close(In)).
68
69prolog:message(ignored_older_module(Module,PreviousFile,File)) -->
70 ['Ignored older file ~a for module ~w; sticking to ~a'-[File,Module,PreviousFile]].
71prolog:message(using_newer_module(Module,PreviousFile,File)) -->
72 ['Forgot older file ~a for module ~w; using instead ~a'-[PreviousFile,Module,File]].
73
74process_terms(In,Term) :- 75 76 read_term(In, Term, [syntax_errors(fail)]),
77 ( Term==end_of_file, ! ;
78 Term= (:- module(URL,_)), is_absolute_url(URL), ! ;
79 true
80 81 ).
82
83
84declare_our_metas(Module) :-
85 Module:meta_predicate(mainGoal(0,+)),
86 Module:meta_predicate(on(0,?)),
87 Module:meta_predicate(because(0,-)).
88
90load_named_file(File,Module,InGittyStorage) :-
91 load_named_file_(File,Module,InGittyStorage),
92 kp_file_modified(Module,Modified,InGittyStorage),
93 retractall(kp_location(Module,File,_,InGittyStorage)),
94 assert(kp_location(Module,File,Modified,InGittyStorage)),
95 (xref_source(Module,[silent(true)]) -> true ; print_message(warning,"failed xref_source"-[])).
96
97load_named_file_(File,Module,true) :- !,
98 99 use_gitty_file(Module:File,[).
100load_named_file_(File,Module,false) :-
101 load_files(File,[module(Module)]).
102
103load_kps :-
104 forall(kp_location(URL,File,InGitty), (
105 load_named_file(File,URL,InGitty)
106 )).
107
108setup_kp_modules :- forall(kp(M), setup_kp_module(M) ).
109
110setup_kp_module(M) :-
111 M:discontiguous((if)/2),
112 M:discontiguous((on)/2),
113 M:discontiguous((because)/2),
114 M:discontiguous(question/2), M:discontiguous(question/3),
115 declare_our_metas(M).
116
117all_kps_loaded :- all_kps_loaded(_).
118
119all_kps_loaded(KP):-
120 print_message(informational,"Loading Knowledge Page(s)..(~w)"-[KP]),
121 forall(kp(KP),loaded_kp(KP)).
122
123:- thread_local module_api_hack/1.
128loaded_kp(Name) :- module_api_hack(Name), !.
129loaded_kp(Name) :- must_be(nonvar,Name), shouldMapModule(_,Name), !. 130loaded_kp(Name) :- \+ kp_location(Name,_,_), !,
131 (\+ reported_missing_kp(Name) -> (
132 assert(reported_missing_kp(Name)), print_message(error,"Unknown knowledge page: ~w"-[Name]))
133 ; true),
134 fail.
135loaded_kp(Name) :- 136 module_property(Name,last_modified_generation(T)), T>0,
137 !,
138 once(( kp_file_modified(Name,FT,InGitty), kp_location(Name,File,LastModified,InGitty) )),
139 (FT>LastModified -> (
140 load_named_file(File,Name,InGitty),
141 print_message(informational,"Reloaded ~w"-[Name])
142 ) ; true).
143loaded_kp(Name) :- kp_location(Name,File,InGitty), !, 144 load_named_file(File,Name,InGitty),
145 (\+ reported_loaded_kp(Name) -> (
146 print_message(informational,loaded(Name,File)), assert(reported_loaded_kp(Name)))
147 ; true).
148loaded_kp(Name) :-
149 \+ reported_missing_kp(Name),
150 print_message(error,no_kp(Name)),
151 assert(reported_missing_kp(Name)), fail.
152
153kp_file_modified(Name,Time,InGitty) :-
154 kp_location(Name,File,InGitty),
155 (InGitty==true -> (storage_meta_data(File, Meta), Time=Meta.time) ; time_file(File,Time)).
156
157
158:-thread_local reported_missing_kp/1. 159:-thread_local reported_loaded_kp/1. 160
161reset_errors :-
162 retractall(reported_missing_kp(_)), retractall(reported_loaded_kp(_)).
163
164prolog:message(loaded(Module,Path)) --> ['Loaded ~w from ~a'-[Module,Path]].
165
166
168:- multifile
169 prolog:xref_source_identifier/2,
170 prolog:xref_open_source/2,
171 prolog:xref_close_source/2,
172 prolog:xref_source_time/2,
173 prolog:meta_goal/2. 174
175prolog:xref_source_identifier(URL, URL) :- kp_location(URL,_,_).
176
177prolog:xref_open_source(URL, Stream) :-
178 kp_location(URL,File,InGitty),
179 (InGitty==true -> (storage_file(File,Data,_Meta), open_string(Data, Stream))
180 ; (open(File,read,Stream))).
181
182prolog:xref_close_source(_, Stream) :-
183 close(Stream).
184
185prolog:xref_source_time(URL, Modified) :-
186 kp_location(URL,_File,Modified,_InGitty).
192xref_all :-
193 forall(kp_location(URL,File,_), (
194 print_message(informational,xreferencing(URL,File)),
195 xref_source(URL,[silent(true)]) 196 )).
197
198prolog:message(xreferencing(URL,File)) --> ['Xreferencing module ~w in file ~w'-[URL,File]].
199prolog:message(no_kp(Name)) --> ["Could not find knowledge page ~w"-[Name]].
200
201xref_clean :-
202 forall(kp_location(URL,_,_), xref_clean(URL)).
203
204
207kp_predicate_mention(KP,G,How) :-
208 (nonvar(KP) -> true ; kp(KP)),
209 ( xref_defined(KP,G,_), How=defined ;
210 xref_called(KP, Called, _By), (Called=_:G->true;Called=G), How=called_by(KP)
211 ),
212 \+ prolog:meta_goal(G,_), \+ system_predicate(G).
217predicate_literal(M,Pred) :- must_be(nonvar,M),
218 (M:clause(Pred,Body,Ref) ; my_xref_called(M,Pred,By), clause(M:By,Body,Ref), \+ \+ contains_term(Pred,Body)),
219 clause_info(Ref,_,_,_,[variable_names(Names)]),
220 bind_vars_with_names(Pred:-Body,Names).
225bind_vars_with_names(T,VN) :- bind_vars_with_names(T,VN,_).
226
227bind_vars_with_names(_,[],[]) :- !.
228bind_vars_with_names(V,[Name=Var|VN],NewVN) :- var(V), !,
229 (var(Var) -> (Var=V,Name=Var,NewVN=VN) ; (bind_vars_with_names(V,VN,NewVN))).
230bind_vars_with_names(X,VN,VN) :- atomic(X), !.
231bind_vars_with_names([X1|Xn],VN1,VNn) :- !, bind_vars_with_names(X1,VN1,VN2), bind_vars_with_names(Xn,VN2,VNn).
232bind_vars_with_names(X,VN1,VNn) :- compound_name_arguments(X,_,Args), bind_vars_with_names(Args,VN1,VNn).
233
234print_kp_predicates :- print_kp_predicates(_).
235
237print_kp_predicates(KP) :- 238 all_kps_loaded,
239 forall(kp(KP),(
240 format("---~nKP: ~w~n",[KP]),
241 format(" Examples:~n"),
242 forall(catch(KP:example(Name,Scenarios),_,fail),(
243 aggregate(sum(N),( member(scenario(Facts,_Assertion),Scenarios), length(Facts,N)), Total),
244 format(" ~w: ~w facts~n",[Name,Total])
245 )),
246 format(" Instance data:~n"),
247 forall(xref_defined(KP,G,thread_local(_)), (
248 functor(G,F,N), format(" ~w~n",[F/N])
249 )),
250 format(" Defined predicates:~n"),
251 forall((xref_defined(KP,G,How),How\=thread_local(_)), (
252 functor(G,F,N), format(" ~w~n",[F/N])
253 )),
254 format(" External predicates called:~n"),
255 forall((
256 xref_called(KP, Called, _By),
257 Called=Other:G, Other\=KP,
258 (\+ prolog:meta_goal(G,_))
259 ),
260 (functor(G,F,N), format(" ~w (~w)~n",[F/N,Other]))
261 ),
262 format(" UNDEFINED predicates:~n"),
263 forall((
264 xref_called(KP, Called, _),
265 (Called=Other:G -> Other\=KP ; (Called=G,Other=KP)),
266 (\+ prolog:meta_goal(G,_)),
267 \+ my_xref_defined(Other,G,_),
268 \+ system_predicate(G)
269 ),
270 (functor(G,F,N), format(" ~w (~w)~n",[F/N,Other]))
271 )
272
273 )).
274
276my_xref_defined(M,G,Class) :-
277 xref_current_source(M), xref_defined(M,G,Class).
278my_xref_called(M,Pred,By) :-
279 xref_current_source(M), xref_called(M,Pred,By).
280
281system_predicate(G) :- predicate_property(G,built_in).
282system_predicate(G) :- kp_dir(D), predicate_property(G,file(F)), \+ sub_atom(F,_,_,_,D).
283system_predicate(example(_,_)).
284system_predicate(mainGoal(_,_)).
285system_predicate(query(_,_)).
286system_predicate(question(_,_)).
287system_predicate(question(_,_,_)).
288system_predicate(irrelevant_explanation(_)).
289system_predicate(function(_,_)).
290
291url_simple(URL,Simple) :- \+ sub_atom(URL,_,_,_,'/'), !,
292 Simple=URL.
293url_simple(URL,Simple) :-
294 parse_url(URL,L), memberchk(path(P),L), atomics_to_string(LL,'/',P),
295 ((last(LL,Simple),Simple\='') -> true ;
296 LL = [Simple] -> true;
297 append(_,[Simple,_],LL)),
298 !.
299url_simple(URL,URL).
300
301:- meta_predicate(must_succeed(0,+)). 302must_succeed(G,_) :- G, !.
303must_succeed(G,M) :- throw("weird_failure_of of ~w: ~w"-[G,M]).
304
305must_succeed(G) :- must_succeed(G,'').
306
307:- thread_local myDeclaredModule_/1. 309myDeclaredModule(M) :- myDeclaredModule_(M), kp(M), !.
310
311swish_editor_path(KP,Path) :- must_be(nonvar,KP),
312 (kp_location(KP,File,true)->true;File=not_on_swish_storage),
313 format(string(Path),"/p/~a",[File]), !.
314
315
316:- if(current_module(swish)). 317:- use_module(swish(lib/storage)). 318:- use_module(swish(lib/gitty)). 319:- use_module(library(pengines)).
326discover_kps_gitty :-
327 retractall(kp_location(_,_,_,true)),
328 forall(storage_file_extension(File,pl),(
329 storage_file(File,Data,Meta),
330 open_string(Data, In),
331 process_file(In,File,Meta.time,true)
332 )).
338save_gitty_files(_ToDirectory) :- \+ storage_file_extension(_File,pl), !,
339 print_message(warning,"No gitty files to save"-[]).
340save_gitty_files(ToDirectory) :-
341 (exists_directory(ToDirectory)->true; make_directory(ToDirectory)),
342 delete_directory_contents(ToDirectory),
343 forall(storage_file_extension(File,pl),(
344 storage_file(File,Data,Meta),
345 directory_file_path(ToDirectory,File,Path),
346 open(Path,write,S), write_term(S,Data,[]), close(S),
347 set_time_file(Path, _OldTimes, [modified(Meta.time)])
348 )).
349
350save_gitty_files :-
351 kp_dir(D), save_gitty_files(D).
358load_gitty_files(From) :-
359 forall(directory_member(From,Path,[extensions([pl])]),(
360 read_file_to_string(Path,Data,[]),
361 time_file(Path,Modified),
362 directory_file_path(_,File,Path),
363 update_gitty_file(File,Modified,From,Data)
364 )).
365
366load_gitty_files :-
367 kp_dir(D), load_gitty_files(D).
368
370update_gitty_file(File,Modified,Origin,Data) :-
371 web_storage:open_gittystore(Store),
372 current_user(User,_Email),
373 (gitty_file(Store, File, OldHead) -> (
374 storage_meta_data(File, Meta),
375 NewMeta = Meta.put([previous=OldHead, modify=[any, login, owner], (public)=true, time=Modified, author=User]),
376 gitty_update(Store, File, Data, NewMeta, _CommitRet)
377 ) ; (
378 gitty_create(Store, File, Data, _{update_gitty_file:Origin, modify:[any, login, owner], public:true, time:Modified, author:User }, _CommitRet)
379 )
380 ).
381
382update_gitty_file(File,Origin,Data) :-
383 get_time(Now), update_gitty_file(File,Now,Origin,Data).
388delete_gitty_file(File) :-
389 must_be(nonvar,File),
390 web_storage:open_gittystore(Store),
391 gitty_file(Store, File, OldHead),
392 393 394 395 396 storage_meta_data(File, Meta),
397 NewMeta = Meta.put([previous=OldHead]),
398 gitty_update(Store, File, "", NewMeta, _CommitRet).
399
400:- listen(swish(X),reactToSaved(X)). 409
410reactToSaved(created(GittyFile,Commit)) :-
411 reactToSaved(updated(GittyFile,Commit)).
412reactToSaved(updated(GittyFile,_Commit)) :- 413 414 storage_file(GittyFile,Data,Meta),
415 open_string(Data,In),
416 must_succeed(process_file(In,GittyFile,Meta.time,true)),
417 (kp_location(URL,GittyFile,true) -> xref_source(URL,[silent(true)]) ;
418 print_message(warning,"Could not find URL for ~w"-[GittyFile])).
423edit_kp(KP) :-
424 kp_location(KP,_File,InGitty),
425 (InGitty==(false) -> print_message(error,"~w is not in SWISH storage"-[KP]);(
426 swish_editor_path(KP,Path),
427 format(string(URL),"http://localhost:3050~a",[Path]), www_open_url(URL)
428 )).
429
431
432:- multifile user:'swish renderer'/2. 433:- use_rendering(user:graphviz). 434
435knowledgePagesGraph(KP,dot(digraph([rankdir='LR'|Graph]))) :-
436 437 setof(edge(From->To,[]), KP^Called^By^ByF^ByN^OtherKP^G^CalledF^CalledN^How^(
438 kp(KP), xref_called(KP, Called, By),
439 functor(By,ByF,ByN), From = at(ByF/ByN,KP),
440 (Called=OtherKP:G -> true ; ( once(xref_defined(KP,Called,How)), OtherKP=KP, G=Called)),
441 \+ prolog:meta_goal(G,_),
442 functor(G,CalledF,CalledN), To = at(CalledF/CalledN,OtherKP)
443 444 ),Edges),
445 setof(node(ID,[abel=Label]), KP^Goal^How^GF^GN^From^EA^Pred^Abrev^(
446 (
447 kp(KP), xref_defined(KP, Goal, How),
448 functor(Goal,GF,GN),
449 ID = at(GF/GN,KP)
450 ;
451 member(edge(From->ID,EA),Edges) 452 ),
453 ID=at(Pred,KP), url_simple(KP,Abrev),
454 format(string(Label),"~w at ~w",[Pred,Abrev])
455 456 ), Nodes),
457 append(Nodes,Edges,Items),
458 Graph=Items.
459 460
461knowledgePagesGraph(G) :- knowledgePagesGraph(_,G).
462
463:- multifile sandbox:safe_primitive/1. 464sandbox:safe_primitive(kp_loader:knowledgePagesGraph(_,_)).
465sandbox:safe_primitive(kp_loader:print_kp_predicates(_)).
466sandbox:safe_primitive(kp_loader:load_gitty_files). 467sandbox:safe_primitive(kp_loader:save_gitty_files).
468sandbox:safe_primitive(kp_loader:all_kps_loaded).
469sandbox:safe_primitive(web_storage:open_gittystore(_)).
470sandbox:safe_primitive(gitty:gitty_file(_, _, _)).
471sandbox:safe_primitive(gitty:load_commit(_,_,_)).
472sandbox:safe_primitive(gitty:gitty_update(_, _, _, _, _)).
473sandbox:safe_primitive(gitty:size_in_bytes(_,_)).
474sandbox:safe_primitive(gitty:save_object(_,_,_,_)).
475sandbox:safe_primitive(gitty:gitty_create(_,_,_,_,_)).
476
478
479:- use_module(library(http/http_json)). 480:- use_module(library(http/http_dispatch)). 481:- use_module(library(http/http_parameters)). 482
483:- http_handler(codemirror(xref), token_references, []). 484token_references(Request) :-
485 486 http_parameters(Request, [arity(Arity,[integer]),text(Text,[]),type(Type,[]),file(Module,[optional(true)]),uuid(UUID,[optional(true)])]),
487 488 489 490 (nonvar(UUID) -> (xref_module(UUID,MyModule), Ignorable=[UUID,MyModule]); Ignorable=[]),
491 catch(term_string(Term_,Text),_,fail),
492 functor(Term_,Functor,_),
493 (atom(Term_) -> functor(Term,Functor,Arity); Term=Term_), 494 (sub_atom(Type, 0, _, _, head) -> ( 495 must_be(var,Module),
496 findall( _{title:Title,line:Line,file:File,target:Functor}, ( 497 xref_called(OtherModule,_Mine:Term,By,_Cond,Line), functor(By,F,N), format(string(Title),"A call from ~w",[F/N]),
498 \+ member(OtherModule,Ignorable),
499 kp_location(OtherModule,File,_InGitty)
500 ),Locations)
501 ) ;
502 sub_atom(Type, 0, _, _, goal) -> ( 503 findall( _{title:Title,line:Line,file:File,target:Functor}, (
504 xref_defined(Module,Term,How), arg(1,How,Line), format(string(Title),"A definition for ~a",[Text]),
505 kp_location(Module,File,_InGitty)
506 ),Locations)
507 ) ;
508 throw(weird_token_type(Type))
509 ),
510 511 reply_json_dict(Locations).
512
514user:term_expansion((:-module(M,L)),(:-module(M,L))) :- !, assert(myDeclaredModule_(M)).
515:- multifile pengines:prepare_module/3. 516:- thread_local myCurrentModule/1. 517pengines:prepare_module(Module, swish, _Options) :-
518 519 setup_kp_module(Module),
520 assert(myCurrentModule(Module)).
521 524shouldMapModule(From,To) :- myDeclaredModule(From), kp(From), myCurrentModule(To), !,
525 (moduleMapping(From,To)->true;(assert(moduleMapping(From,To)))).
526
527:- dynamic moduleMapping/2. 528
529
530current_user(User,Email) :-
531 pengine_user(U), get_dict(user,U,User), Email=U.user_info.email,
532 !.
533current_user(unknown_user,unknown_email).
534
535:- else. 536
537current_user(unknown_user,unknown_email).
538
539shouldMapModule(_,_) :- fail.
540moduleMapping(_,_) :- fail.
545edit_kp(URL) :-
546 kp_location(URL,File,InGitty),
547 (InGitty==(true) -> print_message(error,"That is in SWISH storage, not in the file system!");(
548 edit(file(File))
549 )).
550
551discover_kps_gitty :- print_message(informational,'this only works on SWISH'-[]).
552load_gitty_files :- throw('this only works on SWISH ').
553load_gitty_files(_) :- throw('this only works on SWISH ').
554save_gitty_files(_) :- throw('this only works on SWISH ').
555save_gitty_files :- throw('this only works on SWISH ').
556delete_gitty_file(_) :- throw('this only works on SWISH ').
557update_gitty_file(_,_,_) :- throw('this only works on SWISH ').
558
559knowledgePagesGraph(_,_) :- throw('this only works on SWISH').
560knowledgePagesGraph(_) :- throw('this only works on SWISH').
561gitty_file(_,_,_) :- throw('this only works in SWISH gitty').
562gitty_update(_, _, _, _, _) :- throw('this only works in SWISH gitty').
563:- endif.
Dynamic module loader.
Scans a given set of Prolog files in SWISH storage or in a file system directpry, and identifies "knowledge pages", files which: