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
336
337swish_reply_resource(Request) :-
338 option(path_info(Info), Request),
339 resource_prefix(Prefix),
340 sub_atom(Info, 0, _, _, Prefix), !,
341 http_reply_file(swish_web(Info), [], Request).
342swish_reply_resource(Request) :- 343 option(path_info(Info), Request),
344 sub_atom(Info, 0, _, _, 'fonts/'), !,
345 atom_concat('node_modules/bootstrap/dist/', Info, Path),
346 http_reply_file(swish_web(Path), [], Request).
347
348resource_prefix('css/').
349resource_prefix('help/').
350resource_prefix('form/').
351resource_prefix('icons/').
352resource_prefix('js/').
353resource_prefix('node_modules/').
354
358
359swish_page(Options) -->
360 swish_navbar(Options),
361 swish_content(Options).
362
366
367swish_navbar(Options) -->
368 swish_resources,
369 html(div([id('navbarhelp'),style('height:40px;margin: 10px 5px;text-align:center')], 370 [div([class('container'),style('display: flex; height: 100px;')],[
371 div([style('width: 5%;')],[
372 a([href('https://ml.unife.it'),target('_blank')],
373 [img([src('/icons/logo-unife.png'),height(40)])])]),
374 div([style('flex-grow 1;')],[span([],[span([style('color:maroon')],['cplint on ']),
375 span([style('color:darkblue')],['SWI']),
376 span([style('color:maroon')],['SH']),
377 ' is a web application for probabilistic logic programming',
378 &(nbsp), &(nbsp),
379 a([id('about')],['About']),
380 &(nbsp), &(nbsp),
381 a([href('http://friguzzi.github.io/cplint/'),target('_blank')],['Help']),
382 &(nbsp), &(nbsp),
383 a([href('http://friguzzi.github.io/liftcover/'),target('_blank')],['LIFTCOVER-Help']),
384 &(nbsp), &(nbsp),
385 a([href('http://arnaudfadja.github.io/phil/'),target('_blank')],['PHIL-Help']),
386 &(nbsp), &(nbsp),
387 a([href('http://friguzzi.github.io/pascal/'),target('_blank')],['PASCAL-Help']),
388 &(nbsp), &(nbsp),
389 a([href('/help/credits.html'),target('_blank')],['Credits']),
390 &(nbsp), &(nbsp),
391 a([id('dismisslink'),href('')],['Dismiss']),
392p(['Latest: ',
393a([href('/e/liftcover/liftcover_examples.swinb')],['Threads and Python in LIFTCOVER']),', ',
394a([href('/e/course.swinb')],['course']),', ',
395a([href('/e/phil_examples.swinb')],['PHIL examples']),', ',
396a([href('http://ml.unife.it/plp-book/'),target('_blank')],["book"])
397])])
398 ])])]))
399 ,
400
401 html(nav([ class([navbar, 'navbar-default']),
402 role(navigation)
403 ],
404 [ div(class('navbar-header'),
405 [ \collapsed_button,
406 \swish_logos(Options)
407 ]),
408 div([ class([collapse, 'navbar-collapse']),
409 id(navbar)
410 ],
411 [ ul([class([nav, 'navbar-nav', menubar])], []),
412 ul([class([nav, 'navbar-nav', 'navbar-right'])],
413 [ li(\notifications(Options)),
414 li(\search_box(Options)),
415 \li_login_button(Options),
416 li(\broadcast_bell(Options)),
417 li(\updates(Options))
418 ])
419 ])
420 ])).
421
422li_login_button(Options) -->
423 swish_config:li_login_button(Options).
424li_login_button(_Options) -->
425 [].
426
427collapsed_button -->
428 html(button([type(button),
429 class('navbar-toggle'),
430 'data-toggle'(collapse),
431 'data-target'('#navbar')
432 ],
433 [ span(class('sr-only'), 'Toggle navigation'),
434 span(class('icon-bar'), []),
435 span(class('icon-bar'), []),
436 span(class('icon-bar'), [])
437 ])).
438
439updates(_Options) -->
440 html([ a(id('swish-updates'), []) ]).
441
442
443 446
451
452swish_title(Options) -->
453 swish_config:title(Options), !.
454swish_title(_Options) -->
455 html([ title('cplint on SWISH -- Probabilistic Logic Programming'),
456 link([ rel('shortcut icon'),
457 href('/icons/favicon.ico')
458 ]),
459 link([ rel('apple-touch-icon'),
460 href('/icons/cplint-touch-icon.png')
461 ]),
462 meta([name('msvalidate.01'),
463 content('A9C78799EC9EDC7CE041CB7CD8E2D76E')])
464 ]).
465
470
471swish_logos(Options) -->
472 swish_config:logo(Options), !.
473swish_logos(Options) -->
474 pengine_logo(Options),
475 swish_logo(Options).
476
483
490
491pengine_logo(_Options) -->
492 { http_absolute_location(root(.), HREF, [])
493 },
494 html(a([href(HREF), class('pengine-logo')], &(nbsp))).
495swish_logo(_Options) -->
496 { http_absolute_location(swish(.), HREF, [])
497 },
498 html(a([href(HREF), class('swish-logo')], &(nbsp))).
499
500
501 504
514
515swish_content(Options) -->
516 { document_type(Type, Options)
517 },
518 swish_resources,
519 swish_config_hash(Options),
520 swish_options(Options),
521 html(div([id(content), class([container, 'tile-top'])],
522 [ div([class([tile, horizontal]), 'data-split'('50%')],
523 [ div([ class([editors, tabbed])
524 ],
525 [ \source(Type, Options),
526 \notebooks(Type, Options)
527 ]),
528 div([class([tile, vertical]), 'data-split'('70%')],
529 [ div(class('prolog-runners'), []),
530 div(class('prolog-query'), \query(Options))
531 ])
532 ]),
533 \background(Options),
534 \examples(Options)
535 ])).
536
537
543
544swish_config_hash(Options) -->
545 { swish_config_hash(Hash, Options) },
546 js_script({|javascript(Hash)||
547 window.swish = window.swish||{};
548 window.swish.config_hash = Hash;
549 |}).
550
551
557
558swish_options(Options) -->
559 js_script({|javascript||
560 window.swish = window.swish||{};
561 window.swish.option = window.swish.option||{};
562 |}),
563 swish_options([show_beware, preserve_state], Options).
564
565swish_options([], _) --> [].
566swish_options([H|T], Options) -->
567 swish_option(H, Options),
568 swish_options(T, Options).
569
570swish_option(Name, Options) -->
571 { Opt =.. [Name,Val],
572 option(Opt, Options),
573 JSVal = @(Val)
574 }, !,
575 js_script({|javascript(Name, JSVal)||
576 window.swish.option[Name] = JSVal;
577 |}).
578swish_option(_, _) -->
579 [].
580
597
598source(pl, Options) -->
599 { ( option(code(Spec), Options)
600 ; option(download(browser), Options)
601 ),
602 !,
603 download_source(Spec, Source, Options),
604 phrase(source_data_attrs(Options), Extra),
605 option(label(Label), Options, 'Program')
606 },
607 html(div([ class(['prolog-editor']),
608 'data-label'(Label)
609 ],
610 [ textarea([ class([source,prolog]),
611 style('display:none')
612 | Extra
613 ],
614 Source)
615 ])).
616source(_, _) --> [].
617
618source_data_attrs(Options) -->
619 (source_file_data(Options) -> [] ; []),
620 (source_url_data(Options) -> [] ; []),
621 (source_download_data(Options) -> [] ; []),
622 (source_title_data(Options) -> [] ; []),
623 (source_meta_data(Options) -> [] ; []),
624 (source_st_type_data(Options) -> [] ; []),
625 (source_chat_data(Options) -> [] ; []).
626
627source_file_data(Options) -->
628 { option(file(File), Options) },
629 ['data-file'(File)].
630source_url_data(Options) -->
631 { option(url(URL), Options) },
632 ['data-url'(URL)].
633source_download_data(Options) -->
634 { option(download(Who), Options) },
635 ['data-download'(Who)].
636source_title_data(Options) -->
637 { option(title(File), Options) },
638 ['data-title'(File)].
639source_st_type_data(Options) -->
640 { option(st_type(Type), Options) },
641 ['data-st_type'(Type)].
642source_meta_data(Options) -->
643 { option(meta(Meta), Options), !,
644 atom_json_dict(Text, Meta, [])
645 },
646 ['data-meta'(Text)].
647source_chat_data(Options) -->
648 { option(chat_count(Count), Options),
649 atom_json_term(JSON, _{count:Count}, [as(string)])
650 },
651 ['data-chats'(JSON)].
652
658
659background(Options) -->
660 { option(background(Spec), Options), !,
661 download_source(Spec, Source, Options)
662 },
663 html(textarea([ class([source,prolog,background]),
664 style('display:none')
665 ],
666 Source)).
667background(_) --> [].
668
669
670examples(Options) -->
671 { option(examples(Examples), Options), !
672 },
673 html(textarea([ class([examples,prolog]),
674 style('display:none')
675 ],
676 Examples)).
677examples(_) --> [].
678
679
680query(Options) -->
681 { option(q(Query), Options)
682 }, !,
683 html(textarea([ class([query,prolog]),
684 style('display:none')
685 ],
686 Query)).
687query(_) --> [].
688
693
694notebooks(swinb, Options) -->
695 { option(code(Spec), Options),
696 download_source(Spec, NoteBookText, Options),
697 phrase(source_data_attrs(Options), Extra)
698 },
699 html(div([ class('notebook'),
700 'data-label'('Notebook') 701 ],
702 [ pre([ class('notebook-data'),
703 style('display:none')
704 | Extra
705 ],
706 NoteBookText)
707 ])).
708notebooks(_, _) --> [].
709
724
725download_source(_HREF, Source, Options) :-
726 option(download(browser), Options),
727 !,
728 Source = "".
729download_source(HREF, Source, Options) :-
730 uri_is_global(HREF), !,
731 download_href(HREF, Source, Options).
732download_source(Source0, Source, Options) :-
733 option(max_length(MaxLen), Options, 1_000_000),
734 string_length(Source0, Len),
735 ( Len =< MaxLen
736 -> Source = Source0
737 ; format(string(Source),
738 '% ERROR: Content too long (max ~D)~n', [MaxLen])
739 ).
740
741download_href(HREF, Source, Options) :-
742 option(timeout(TMO), Options, 10),
743 option(max_length(MaxLen), Options, 1_000_000),
744 catch(call_with_time_limit(
745 TMO,
746 setup_call_cleanup(
747 http_open(HREF, In,
748 [ cert_verify_hook(cert_accept_any)
749 ]),
750 read_source(In, MaxLen, Source, Options),
751 close(In))),
752 E, load_error(E, Source)).
753
754read_source(In, MaxLen, Source, Options) :-
755 option(encoding(Enc), Options, utf8),
756 set_stream(In, encoding(Enc)),
757 ReadMax is MaxLen + 1,
758 read_string(In, ReadMax, Source0),
759 string_length(Source0, Len),
760 ( Len =< MaxLen
761 -> Source = Source0
762 ; format(string(Source),
763 ' % ERROR: Content too long (max ~D)~n', [MaxLen])
764 ).
765
766load_error(E, Source) :-
767 message_to_string(E, String),
768 format(string(Source), '% ERROR: ~s~n', [String]).
769
775
776document_type(Type, Options) :-
777 ( option(type(Type0), Options)
778 -> Type = Type0
779 ; option(meta(Meta), Options),
780 file_name_extension(_, Type0, Meta.name),
781 Type0 \== ''
782 -> Type = Type0
783 ; option(st_type(external), Options),
784 option(url(URL), Options),
785 file_name_extension(_, Ext, URL),
786 ext_type(Ext, Type)
787 -> true
788 ; Type = pl
789 ).
790
791ext_type(swinb, swinb).
792
793
794 797
803
804swish_resources -->
805 swish_css,
806 swish_js.
807
808swish_js --> html_post(head, \include_swish_js).
809swish_css --> html_post(head, \include_swish_css).
810
811include_swish_js -->
812 html(script([],[
813 '(function(i,s,o,g,r,a,m){i[''GoogleAnalyticsObject'']=r;i[r]=i[r]||function(){
814 (i[r].q=i[r].q||[]).push(arguments)},i[r].l=1*new Date();a=s.createElement(o),
815 m=s.getElementsByTagName(o)[0];a.async=1;a.src=g;m.parentNode.insertBefore(a,m)
816 })(window,document,''script'',''//www.google-analytics.com/analytics.js'',''ga'');
817
818 ga(''create'', ''UA-16202613-9'', ''auto'');
819 ga(''send'', ''pageview'');'])),
820 html(\['<!-- Global site tag (gtag.js) - Google Analytics -->
821<script async src="https://www.googletagmanager.com/gtag/js?id=G-GL8L9W5NE7"></script>
822<script>
823 window.dataLayer = window.dataLayer || [];
824 function gtag(){dataLayer.push(arguments);}
825 gtag(''js'', new Date());
826
827 gtag(''config'', ''G-GL8L9W5NE7'');
828</script>']),
829 { swish_resource(js, JS),
830 swish_resource(rjs, RJS),
831 http_absolute_location(swish(js/JS), SwishJS, []),
832 http_absolute_location(swish(RJS), SwishRJS, [])
833 },
834 rjs_timeout(JS),
835 html(script([ src(SwishRJS),
836 'data-main'(SwishJS)
837 ], [])).
838
839rjs_timeout('swish-min') --> !,
840 js_script({|javascript||
841// Override RequireJS timeout, until main file is loaded.
842window.require = { waitSeconds: 0 };
843 |}).
844rjs_timeout(_) --> [].
845
846
847include_swish_css -->
848 { swish_resource(css, CSS),
849 http_absolute_location(swish(css/CSS), SwishCSS, [])
850 },
851 html(link([ rel(stylesheet),
852 href(SwishCSS)
853 ])).
854
855swish_resource(Type, ID) :-
856 alt(Type, ID, File),
857 ( File == (-)
858 ; absolute_file_name(File, _P, [file_errors(fail), access(read)])
859 ), !.
860
861alt(js, 'swish-min', swish_web('js/swish-min.js')) :-
862 \+ debugging(nominified).
863alt(js, 'swish', swish_web('js/swish.js')).
864alt(css, 'swish-min.css', swish_web('css/swish-min.css')) :-
865 \+ debugging(nominified).
866alt(css, 'swish.css', swish_web('css/swish.css')).
867alt(rjs, 'js/require.js', swish_web('js/require.js')) :-
868 \+ debugging(nominified).
869alt(rjs, 'node_modules/requirejs/require.js', -).
870
871
872 875
880
881swish_rest_reply(put, Request, Options) :-
882 merge_options(Options, [alias(_)], Options1),
883 source_file(Request, File, Options1), !,
884 option(content_type(String), Request),
885 http_parse_header_value(content_type, String, Type),
886 read_data(Type, Request, Data, Meta),
887 authorized(file(update(File,Meta)), Options1),
888 setup_call_cleanup(
889 open(File, write, Out, [encoding(utf8)]),
890 format(Out, '~s', [Data]),
891 close(Out)),
892 reply_json_dict(true).
893
894read_data(media(Type,_), Request, Data, Meta) :-
895 http_json:json_type(Type), !,
896 http_read_json_dict(Request, Dict),
897 del_dict(data, Dict, Data, Meta).
898read_data(media(text/_,_), Request, Data, _{}) :-
899 http_read_data(Request, Data,
900 [ to(string),
901 input_encoding(utf8)
902 ])