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