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).
85http:location(pldoc, swish(pldoc), [priority(100)]).
86
87:- http_handler(swish(.), swish_reply([]), [id(swish), prefix]). 88
89:- multifile
90 swish_config:logo//1,
91 swish_config:title//1,
92 swish_config:source_alias/2,
93 swish_config:reply_page/1,
94 swish_config:li_login_button//1.
116swish_reply(Options, Request) :-
117 ( option(identity(_), Options)
118 -> Options2 = Options
119 ; authenticate(Request, Auth),
120 Options2 = [identity(Auth)|Options]
121 ),
122 swish_reply2(Options2, Request).
123
124swish_reply2(Options, Request) :-
125 option(method(Method), Request),
126 Method \== get, Method \== head, !,
127 swish_rest_reply(Method, Request, Options).
128swish_reply2(_, Request) :-
129 swish_reply_resource(Request), !.
130swish_reply2(Options, Request) :-
131 swish_reply_config(Request, Options), !.
132swish_reply2(SwishOptions, Request) :-
133 Params = [ code(_, [optional(true)]),
134 show_beware(_, [optional(true)]),
135 background(_, [optional(true)]),
136 examples(_, [optional(true)]),
137 q(_, [optional(true)]),
138 format(_, [oneof([swish,raw,json]), default(swish)])
139 ],
140 http_parameters(Request, Params),
141 params_options(Params, Options0),
142 add_show_beware(Options0, Options1),
143 add_preserve_state(Options1, Options2),
144 merge_options(Options2, SwishOptions, Options3),
145 source_option(Request, Options3, Options4),
146 option(format(Format), Options4),
147 swish_reply3(Format, Options4).
148
149swish_reply3(raw, Options) :-
150 option(code(Code), Options), !,
151 format('Content-type: text/x-prolog~n~n'),
152 format('~s', [Code]).
153swish_reply3(json, Options) :-
154 option(code(Code), Options), !,
155 option(meta(Meta), Options, _{}),
156 option(chat_count(Count), Options, 0),
157 reply_json_dict(json{data:Code, meta:Meta, chats:_{total:Count}}).
158swish_reply3(_, Options) :-
159 swish_config:reply_page(Options), !.
160swish_reply3(_, Options) :-
161 reply_html_page(
162 swish(main),
163 \swish_title(Options),
164 \swish_page(Options)).
165
166params_options([], []).
167params_options([H0|T0], [H|T]) :-
168 arg(1, H0, Value), nonvar(Value), !,
169 functor(H0, Name, _),
170 H =.. [Name,Value],
171 params_options(T0, T).
172params_options([_|T0], T) :-
173 params_options(T0, T).
180add_show_beware(Options0, Options) :-
181 implicit_no_show_beware(Options0), !,
182 Options = [show_beware(false)|Options0].
183add_show_beware(Options, Options).
184
185implicit_no_show_beware(Options) :-
186 option(show_beware(_), Options), !,
187 fail.
188implicit_no_show_beware(Options) :-
189 \+ option(format(swish), Options), !,
190 fail.
191implicit_no_show_beware(Options) :-
192 option(code(_), Options).
193implicit_no_show_beware(Options) :-
194 option(q(_), Options).
195implicit_no_show_beware(Options) :-
196 option(examples(_), Options).
197implicit_no_show_beware(Options) :-
198 option(background(_), Options).
204add_preserve_state(Options0, Options) :-
205 option(preserve_state(_), Options0), !,
206 Options = Options0.
207add_preserve_state(Options0, Options) :-
208 option(code(_), Options0), !,
209 Options = [preserve_state(false)|Options0].
210add_preserve_state(Options, Options).
218source_option(_Request, Options0, Options) :-
219 option(code(Code), Options0),
220 option(format(swish), Options0), !,
221 ( uri_is_global(Code)
222 -> Options = [url(Code),st_type(external)|Options0]
223 ; Options = Options0
224 ).
225source_option(Request, Options0, Options) :-
226 source_file(Request, File, Options0), !,
227 option(path(Path), Request),
228 ( source_data(File, String, Options1)
229 -> append([ [code(String), url(Path), st_type(filesys)],
230 Options1,
231 Options0
232 ], Options)
233 ; http_404([], Request)
234 ).
235source_option(_, Options, Options).
247source_file(Request, File, Options) :-
248 option(path_info(PathInfo), Request), !,
249 PathInfo \== 'index.html',
250 ( path_info_file(PathInfo, File, Options)
251 -> true
252 ; http_404([], Request)
253 ).
254
255path_info_file(PathInfo, Path, Options) :-
256 sub_atom(PathInfo, B, _, A, /),
257 sub_atom(PathInfo, 0, B, _, Alias),
258 sub_atom(PathInfo, _, A, 0, File),
259 catch(swish_config:source_alias(Alias, AliasOptions), E,
260 (print_message(warning, E), fail)),
261 Spec =.. [Alias,File],
262 http_safe_file(Spec, []),
263 absolute_file_name(Spec, Path,
264 [ access(read),
265 file_errors(fail)
266 ]),
267 confirm_access(Path, AliasOptions), !,
268 option(alias(Alias), Options, _).
269
270source_data(Path, Code, [title(Title), type(Ext), meta(Meta)]) :-
271 setup_call_cleanup(
272 open(Path, read, In, [encoding(utf8)]),
273 read_string(In, _, Code),
274 close(In)),
275 source_metadata(Path, Code, Meta),
276 file_base_name(Path, File),
277 file_name_extension(Title, Ext, File).
292source_metadata(Path, Code, Meta) :-
293 findall(Name-Value, source_metadata(Path, Code, Name, Value), Pairs),
294 dict_pairs(Meta, meta, Pairs).
295
296source_metadata(Path, _Code, path, Path).
297source_metadata(Path, _Code, last_modified, Modified) :-
298 time_file(Path, Modified).
299source_metadata(Path, _Code, loaded, true) :-
300 source_file(Path).
301source_metadata(Path, _Code, modified_since_loaded, true) :-
302 source_file_property(Path, modified(ModifiedWhenLoaded)),
303 time_file(Path, Modified),
304 ModifiedWhenLoaded \== Modified.
305source_metadata(Path, _Code, module, Module) :-
306 file_name_extension(_, Ext, Path),
307 user:prolog_file_type(Ext, prolog),
308 xref_public_list(Path, _, [module(Module)]).
309
310confirm_access(Path, Options) :-
311 option(if(Condition), Options), !,
312 must_be(oneof([loaded]), Condition),
313 eval_condition(Condition, Path).
314confirm_access(_, _).
315
316eval_condition(loaded, Path) :-
317 source_file(Path).
323swish_reply_resource(Request) :-
324 option(path_info(Info), Request),
325 resource_prefix(Prefix),
326 sub_atom(Info, 0, _, _, Prefix), !,
327 http_reply_file(swish_web(Info), [], Request).
328
329resource_prefix('css/').
330resource_prefix('help/').
331resource_prefix('form/').
332resource_prefix('icons/').
333resource_prefix('js/').
334resource_prefix('bower_components/').
340swish_page(Options) -->
341 swish_navbar(Options),
342 swish_content(Options).
348swish_navbar(Options) -->
349 swish_resources,
350 html(nav([ class([navbar, 'navbar-default']),
351 role(navigation)
352 ],
353 [ div(class('navbar-header'),
354 [ \collapsed_button,
355 \swish_logos(Options)
356 ]),
357 div([ class([collapse, 'navbar-collapse']),
358 id(navbar)
359 ],
360 [ ul([class([nav, 'navbar-nav', menubar])], []),
361 ul([class([nav, 'navbar-nav', 'navbar-right'])],
362 [ li(\notifications(Options)),
363 li(\search_box(Options)),
364 \li_login_button(Options),
365 li(\broadcast_bell(Options)),
366 li(\updates(Options))
367 ])
368 ])
369 ])).
370
371li_login_button(Options) -->
372 swish_config:li_login_button(Options).
373li_login_button(_Options) -->
374 [].
375
376collapsed_button -->
377 html(button([type(button),
378 class('navbar-toggle'),
379 'data-toggle'(collapse),
380 'data-target'('#navbar')
381 ],
382 [ span(class('sr-only'), 'Toggle navigation'),
383 span(class('icon-bar'), []),
384 span(class('icon-bar'), []),
385 span(class('icon-bar'), [])
386 ])).
387
388updates(_Options) -->
389 html([ a(id('swish-updates'), []) ]).
390
391
392
401swish_title(Options) -->
402 swish_config:title(Options), !.
403swish_title(_Options) -->
404 html([ title('SWISH -- SWI-Prolog for SHaring'),
405 link([ rel('shortcut icon'),
406 href('/icons/favicon.ico')
407 ]),
408 link([ rel('apple-touch-icon'),
409 href('/icons/swish-touch-icon.png')
410 ])
411 ]).
418swish_logos(Options) -->
419 swish_config:logo(Options), !.
420swish_logos(Options) -->
421 pengine_logo(Options),
422 swish_logo(Options).
438pengine_logo(_Options) -->
439 { http_absolute_location(root(.), HREF, [])
440 },
441 html(a([href(HREF), class('pengine-logo')], &(nbsp))).
442swish_logo(_Options) -->
443 { http_absolute_location(swish(.), HREF, [])
444 },
445 html(a([href(HREF), class('swish-logo')], &(nbsp))).
446
447
448
462swish_content(Options) -->
463 { document_type(Type, Options)
464 },
465 swish_resources,
466 swish_config_hash(Options),
467 swish_options(Options),
468 html(div([id(content), class([container, 'tile-top'])],
469 [ div([class([tile, horizontal]), 'data-split'('50%')],
470 [ div([ class([editors, tabbed])
471 ],
472 [ \source(Type, Options),
473 \notebooks(Type, Options)
474 ]),
475 div([class([tile, vertical]), 'data-split'('70%')],
476 [ div(class('prolog-runners'), []),
477 div(class('prolog-query'), \query(Options))
478 ])
479 ]),
480 \background(Options),
481 \examples(Options)
482 ])).
491swish_config_hash(Options) -->
492 { swish_config_hash(Hash, Options) },
493 js_script({|javascript(Hash)||
494 window.swish = window.swish||{};
495 window.swish.config_hash = Hash;
496 |}).
505swish_options(Options) -->
506 js_script({|javascript||
507 window.swish = window.swish||{};
508 window.swish.option = window.swish.option||{};
509 |}),
510 swish_options([show_beware, preserve_state], Options).
511
512swish_options([], _) --> [].
513swish_options([H|T], Options) -->
514 swish_option(H, Options),
515 swish_options(T, Options).
516
517swish_option(Name, Options) -->
518 { Opt =.. [Name,Val],
519 option(Opt, Options),
520 JSVal = @(Val)
521 }, !,
522 js_script({|javascript(Name, JSVal)||
523 window.swish.option[Name] = JSVal;
524 |}).
525swish_option(_, _) -->
526 [].
545source(pl, Options) -->
546 { option(code(Spec), Options), !,
547 download_source(Spec, Source, Options),
548 phrase(source_data_attrs(Options), Extra)
549 },
550 html(div([ class(['prolog-editor']),
551 'data-label'('Program')
552 ],
553 [ textarea([ class([source,prolog]),
554 style('display:none')
555 | Extra
556 ],
557 Source)
558 ])).
559source(_, _) --> [].
560
561source_data_attrs(Options) -->
562 (source_file_data(Options) -> [] ; []),
563 (source_url_data(Options) -> [] ; []),
564 (source_title_data(Options) -> [] ; []),
565 (source_meta_data(Options) -> [] ; []),
566 (source_st_type_data(Options) -> [] ; []),
567 (source_chat_data(Options) -> [] ; []).
568
569source_file_data(Options) -->
570 { option(file(File), Options) },
571 ['data-file'(File)].
572source_url_data(Options) -->
573 { option(url(URL), Options) },
574 ['data-url'(URL)].
575source_title_data(Options) -->
576 { option(title(File), Options) },
577 ['data-title'(File)].
578source_st_type_data(Options) -->
579 { option(st_type(Type), Options) },
580 ['data-st_type'(Type)].
581source_meta_data(Options) -->
582 { option(meta(Meta), Options), !,
583 atom_json_dict(Text, Meta, [])
584 },
585 ['data-meta'(Text)].
586source_chat_data(Options) -->
587 { option(chat_count(Count), Options),
588 atom_json_term(JSON, _{count:Count}, [as(string)])
589 },
590 ['data-chats'(JSON)].
598background(Options) -->
599 { option(background(Spec), Options), !,
600 download_source(Spec, Source, Options)
601 },
602 html(textarea([ class([source,prolog,background]),
603 style('display:none')
604 ],
605 Source)).
606background(_) --> [].
607
608
609examples(Options) -->
610 { option(examples(Examples), Options), !
611 },
612 html(textarea([ class([examples,prolog]),
613 style('display:none')
614 ],
615 Examples)).
616examples(_) --> [].
617
618
619query(Options) -->
620 { option(q(Query), Options)
621 }, !,
622 html(textarea([ class([query,prolog]),
623 style('display:none')
624 ],
625 Query)).
626query(_) --> [].
633notebooks(swinb, Options) -->
634 { option(code(Spec), Options),
635 download_source(Spec, NoteBookText, Options),
636 phrase(source_data_attrs(Options), Extra)
637 },
638 html(div([ class('notebook'),
639 'data-label'('Notebook') 640 ],
641 [ pre([ class('notebook-data'),
642 style('display:none')
643 | Extra
644 ],
645 NoteBookText)
646 ])).
647notebooks(_, _) --> [].
664download_source(HREF, Source, Options) :-
665 uri_is_global(HREF), !,
666 option(timeout(TMO), Options, 10),
667 option(max_length(MaxLen), Options, 1_000_000),
668 catch(call_with_time_limit(
669 TMO,
670 setup_call_cleanup(
671 http_open(HREF, In,
672 [ cert_verify_hook(cert_accept_any)
673 ]),
674 read_source(In, MaxLen, Source, Options),
675 close(In))),
676 E, load_error(E, Source)).
677download_source(Source0, Source, Options) :-
678 option(max_length(MaxLen), Options, 1_000_000),
679 string_length(Source0, Len),
680 ( Len =< MaxLen
681 -> Source = Source0
682 ; format(string(Source),
683 '% ERROR: Content too long (max ~D)~n', [MaxLen])
684 ).
685
686read_source(In, MaxLen, Source, Options) :-
687 option(encoding(Enc), Options, utf8),
688 set_stream(In, encoding(Enc)),
689 ReadMax is MaxLen + 1,
690 read_string(In, ReadMax, Source0),
691 string_length(Source0, Len),
692 ( Len =< MaxLen
693 -> Source = Source0
694 ; format(string(Source),
695 ' % ERROR: Content too long (max ~D)~n', [MaxLen])
696 ).
697
698load_error(E, Source) :-
699 message_to_string(E, String),
700 format(string(Source), '% ERROR: ~s~n', [String]).
708document_type(Type, Options) :-
709 ( option(type(Type0), Options)
710 -> Type = Type0
711 ; option(meta(Meta), Options),
712 file_name_extension(_, Type0, Meta.name),
713 Type0 \== ''
714 -> Type = Type0
715 ; option(st_type(external), Options),
716 option(url(URL), Options),
717 file_name_extension(_, Ext, URL),
718 ext_type(Ext, Type)
719 -> true
720 ; Type = pl
721 ).
722
723ext_type(swinb, swinb).
724
725
726
736swish_resources -->
737 swish_css,
738 swish_js.
739
740swish_js --> html_post(head, \include_swish_js).
741swish_css --> html_post(head, \include_swish_css).
742
743include_swish_js -->
744 { swish_resource(js, JS),
745 swish_resource(rjs, RJS),
746 http_absolute_location(swish(js/JS), SwishJS, []),
747 http_absolute_location(swish(RJS), SwishRJS, [])
748 },
749 rjs_timeout(JS),
750 html(script([ src(SwishRJS),
751 'data-main'(SwishJS)
752 ], [])).
753
754rjs_timeout('swish-min') --> !,
755 js_script({|javascript||
756// Override RequireJS timeout, until main file is loaded.
757window.require = { waitSeconds: 0 };
758 |}).
759rjs_timeout(_) --> [].
760
761
762include_swish_css -->
763 { swish_resource(css, CSS),
764 http_absolute_location(swish(css/CSS), SwishCSS, [])
765 },
766 html(link([ rel(stylesheet),
767 href(SwishCSS)
768 ])).
769
770swish_resource(Type, ID) :-
771 alt(Type, ID, File),
772 ( File == (-)
773 ; absolute_file_name(File, _P, [file_errors(fail), access(read)])
774 ), !.
775
776alt(js, 'swish-min', swish_web('js/swish-min.js')) :-
777 \+ debugging(nominified).
778alt(js, 'swish', swish_web('js/swish.js')).
779alt(css, 'swish-min.css', swish_web('css/swish-min.css')) :-
780 \+ debugging(nominified).
781alt(css, 'swish.css', swish_web('css/swish.css')).
782alt(rjs, 'js/require.js', swish_web('js/require.js')) :-
783 \+ debugging(nominified).
784alt(rjs, 'bower_components/requirejs/require.js', -).
785
786
787
796swish_rest_reply(put, Request, Options) :-
797 merge_options(Options, [alias(_)], Options1),
798 source_file(Request, File, Options1), !,
799 option(content_type(String), Request),
800 http_parse_header_value(content_type, String, Type),
801 read_data(Type, Request, Data, Meta),
802 authorized(file(update(File,Meta)), Options1),
803 setup_call_cleanup(
804 open(File, write, Out),
805 format(Out, '~s', [Data]),
806 close(Out)),
807 reply_json_dict(true).
808
809read_data(media(Type,_), Request, Data, Meta) :-
810 http_json:json_type(Type), !,
811 http_read_json_dict(Request, Dict),
812 del_dict(data, Dict, Data, Meta).
813read_data(media(text/_,_), Request, Data, _{}) :-
814 http_read_data(Request, Data, [to(string)])
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. */