View source with raw comments or as raw
    1/*  Part of SWISH
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2014-2018, VU University Amsterdam
    7			      CWI, Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(swish_page,
   37	  [ swish_reply/2,			% +Options, +Request
   38	    swish_reply_resource/1,		% +Request
   39	    swish_page//1,			% +Options
   40
   41	    swish_navbar//1,			% +Options
   42	    swish_content//1,			% +Options
   43
   44	    pengine_logo//1,			% +Options
   45	    swish_logo//1,			% +Options
   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).

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. */

   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.
 swish_reply(+Options, +Request)
HTTP handler to reply the default SWISH page. Processes the following parameters:
code(Code)
Use Code as initial code. Code is either an HTTP url or
url(URL)
Download code from URL. As code(URL), but makes the browser download the source rather than the server.
background(Code)
Similar to Code, but not displayed in the editor.
examples(Code)
Provide examples. Each example starts with ?- at the beginning of a line.
q(Query)
Use Query as the initial query.
show_beware(Boolean)
Control showing the beware limited edition warning.
preserve_state(Boolean)
If true, save state on unload and restore old state on load.
  118swish_reply(Options, Request) :-
  119	(   option(identity(_), Options)
  120	->  Options2 = Options
  121	;   authenticate(Request, Auth),
  122	    Options2 = [identity(Auth)|Options]
  123	),
  124	swish_reply2(Options2, Request).
  125
  126swish_reply2(Options, Request) :-
  127	option(method(Method), Request),
  128	Method \== get, Method \== head, !,
  129	swish_rest_reply(Method, Request, Options).
  130swish_reply2(_, Request) :-
  131	swish_reply_resource(Request), !.
  132swish_reply2(Options, Request) :-
  133	swish_reply_config(Request, Options), !.
  134swish_reply2(SwishOptions, Request) :-
  135	Params = [ code(_,	  [optional(true)]),
  136		   url(_,	  [optional(true)]),
  137		   label(_,	  [optional(true)]),
  138		   show_beware(_, [optional(true)]),
  139		   background(_,  [optional(true)]),
  140		   examples(_,    [optional(true)]),
  141		   q(_,           [optional(true)]),
  142		   format(_,      [oneof([swish,raw,json]), default(swish)])
  143		 ],
  144	http_parameters(Request, Params),
  145	params_options(Params, Options0),
  146	add_show_beware(Options0, Options1),
  147	add_preserve_state(Options1, Options2),
  148	merge_options(Options2, SwishOptions, Options3),
  149	source_option(Request, Options3, Options4),
  150	option(format(Format), Options4),
  151	swish_reply3(Format, Options4).
  152
  153swish_reply3(raw, Options) :-
  154	option(code(Code), Options), !,
  155	format('Content-type: text/x-prolog~n~n'),
  156	format('~s', [Code]).
  157swish_reply3(json, Options) :-
  158	option(code(Code), Options), !,
  159	option(meta(Meta), Options, _{}),
  160	option(chat_count(Count), Options, 0),
  161	reply_json_dict(json{data:Code, meta:Meta, chats:_{total:Count}}).
  162swish_reply3(_, Options) :-
  163	swish_config:reply_page(Options), !.
  164swish_reply3(_, Options) :-
  165	reply_html_page(
  166	    swish(main),
  167	    \swish_title(Options),
  168	    \swish_page(Options)).
  169
  170params_options([], []).
  171params_options([H0|T0], [H|T]) :-
  172	arg(1, H0, Value), nonvar(Value), !,
  173	functor(H0, Name, _),
  174	H =.. [Name,Value],
  175	params_options(T0, T).
  176params_options([_|T0], T) :-
  177	params_options(T0, T).
 add_show_beware(+Options0, -Option) is det
Add show_beware(false) when called with code, query or examples. These are dedicated calls that do not justify this message.
  184add_show_beware(Options0, Options) :-
  185	implicit_no_show_beware(Options0), !,
  186	Options = [show_beware(false)|Options0].
  187add_show_beware(Options, Options).
  188
  189implicit_no_show_beware(Options) :-
  190	option(show_beware(_), Options), !,
  191	fail.
  192implicit_no_show_beware(Options) :-
  193	\+ option(format(swish), Options), !,
  194	fail.
  195implicit_no_show_beware(Options) :-
  196	option(code(_), Options).
  197implicit_no_show_beware(Options) :-
  198	option(q(_), Options).
  199implicit_no_show_beware(Options) :-
  200	option(examples(_), Options).
  201implicit_no_show_beware(Options) :-
  202	option(background(_), Options).
 add_preserve_state(+Options0, -Option) is det
Add preserve_state(false) when called with code.
  208add_preserve_state(Options0, Options) :-
  209	option(preserve_state(_), Options0), !,
  210	Options = Options0.
  211add_preserve_state(Options0, Options) :-
  212	option(code(_), Options0), !,
  213	Options = [preserve_state(false)|Options0].
  214add_preserve_state(Options, Options).
 source_option(+Request, +Options0, -Options)
If the data was requested as '/Alias/File', reply using file Alias(File).
  222source_option(_Request, Options0, Options) :-
  223	option(code(Code), Options0),
  224	option(format(swish), Options0), !,
  225	(   uri_is_global(Code)
  226	->  Options = [url(Code),st_type(external)|Options0]
  227	;   Options = Options0
  228	).
  229source_option(_Request, Options0, Options) :-
  230	option(url(_), Options0),
  231	option(format(swish), Options0), !,
  232	Options = [st_type(external),download(browser)|Options0].
  233source_option(Request, Options0, Options) :-
  234	source_file(Request, File, Options0), !,
  235	option(path(Path), Request),
  236	(   source_data(File, String, Options1)
  237	->  append([ [code(String), url(Path), st_type(filesys)],
  238		     Options1,
  239		     Options0
  240		   ], Options)
  241	;   http_404([], Request)
  242	).
  243source_option(_, Options, Options).
 source_file(+Request, -File, +Options) is semidet
File is the file associated with a SWISH request. A file is associated if path_info is provided. If the file does not exist, an HTTP 404 exception is returned. Options:
alias(-Alias)
Get the swish_config:source_alias/2 Alias name that was used to find File.
  255source_file(Request, File, Options) :-
  256	option(path_info(PathInfo), Request), !,
  257	PathInfo \== 'index.html',
  258	(   path_info_file(PathInfo, File, Options)
  259	->  true
  260	;   http_404([], Request)
  261	).
  262
  263path_info_file(PathInfo, Path, Options) :-
  264	sub_atom(PathInfo, B, _, A, /),
  265	sub_atom(PathInfo, 0, B, _, Alias),
  266	sub_atom(PathInfo, _, A, 0, File),
  267	catch(swish_config:source_alias(Alias, AliasOptions), E,
  268	      (print_message(warning, E), fail)),
  269	Spec =.. [Alias,File],
  270	http_safe_file(Spec, []),
  271	absolute_file_name(Spec, Path,
  272			   [ access(read),
  273			     file_errors(fail)
  274			   ]),
  275	confirm_access(Path, AliasOptions), !,
  276	option(alias(Alias), Options, _).
  277
  278source_data(Path, Code, [title(Title), type(Ext), meta(Meta)]) :-
  279	setup_call_cleanup(
  280	    open(Path, read, In, [encoding(utf8)]),
  281	    read_string(In, _, Code),
  282	    close(In)),
  283	source_metadata(Path, Code, Meta),
  284	file_base_name(Path, File),
  285	file_name_extension(Title, Ext, File).
 source_metadata(+Path, +Code, -Meta:dict) is det
Obtain meta information about a local source file. Defined meta info is:
last_modified:Time
Last modified stamp of the file. Always present.
loaded:true
Present of the file is a loaded source file
modified_since_loaded:true
Present if the file loaded, has been edited, but not yet reloaded.
  300source_metadata(Path, Code, Meta) :-
  301	findall(Name-Value, source_metadata(Path, Code, Name, Value), Pairs),
  302	dict_pairs(Meta, meta, Pairs).
  303
  304source_metadata(Path, _Code, path, Path).
  305source_metadata(Path, _Code, last_modified, Modified) :-
  306	time_file(Path, Modified).
  307source_metadata(Path, _Code, loaded, true) :-
  308	source_file(Path).
  309source_metadata(Path, _Code, modified_since_loaded, true) :-
  310	source_file_property(Path, modified(ModifiedWhenLoaded)),
  311	time_file(Path, Modified),
  312	ModifiedWhenLoaded \== Modified.
  313source_metadata(Path, _Code, module, Module) :-
  314	file_name_extension(_, Ext, Path),
  315	user:prolog_file_type(Ext, prolog),
  316	xref_public_list(Path, _, [module(Module)]).
  317
  318confirm_access(Path, Options) :-
  319	option(if(Condition), Options), !,
  320	must_be(oneof([loaded]), Condition),
  321	eval_condition(Condition, Path).
  322confirm_access(_, _).
  323
  324eval_condition(loaded, Path) :-
  325	source_file(Path).
 swish_reply_resource(+Request) is semidet
Serve /swish/Resource files. In recent Bootstrap versions, the path to `fonts/` is generated that should refer to node_modules/bootstrap/dist/fonts. This could be a bug in Bootstrap or in teh CSS cleaning. For now, we hack around the issue here.
  335swish_reply_resource(Request) :-
  336	option(path_info(Info), Request),
  337	resource_prefix(Prefix),
  338	sub_atom(Info, 0, _, _, Prefix), !,
  339	http_reply_file(swish_web(Info), [], Request).
  340swish_reply_resource(Request) :-	% see above
  341	option(path_info(Info), Request),
  342	sub_atom(Info, 0, _, _, 'fonts/'), !,
  343	atom_concat('node_modules/bootstrap/dist/', Info, Path),
  344	http_reply_file(swish_web(Path), [], Request).
  345
  346resource_prefix('css/').
  347resource_prefix('help/').
  348resource_prefix('form/').
  349resource_prefix('icons/').
  350resource_prefix('js/').
  351resource_prefix('node_modules/').
 swish_page(+Options)//
Generate the entire SWISH default page.
  357swish_page(Options) -->
  358	swish_navbar(Options),
  359	swish_content(Options).
 swish_navbar(+Options)//
Generate the swish navigation bar.
  365swish_navbar(Options) -->
  366	swish_resources,
  367	html(nav([ class([navbar, 'navbar-default']),
  368		   role(navigation)
  369		 ],
  370		 [ div(class('navbar-header'),
  371		       [ \collapsed_button,
  372			 \swish_logos(Options)
  373		       ]),
  374		   div([ class([collapse, 'navbar-collapse']),
  375			 id(navbar)
  376		       ],
  377		       [ ul([class([nav, 'navbar-nav', menubar])], []),
  378			 ul([class([nav, 'navbar-nav', 'navbar-right'])],
  379			    [ li(\notifications(Options)),
  380			      li(\search_box(Options)),
  381			      \li_login_button(Options),
  382			      li(\broadcast_bell(Options)),
  383			      li(\updates(Options))
  384			    ])
  385		       ])
  386		 ])).
  387
  388li_login_button(Options) -->
  389	swish_config:li_login_button(Options).
  390li_login_button(_Options) -->
  391	[].
  392
  393collapsed_button -->
  394	html(button([type(button),
  395		     class('navbar-toggle'),
  396		     'data-toggle'(collapse),
  397		     'data-target'('#navbar')
  398		    ],
  399		    [ span(class('sr-only'), 'Toggle navigation'),
  400		      span(class('icon-bar'), []),
  401		      span(class('icon-bar'), []),
  402		      span(class('icon-bar'), [])
  403		    ])).
  404
  405updates(_Options) -->
  406	html([ a(id('swish-updates'), []) ]).
  407
  408
  409		 /*******************************
  410		 *	      BRANDING		*
  411		 *******************************/
 swish_title(+Options)// is det
Emit the HTML header options dealing with the title and shortcut icons. This can be hooked using title//1.
  418swish_title(Options) -->
  419	swish_config:title(Options), !.
  420swish_title(_Options) -->
  421	html([ title('SWISH -- SWI-Prolog for SHaring'),
  422	       link([ rel('shortcut icon'),
  423		      href('/icons/favicon.ico')
  424		    ]),
  425	       link([ rel('apple-touch-icon'),
  426		      href('/icons/swish-touch-icon.png')
  427		    ])
  428	     ]).
 swish_logos(+Options)// is det
Emit the navbar branding logos at the top-left. Can be hooked using swish_logos//1.
  435swish_logos(Options) -->
  436	swish_config:logo(Options), !.
  437swish_logos(Options) -->
  438	pengine_logo(Options),
  439	swish_logo(Options).
 swish_config:logo(+Options)// is semidet
Hook to include the top-left logos. The default calls pengine_logo//1 and swish_logo//1. The implementation should emit zero or more <a> elements. See config_available/branding.pl for an example.
 pengine_logo(+Options)// is det
 swish_logo(+Options)// is det
Emit an <a> element that provides a link to Pengines and SWISH on this server. These may be called from swish_config:logo//1 to include the default logos.
  455pengine_logo(_Options) -->
  456	{ http_absolute_location(root(.), HREF, [])
  457	},
  458	html(a([href(HREF), class('pengine-logo')], &(nbsp))).
  459swish_logo(_Options) -->
  460	{ http_absolute_location(swish(.), HREF, [])
  461	},
  462	html(a([href(HREF), class('swish-logo')], &(nbsp))).
  463
  464
  465		 /*******************************
  466		 *	     CONTENT		*
  467		 *******************************/
 swish_content(+Options)//
Generate the SWISH editor, Prolog output area and query editor. Options processed:
source(HREF)
Load initial source from HREF
chat_count(Count)
Indicate the presense of Count chat messages
  479swish_content(Options) -->
  480	{ document_type(Type, Options)
  481	},
  482	swish_resources,
  483	swish_config_hash(Options),
  484	swish_options(Options),
  485	html(div([id(content), class([container, 'tile-top'])],
  486		 [ div([class([tile, horizontal]), 'data-split'('50%')],
  487		       [ div([ class([editors, tabbed])
  488			     ],
  489			     [ \source(Type, Options),
  490			       \notebooks(Type, Options)
  491			     ]),
  492			 div([class([tile, vertical]), 'data-split'('70%')],
  493			     [ div(class('prolog-runners'), []),
  494			       div(class('prolog-query'), \query(Options))
  495			     ])
  496		       ]),
  497		   \background(Options),
  498		   \examples(Options)
  499		 ])).
 swish_config_hash(+Options)//
Set window.swish.config_hash to a hash that represents the current configuration. This is used by config.js to cache the configuration in the browser's local store.
  508swish_config_hash(Options) -->
  509	{ swish_config_hash(Hash, Options) },
  510	js_script({|javascript(Hash)||
  511		   window.swish = window.swish||{};
  512		   window.swish.config_hash = Hash;
  513		   |}).
 swish_options(+Options)//
Emit additional options. This is similar to config, but the config object is big and stable for a particular SWISH server. The options are set per session.
  522swish_options(Options) -->
  523	js_script({|javascript||
  524		   window.swish = window.swish||{};
  525		   window.swish.option = window.swish.option||{};
  526		  |}),
  527	swish_options([show_beware, preserve_state], Options).
  528
  529swish_options([], _) --> [].
  530swish_options([H|T], Options) -->
  531	swish_option(H, Options),
  532	swish_options(T, Options).
  533
  534swish_option(Name, Options) -->
  535	{ Opt =.. [Name,Val],
  536	  option(Opt, Options),
  537	  JSVal = @(Val)
  538	}, !,
  539	js_script({|javascript(Name, JSVal)||
  540		   window.swish.option[Name] = JSVal;
  541		   |}).
  542swish_option(_, _) -->
  543	[].
 source(+Type, +Options)//
Associate the source with the SWISH page. The source itself is stored in the textarea from which CodeMirror is created. Options:
code(+String)
Initial code of the source editor
file(+File)
If present and code(String) is present, also associate the editor with the given file. See storage.pl.
url(+URL)
as file(File), but used if the data is loaded from an alias/file path.
title(+Title)
Defines the title used for the tab.
  562source(pl, Options) -->
  563	{ (   option(code(Spec), Options)
  564	  ;   option(download(browser), Options)
  565          ),
  566          !,
  567          download_source(Spec, Source, Options),
  568	  phrase(source_data_attrs(Options), Extra),
  569          option(label(Label), Options, 'Program')
  570	},
  571	html(div([ class(['prolog-editor']),
  572		   'data-label'(Label)
  573		 ],
  574		 [ textarea([ class([source,prolog]),
  575			      style('display:none')
  576			    | Extra
  577			    ],
  578			    Source)
  579		 ])).
  580source(_, _) --> [].
  581
  582source_data_attrs(Options) -->
  583	(source_file_data(Options) -> [] ; []),
  584	(source_url_data(Options) -> [] ; []),
  585	(source_download_data(Options) -> [] ; []),
  586	(source_title_data(Options) -> [] ; []),
  587	(source_meta_data(Options) -> [] ; []),
  588	(source_st_type_data(Options) -> [] ; []),
  589	(source_chat_data(Options) -> [] ; []).
  590
  591source_file_data(Options) -->
  592	{ option(file(File), Options) },
  593	['data-file'(File)].
  594source_url_data(Options) -->
  595	{ option(url(URL), Options) },
  596	['data-url'(URL)].
  597source_download_data(Options) -->
  598	{ option(download(Who), Options) },
  599	['data-download'(Who)].
  600source_title_data(Options) -->
  601	{ option(title(File), Options) },
  602	['data-title'(File)].
  603source_st_type_data(Options) -->
  604	{ option(st_type(Type), Options) },
  605	['data-st_type'(Type)].
  606source_meta_data(Options) -->
  607	{ option(meta(Meta), Options), !,
  608	  atom_json_dict(Text, Meta, [])
  609	},
  610	['data-meta'(Text)].
  611source_chat_data(Options) -->
  612	{ option(chat_count(Count), Options),
  613	  atom_json_term(JSON, _{count:Count}, [as(string)])
  614	},
  615	['data-chats'(JSON)].
 background(+Options)//
Associate the background program (if any). The background program is not displayed in the editor, but is sent to the pengine for execution.
  623background(Options) -->
  624	{ option(background(Spec), Options), !,
  625	  download_source(Spec, Source, Options)
  626	},
  627	html(textarea([ class([source,prolog,background]),
  628			style('display:none')
  629		      ],
  630		      Source)).
  631background(_) --> [].
  632
  633
  634examples(Options) -->
  635	{ option(examples(Examples), Options), !
  636	},
  637	html(textarea([ class([examples,prolog]),
  638			style('display:none')
  639		      ],
  640		      Examples)).
  641examples(_) --> [].
  642
  643
  644query(Options) -->
  645	{ option(q(Query), Options)
  646	}, !,
  647	html(textarea([ class([query,prolog]),
  648			style('display:none')
  649		      ],
  650		      Query)).
  651query(_) --> [].
 notebooks(+Type, +Options)//
We have opened a notebook. Embed the notebook data in the left-pane tab area.
  658notebooks(swinb, Options) -->
  659	{ option(code(Spec), Options),
  660	  download_source(Spec, NoteBookText, Options),
  661	  phrase(source_data_attrs(Options), Extra)
  662	},
  663	html(div([ class('notebook'),
  664		   'data-label'('Notebook')		% Use file?
  665		 ],
  666		 [ pre([ class('notebook-data'),
  667			 style('display:none')
  668		       | Extra
  669		       ],
  670		       NoteBookText)
  671		 ])).
  672notebooks(_, _) --> [].
 download_source(+HREF, -Source, +Options) is det
Download source from a URL. Options processed:
timeout(+Seconds)
Max time to wait for reading the source. Default is 10 seconds.
max_length(+Chars)
Maximum lenght of the content. Default is 1 million.
encoding(+Encoding)
Encoding used to interpret the text. Default is UTF-8.
bug
- : Should try to interpret the encoding from the HTTP header.
  689download_source(_HREF, Source, Options) :-
  690	option(download(browser), Options),
  691	!,
  692        Source = "".
  693download_source(HREF, Source, Options) :-
  694	uri_is_global(HREF), !,
  695	download_href(HREF, Source, Options).
  696download_source(Source0, Source, Options) :-
  697	option(max_length(MaxLen), Options, 1_000_000),
  698	string_length(Source0, Len),
  699	(   Len =< MaxLen
  700	->  Source = Source0
  701	;   format(string(Source),
  702		   '% ERROR: Content too long (max ~D)~n', [MaxLen])
  703	).
  704
  705download_href(HREF, Source, Options) :-
  706	option(timeout(TMO), Options, 10),
  707	option(max_length(MaxLen), Options, 1_000_000),
  708	catch(call_with_time_limit(
  709		  TMO,
  710		  setup_call_cleanup(
  711		      http_open(HREF, In,
  712				[ cert_verify_hook(cert_accept_any)
  713				]),
  714		      read_source(In, MaxLen, Source, Options),
  715		      close(In))),
  716	      E, load_error(E, Source)).
  717
  718read_source(In, MaxLen, Source, Options) :-
  719	option(encoding(Enc), Options, utf8),
  720	set_stream(In, encoding(Enc)),
  721	ReadMax is MaxLen + 1,
  722	read_string(In, ReadMax, Source0),
  723	string_length(Source0, Len),
  724	(   Len =< MaxLen
  725	->  Source = Source0
  726	;   format(string(Source),
  727		   ' % ERROR: Content too long (max ~D)~n', [MaxLen])
  728	).
  729
  730load_error(E, Source) :-
  731	message_to_string(E, String),
  732	format(string(Source), '% ERROR: ~s~n', [String]).
 document_type(-Type, +Options) is det
Determine the type of document.
Arguments:
Type- is one of swinb or pl
  740document_type(Type, Options) :-
  741	(   option(type(Type0), Options)
  742	->  Type = Type0
  743	;   option(meta(Meta), Options),
  744	    file_name_extension(_, Type0, Meta.name),
  745	    Type0 \== ''
  746	->  Type = Type0
  747	;   option(st_type(external), Options),
  748	    option(url(URL), Options),
  749	    file_name_extension(_, Ext, URL),
  750	    ext_type(Ext, Type)
  751	->  true
  752	;   Type = pl
  753	).
  754
  755ext_type(swinb, swinb).
  756
  757
  758		 /*******************************
  759		 *	     RESOURCES		*
  760		 *******************************/
 swish_resources//
Include SWISH CSS and JavaScript. This does not use html_require//1 because we need to include the JS using RequireJS, which requires a non-standard script element.
  768swish_resources -->
  769	swish_css,
  770	swish_js.
  771
  772swish_js  --> html_post(head, \include_swish_js).
  773swish_css --> html_post(head, \include_swish_css).
  774
  775include_swish_js -->
  776	{ swish_resource(js, JS),
  777	  swish_resource(rjs, RJS),
  778	  http_absolute_location(swish(js/JS), SwishJS, []),
  779	  http_absolute_location(swish(RJS),   SwishRJS, [])
  780	},
  781	rjs_timeout(JS),
  782	html(script([ src(SwishRJS),
  783		      'data-main'(SwishJS)
  784		    ], [])).
  785
  786rjs_timeout('swish-min') --> !,
  787	js_script({|javascript||
  788// Override RequireJS timeout, until main file is loaded.
  789window.require = { waitSeconds: 0 };
  790		  |}).
  791rjs_timeout(_) --> [].
  792
  793
  794include_swish_css -->
  795	{ swish_resource(css, CSS),
  796	  http_absolute_location(swish(css/CSS), SwishCSS, [])
  797	},
  798	html(link([ rel(stylesheet),
  799		    href(SwishCSS)
  800		  ])).
  801
  802swish_resource(Type, ID) :-
  803	alt(Type, ID, File),
  804	(   File == (-)
  805	;   absolute_file_name(File, _P, [file_errors(fail), access(read)])
  806	), !.
  807
  808alt(js,  'swish-min',     swish_web('js/swish-min.js')) :-
  809	\+ debugging(nominified).
  810alt(js,  'swish',         swish_web('js/swish.js')).
  811alt(css, 'swish-min.css', swish_web('css/swish-min.css')) :-
  812	\+ debugging(nominified).
  813alt(css, 'swish.css',     swish_web('css/swish.css')).
  814alt(rjs, 'js/require.js', swish_web('js/require.js')) :-
  815	\+ debugging(nominified).
  816alt(rjs, 'node_modules/requirejs/require.js', -).
  817
  818
  819		 /*******************************
  820		 *	       REST		*
  821		 *******************************/
 swish_rest_reply(+Method, +Request, +Options) is det
Handle non-GET requests. Such requests may be used to modify source code.
  828swish_rest_reply(put, Request, Options) :-
  829	merge_options(Options, [alias(_)], Options1),
  830	source_file(Request, File, Options1), !,
  831	option(content_type(String), Request),
  832	http_parse_header_value(content_type, String, Type),
  833	read_data(Type, Request, Data, Meta),
  834	authorized(file(update(File,Meta)), Options1),
  835	setup_call_cleanup(
  836	    open(File, write, Out, [encoding(utf8)]),
  837	    format(Out, '~s', [Data]),
  838	    close(Out)),
  839	reply_json_dict(true).
  840
  841read_data(media(Type,_), Request, Data, Meta) :-
  842	http_json:json_type(Type), !,
  843	http_read_json_dict(Request, Dict),
  844	del_dict(data, Dict, Data, Meta).
  845read_data(media(text/_,_), Request, Data, _{}) :-
  846	http_read_data(Request, Data,
  847		       [ to(string),
  848			 input_encoding(utf8)
  849		       ])