35
36:- module(swish_page,
37 [ swish_reply/2, 38 swish_reply_resource/1, 39 swish_page//1, 40
41 swish_navbar//1, 42 swish_content//1, 43
44 pengine_logo//1, 45 swish_logo//1, 46
47 swish_resources//0,
48 swish_js//0,
49 swish_css//0
50 ]). 51:- use_module(library(http/http_open)). 52:- use_module(library(http/http_dispatch)). 53:- use_module(library(http/http_parameters)). 54:- use_module(library(http/http_header)). 55:- use_module(library(http/html_write)). 56:- use_module(library(http/js_write)). 57:- use_module(library(http/json)). 58:- use_module(library(http/http_json)). 59:- use_module(library(http/http_path)). 60:- if(exists_source(library(http/http_ssl_plugin))). 61:- use_module(library(http/http_ssl_plugin)). 62:- endif. 63:- use_module(library(debug)). 64:- use_module(library(time)). 65:- use_module(library(lists)). 66:- use_module(library(option)). 67:- use_module(library(uri)). 68:- use_module(library(error)). 69:- use_module(library(http/http_client)). 70
71:- use_module(config). 72:- use_module(help). 73:- use_module(search). 74:- use_module(chat). 75:- use_module(authenticate). 76:- use_module(pep). 77
84
85http:location(pldoc, swish(pldoc), [priority(100)]).
86
87:- http_handler(swish(.), swish_reply([]), [id(swish), prefix]). 88:- http_handler('/sitemap.xml', http_reply_file('sitemap.xml', []),[]). 89:- http_handler('/robots.txt', http_reply_file('robots.txt', []),[]). 90
91:- multifile
92 swish_config:logo//1,
93 swish_config:title//1,
94 swish_config:source_alias/2,
95 swish_config:reply_page/1,
96 swish_config:li_login_button//1. 97
119
120swish_reply(Options, Request) :-
121 ( option(identity(_), Options)
122 -> Options2 = Options
123 ; authenticate(Request, Auth),
124 Options2 = [identity(Auth)|Options]
125 ),
126 swish_reply2(Options2, Request).
127
128swish_reply2(Options, Request) :-
129 option(method(Method), Request),
130 Method \== get, Method \== head, !,
131 swish_rest_reply(Method, Request, Options).
132swish_reply2(_, Request) :-
133 swish_reply_resource(Request), !.
134swish_reply2(Options, Request) :-
135 swish_reply_config(Request, Options), !.
136swish_reply2(SwishOptions, Request) :-
137 Params = [ code(_, [optional(true)]),
138 url(_, [optional(true)]),
139 label(_, [optional(true)]),
140 show_beware(_, [optional(true)]),
141 background(_, [optional(true)]),
142 examples(_, [optional(true)]),
143 q(_, [optional(true)]),
144 format(_, [oneof([swish,raw,json]), default(swish)])
145 ],
146 http_parameters(Request, Params),
147 params_options(Params, Options0),
148 add_show_beware(Options0, Options1),
149 add_preserve_state(Options1, Options2),
150 merge_options(Options2, SwishOptions, Options3),
151 source_option(Request, Options3, Options4),
152 option(format(Format), Options4),
153 swish_reply3(Format, Options4).
154
155swish_reply3(raw, Options) :-
156 option(code(Code), Options), !,
157 format('Content-type: text/x-prolog~n~n'),
158 format('~s', [Code]).
159swish_reply3(json, Options) :-
160 option(code(Code), Options), !,
161 option(meta(Meta), Options, _{}),
162 option(chat_count(Count), Options, 0),
163 reply_json_dict(json{data:Code, meta:Meta, chats:_{total:Count}}).
164swish_reply3(_, Options) :-
165 swish_config:reply_page(Options), !.
166swish_reply3(_, Options) :-
167 reply_html_page(
168 swish(main),
169 \swish_title(Options),
170 \swish_page(Options)).
171
172params_options([], []).
173params_options([H0|T0], [H|T]) :-
174 arg(1, H0, Value), nonvar(Value), !,
175 functor(H0, Name, _),
176 H =.. [Name,Value],
177 params_options(T0, T).
178params_options([_|T0], T) :-
179 params_options(T0, T).
180
185
186add_show_beware(Options0, Options) :-
187 implicit_no_show_beware(Options0), !,
188 Options = [show_beware(false)|Options0].
189add_show_beware(Options, Options).
190
191implicit_no_show_beware(Options) :-
192 option(show_beware(_), Options), !,
193 fail.
194implicit_no_show_beware(Options) :-
195 \+ option(format(swish), Options), !,
196 fail.
197implicit_no_show_beware(Options) :-
198 option(code(_), Options).
199implicit_no_show_beware(Options) :-
200 option(q(_), Options).
201implicit_no_show_beware(Options) :-
202 option(examples(_), Options).
203implicit_no_show_beware(Options) :-
204 option(background(_), Options).
205
209
210add_preserve_state(Options0, Options) :-
211 option(preserve_state(_), Options0), !,
212 Options = Options0.
213add_preserve_state(Options0, Options) :-
214 option(code(_), Options0), !,
215 Options = [preserve_state(false)|Options0].
216add_preserve_state(Options, Options).
217
218
223
224source_option(_Request, Options0, Options) :-
225 option(code(Code), Options0),
226 option(format(swish), Options0), !,
227 ( uri_is_global(Code)
228 -> Options = [url(Code),st_type(external)|Options0]
229 ; Options = Options0
230 ).
231source_option(_Request, Options0, Options) :-
232 option(url(_), Options0),
233 option(format(swish), Options0), !,
234 Options = [st_type(external),download(browser)|Options0].
235source_option(Request, Options0, Options) :-
236 source_file(Request, File, Options0), !,
237 option(path(Path), Request),
238 ( source_data(File, String, Options1)
239 -> append([ [code(String), url(Path), st_type(filesys)],
240 Options1,
241 Options0
242 ], Options)
243 ; http_404([], Request)
244 ).
245source_option(_, Options, Options).
246
256
257source_file(Request, File, Options) :-
258 option(path_info(PathInfo), Request), !,
259 PathInfo \== 'index.html',
260 ( path_info_file(PathInfo, File, Options)
261 -> true
262 ; http_404([], Request)
263 ).
264
265path_info_file(PathInfo, Path, Options) :-
266 sub_atom(PathInfo, B, _, A, /),
267 sub_atom(PathInfo, 0, B, _, Alias),
268 sub_atom(PathInfo, _, A, 0, File),
269 catch(swish_config:source_alias(Alias, AliasOptions), E,
270 (print_message(warning, E), fail)),
271 Spec =.. [Alias,File],
272 http_safe_file(Spec, []),
273 absolute_file_name(Spec, Path,
274 [ access(read),
275 file_errors(fail)
276 ]),
277 confirm_access(Path, AliasOptions), !,
278 option(alias(Alias), Options, _).
279
280source_data(Path, Code, [title(Title), type(Ext), meta(Meta)]) :-
281 setup_call_cleanup(
282 open(Path, read, In, [encoding(utf8)]),
283 read_string(In, _, Code),
284 close(In)),
285 source_metadata(Path, Code, Meta),
286 file_base_name(Path, File),
287 file_name_extension(Title, Ext, File).
288
301
302source_metadata(Path, Code, Meta) :-
303 findall(Name-Value, source_metadata(Path, Code, Name, Value), Pairs),
304 dict_pairs(Meta, meta, Pairs).
305
306source_metadata(Path, _Code, path, Path).
307source_metadata(Path, _Code, last_modified, Modified) :-
308 time_file(Path, Modified).
309source_metadata(Path, _Code, loaded, true) :-
310 source_file(Path).
311source_metadata(Path, _Code, modified_since_loaded, true) :-
312 source_file_property(Path, modified(ModifiedWhenLoaded)),
313 time_file(Path, Modified),
314 ModifiedWhenLoaded \== Modified.
315source_metadata(Path, _Code, module, Module) :-
316 file_name_extension(_, Ext, Path),
317 user:prolog_file_type(Ext, prolog),
318 xref_public_list(Path, _, [module(Module)]).
319
320confirm_access(Path, Options) :-
321 option(if(Condition), Options), !,
322 must_be(oneof([loaded]), Condition),
323 eval_condition(Condition, Path).
324confirm_access(_, _).
325
326eval_condition(loaded, Path) :-
327 source_file(Path).
328
332
333swish_reply_resource(Request) :-
334 option(path_info(Info), Request),
335 resource_prefix(Prefix),
336 sub_atom(Info, 0, _, _, Prefix), !,
337 http_reply_file(swish_web(Info), [], Request).
338
339resource_prefix('css/').
340resource_prefix('help/').
341resource_prefix('form/').
342resource_prefix('icons/').
343resource_prefix('js/').
344resource_prefix('node_modules/').
345
349
350swish_page(Options) -->
351 swish_navbar(Options),
352 swish_content(Options).
353
357
358swish_navbar(Options) -->
359 swish_resources,
360 html(div([id('navbarhelp'),style('height:40px;margin: 10px 5px;text-align:center')], 361 [div([class('container'),style('display: flex; height: 100px;')],[
362 div([style('width: 5%;')],[
363 a([href('https://ml.unife.it'),target('_blank')],
364 [img([src('/icons/logo-unife.png'),height(40)])])]),
365 div([style('flex-grow 1;')],[span([],[span([style('color:maroon')],['cplint on ']),
366 span([style('color:darkblue')],['SWI']),
367 span([style('color:maroon')],['SH']),
368 ' is a web application for probabilistic logic programming',
369 &(nbsp), &(nbsp),
370 a([id('about')],['About']),
371 &(nbsp), &(nbsp),
372 a([href('http://friguzzi.github.io/cplint/'),target('_blank')],['Help']),
373 &(nbsp), &(nbsp),
374 a([href('http://friguzzi.github.io/liftcover/'),target('_blank')],['LIFTCOVER-Help']),
375 &(nbsp), &(nbsp),
376 a([href('http://arnaudfadja.github.io/phil/'),target('_blank')],['PHIL-Help']),
377 &(nbsp), &(nbsp),
378 a([href('http://friguzzi.github.io/pascal/'),target('_blank')],['PASCAL-Help']),
379 &(nbsp), &(nbsp),
380 a([href('/help/credits.html'),target('_blank')],['Credits']),
381 &(nbsp), &(nbsp),
382 a([id('dismisslink'),href('')],['Dismiss']),
383p(['Latest: ',
384a([href('/e/liftcover/liftcover_examples.swinb')],['Threads and Python in LIFTCOVER']),', ',
385a([href('/e/course.swinb')],['course']),', ',
386a([href('/e/phil_examples.swinb')],['PHIL examples']),', ',
387a([href('http://ml.unife.it/plp-book/'),target('_blank')],["book"])
388])])
389 ])])]))
390 ,
391
392 html(nav([ class([navbar, 'navbar-default']),
393 role(navigation)
394 ],
395 [ div(class('navbar-header'),
396 [ \collapsed_button,
397 \swish_logos(Options)
398 ]),
399 div([ class([collapse, 'navbar-collapse']),
400 id(navbar)
401 ],
402 [ ul([class([nav, 'navbar-nav', menubar])], []),
403 ul([class([nav, 'navbar-nav', 'navbar-right'])],
404 [ li(\notifications(Options)),
405 li(\search_box(Options)),
406 \li_login_button(Options),
407 li(\broadcast_bell(Options)),
408 li(\updates(Options))
409 ])
410 ])
411 ])).
412
413li_login_button(Options) -->
414 swish_config:li_login_button(Options).
415li_login_button(_Options) -->
416 [].
417
418collapsed_button -->
419 html(button([type(button),
420 class('navbar-toggle'),
421 'data-toggle'(collapse),
422 'data-target'('#navbar')
423 ],
424 [ span(class('sr-only'), 'Toggle navigation'),
425 span(class('icon-bar'), []),
426 span(class('icon-bar'), []),
427 span(class('icon-bar'), [])
428 ])).
429
430updates(_Options) -->
431 html([ a(id('swish-updates'), []) ]).
432
433
434 437
442
443swish_title(Options) -->
444 swish_config:title(Options), !.
445swish_title(_Options) -->
446 html([ title('cplint on SWISH -- Probabilistic Logic Programming'),
447 link([ rel('shortcut icon'),
448 href('/icons/favicon.ico')
449 ]),
450 link([ rel('apple-touch-icon'),
451 href('/icons/cplint-touch-icon.png')
452 ]),
453 meta([name('msvalidate.01'),
454 content('A9C78799EC9EDC7CE041CB7CD8E2D76E')])
455 ]).
456
461
462swish_logos(Options) -->
463 swish_config:logo(Options), !.
464swish_logos(Options) -->
465 pengine_logo(Options),
466 swish_logo(Options).
467
474
481
482pengine_logo(_Options) -->
483 { http_absolute_location(root(.), HREF, [])
484 },
485 html(a([href(HREF), class('pengine-logo')], &(nbsp))).
486swish_logo(_Options) -->
487 { http_absolute_location(swish(.), HREF, [])
488 },
489 html(a([href(HREF), class('swish-logo')], &(nbsp))).
490
491
492 495
505
506swish_content(Options) -->
507 { document_type(Type, Options)
508 },
509 swish_resources,
510 swish_config_hash(Options),
511 swish_options(Options),
512 html(div([id(content), class([container, 'tile-top'])],
513 [ div([class([tile, horizontal]), 'data-split'('50%')],
514 [ div([ class([editors, tabbed])
515 ],
516 [ \source(Type, Options),
517 \notebooks(Type, Options)
518 ]),
519 div([class([tile, vertical]), 'data-split'('70%')],
520 [ div(class('prolog-runners'), []),
521 div(class('prolog-query'), \query(Options))
522 ])
523 ]),
524 \background(Options),
525 \examples(Options)
526 ])).
527
528
534
535swish_config_hash(Options) -->
536 { swish_config_hash(Hash, Options) },
537 js_script({|javascript(Hash)||
538 window.swish = window.swish||{};
539 window.swish.config_hash = Hash;
540 |}).
541
542
548
549swish_options(Options) -->
550 js_script({|javascript||
551 window.swish = window.swish||{};
552 window.swish.option = window.swish.option||{};
553 |}),
554 swish_options([show_beware, preserve_state], Options).
555
556swish_options([], _) --> [].
557swish_options([H|T], Options) -->
558 swish_option(H, Options),
559 swish_options(T, Options).
560
561swish_option(Name, Options) -->
562 { Opt =.. [Name,Val],
563 option(Opt, Options),
564 JSVal = @(Val)
565 }, !,
566 js_script({|javascript(Name, JSVal)||
567 window.swish.option[Name] = JSVal;
568 |}).
569swish_option(_, _) -->
570 [].
571
588
589source(pl, Options) -->
590 { ( option(code(Spec), Options)
591 ; option(download(browser), Options)
592 ),
593 !,
594 download_source(Spec, Source, Options),
595 phrase(source_data_attrs(Options), Extra),
596 option(label(Label), Options, 'Program')
597 },
598 html(div([ class(['prolog-editor']),
599 'data-label'(Label)
600 ],
601 [ textarea([ class([source,prolog]),
602 style('display:none')
603 | Extra
604 ],
605 Source)
606 ])).
607source(_, _) --> [].
608
609source_data_attrs(Options) -->
610 (source_file_data(Options) -> [] ; []),
611 (source_url_data(Options) -> [] ; []),
612 (source_download_data(Options) -> [] ; []),
613 (source_title_data(Options) -> [] ; []),
614 (source_meta_data(Options) -> [] ; []),
615 (source_st_type_data(Options) -> [] ; []),
616 (source_chat_data(Options) -> [] ; []).
617
618source_file_data(Options) -->
619 { option(file(File), Options) },
620 ['data-file'(File)].
621source_url_data(Options) -->
622 { option(url(URL), Options) },
623 ['data-url'(URL)].
624source_download_data(Options) -->
625 { option(download(Who), Options) },
626 ['data-download'(Who)].
627source_title_data(Options) -->
628 { option(title(File), Options) },
629 ['data-title'(File)].
630source_st_type_data(Options) -->
631 { option(st_type(Type), Options) },
632 ['data-st_type'(Type)].
633source_meta_data(Options) -->
634 { option(meta(Meta), Options), !,
635 atom_json_dict(Text, Meta, [])
636 },
637 ['data-meta'(Text)].
638source_chat_data(Options) -->
639 { option(chat_count(Count), Options),
640 atom_json_term(JSON, _{count:Count}, [as(string)])
641 },
642 ['data-chats'(JSON)].
643
649
650background(Options) -->
651 { option(background(Spec), Options), !,
652 download_source(Spec, Source, Options)
653 },
654 html(textarea([ class([source,prolog,background]),
655 style('display:none')
656 ],
657 Source)).
658background(_) --> [].
659
660
661examples(Options) -->
662 { option(examples(Examples), Options), !
663 },
664 html(textarea([ class([examples,prolog]),
665 style('display:none')
666 ],
667 Examples)).
668examples(_) --> [].
669
670
671query(Options) -->
672 { option(q(Query), Options)
673 }, !,
674 html(textarea([ class([query,prolog]),
675 style('display:none')
676 ],
677 Query)).
678query(_) --> [].
679
684
685notebooks(swinb, Options) -->
686 { option(code(Spec), Options),
687 download_source(Spec, NoteBookText, Options),
688 phrase(source_data_attrs(Options), Extra)
689 },
690 html(div([ class('notebook'),
691 'data-label'('Notebook') 692 ],
693 [ pre([ class('notebook-data'),
694 style('display:none')
695 | Extra
696 ],
697 NoteBookText)
698 ])).
699notebooks(_, _) --> [].
700
715
716download_source(_HREF, Source, Options) :-
717 option(download(browser), Options),
718 !,
719 Source = "".
720download_source(HREF, Source, Options) :-
721 uri_is_global(HREF), !,
722 download_href(HREF, Source, Options).
723download_source(Source0, Source, Options) :-
724 option(max_length(MaxLen), Options, 1_000_000),
725 string_length(Source0, Len),
726 ( Len =< MaxLen
727 -> Source = Source0
728 ; format(string(Source),
729 '% ERROR: Content too long (max ~D)~n', [MaxLen])
730 ).
731
732download_href(HREF, Source, Options) :-
733 option(timeout(TMO), Options, 10),
734 option(max_length(MaxLen), Options, 1_000_000),
735 catch(call_with_time_limit(
736 TMO,
737 setup_call_cleanup(
738 http_open(HREF, In,
739 [ cert_verify_hook(cert_accept_any)
740 ]),
741 read_source(In, MaxLen, Source, Options),
742 close(In))),
743 E, load_error(E, Source)).
744
745read_source(In, MaxLen, Source, Options) :-
746 option(encoding(Enc), Options, utf8),
747 set_stream(In, encoding(Enc)),
748 ReadMax is MaxLen + 1,
749 read_string(In, ReadMax, Source0),
750 string_length(Source0, Len),
751 ( Len =< MaxLen
752 -> Source = Source0
753 ; format(string(Source),
754 ' % ERROR: Content too long (max ~D)~n', [MaxLen])
755 ).
756
757load_error(E, Source) :-
758 message_to_string(E, String),
759 format(string(Source), '% ERROR: ~s~n', [String]).
760
766
767document_type(Type, Options) :-
768 ( option(type(Type0), Options)
769 -> Type = Type0
770 ; option(meta(Meta), Options),
771 file_name_extension(_, Type0, Meta.name),
772 Type0 \== ''
773 -> Type = Type0
774 ; option(st_type(external), Options),
775 option(url(URL), Options),
776 file_name_extension(_, Ext, URL),
777 ext_type(Ext, Type)
778 -> true
779 ; Type = pl
780 ).
781
782ext_type(swinb, swinb).
783
784
785 788
794
795swish_resources -->
796 swish_css,
797 swish_js.
798
799swish_js --> html_post(head, \include_swish_js).
800swish_css --> html_post(head, \include_swish_css).
801
802include_swish_js -->
803 html(script([],[
804 '(function(i,s,o,g,r,a,m){i[''GoogleAnalyticsObject'']=r;i[r]=i[r]||function(){
805 (i[r].q=i[r].q||[]).push(arguments)},i[r].l=1*new Date();a=s.createElement(o),
806 m=s.getElementsByTagName(o)[0];a.async=1;a.src=g;m.parentNode.insertBefore(a,m)
807 })(window,document,''script'',''//www.google-analytics.com/analytics.js'',''ga'');
808
809 ga(''create'', ''UA-16202613-9'', ''auto'');
810 ga(''send'', ''pageview'');'])),
811 html(\['<!-- Global site tag (gtag.js) - Google Analytics -->
812<script async src="https://www.googletagmanager.com/gtag/js?id=G-GL8L9W5NE7"></script>
813<script>
814 window.dataLayer = window.dataLayer || [];
815 function gtag(){dataLayer.push(arguments);}
816 gtag(''js'', new Date());
817
818 gtag(''config'', ''G-GL8L9W5NE7'');
819</script>']),
820 { swish_resource(js, JS),
821 swish_resource(rjs, RJS),
822 http_absolute_location(swish(js/JS), SwishJS, []),
823 http_absolute_location(swish(RJS), SwishRJS, [])
824 },
825 rjs_timeout(JS),
826 html(script([ src(SwishRJS),
827 'data-main'(SwishJS)
828 ], [])).
829
830rjs_timeout('swish-min') --> !,
831 js_script({|javascript||
832// Override RequireJS timeout, until main file is loaded.
833window.require = { waitSeconds: 0 };
834 |}).
835rjs_timeout(_) --> [].
836
837
838include_swish_css -->
839 { swish_resource(css, CSS),
840 http_absolute_location(swish(css/CSS), SwishCSS, [])
841 },
842 html(link([ rel(stylesheet),
843 href(SwishCSS)
844 ])).
845
846swish_resource(Type, ID) :-
847 alt(Type, ID, File),
848 ( File == (-)
849 ; absolute_file_name(File, _P, [file_errors(fail), access(read)])
850 ), !.
851
852alt(js, 'swish-min', swish_web('js/swish-min.js')) :-
853 \+ debugging(nominified).
854alt(js, 'swish', swish_web('js/swish.js')).
855alt(css, 'swish-min.css', swish_web('css/swish-min.css')) :-
856 \+ debugging(nominified).
857alt(css, 'swish.css', swish_web('css/swish.css')).
858alt(rjs, 'js/require.js', swish_web('js/require.js')) :-
859 \+ debugging(nominified).
860alt(rjs, 'node_modules/requirejs/require.js', -).
861
862
863 866
871
872swish_rest_reply(put, Request, Options) :-
873 merge_options(Options, [alias(_)], Options1),
874 source_file(Request, File, Options1), !,
875 option(content_type(String), Request),
876 http_parse_header_value(content_type, String, Type),
877 read_data(Type, Request, Data, Meta),
878 authorized(file(update(File,Meta)), Options1),
879 setup_call_cleanup(
880 open(File, write, Out, [encoding(utf8)]),
881 format(Out, '~s', [Data]),
882 close(Out)),
883 reply_json_dict(true).
884
885read_data(media(Type,_), Request, Data, Meta) :-
886 http_json:json_type(Type), !,
887 http_read_json_dict(Request, Dict),
888 del_dict(data, Dict, Data, Meta).
889read_data(media(text/_,_), Request, Data, _{}) :-
890 http_read_data(Request, Data,
891 [ to(string),
892 input_encoding(utf8)
893 ])