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.
  331swish_reply_resource(Request) :-
  332	option(path_info(Info), Request),
  333	resource_prefix(Prefix),
  334	sub_atom(Info, 0, _, _, Prefix), !,
  335	http_reply_file(swish_web(Info), [], Request).
  336
  337resource_prefix('css/').
  338resource_prefix('help/').
  339resource_prefix('form/').
  340resource_prefix('icons/').
  341resource_prefix('js/').
  342resource_prefix('node_modules/').
 swish_page(+Options)//
Generate the entire SWISH default page.
  348swish_page(Options) -->
  349	swish_navbar(Options),
  350	swish_content(Options).
 swish_navbar(+Options)//
Generate the swish navigation bar.
  356swish_navbar(Options) -->
  357	swish_resources,
  358	html(nav([ class([navbar, 'navbar-default']),
  359		   role(navigation)
  360		 ],
  361		 [ div(class('navbar-header'),
  362		       [ \collapsed_button,
  363			 \swish_logos(Options)
  364		       ]),
  365		   div([ class([collapse, 'navbar-collapse']),
  366			 id(navbar)
  367		       ],
  368		       [ ul([class([nav, 'navbar-nav', menubar])], []),
  369			 ul([class([nav, 'navbar-nav', 'navbar-right'])],
  370			    [ li(\notifications(Options)),
  371			      li(\search_box(Options)),
  372			      \li_login_button(Options),
  373			      li(\broadcast_bell(Options)),
  374			      li(\updates(Options))
  375			    ])
  376		       ])
  377		 ])).
  378
  379li_login_button(Options) -->
  380	swish_config:li_login_button(Options).
  381li_login_button(_Options) -->
  382	[].
  383
  384collapsed_button -->
  385	html(button([type(button),
  386		     class('navbar-toggle'),
  387		     'data-toggle'(collapse),
  388		     'data-target'('#navbar')
  389		    ],
  390		    [ span(class('sr-only'), 'Toggle navigation'),
  391		      span(class('icon-bar'), []),
  392		      span(class('icon-bar'), []),
  393		      span(class('icon-bar'), [])
  394		    ])).
  395
  396updates(_Options) -->
  397	html([ a(id('swish-updates'), []) ]).
  398
  399
  400		 /*******************************
  401		 *	      BRANDING		*
  402		 *******************************/
 swish_title(+Options)// is det
Emit the HTML header options dealing with the title and shortcut icons. This can be hooked using title//1.
  409swish_title(Options) -->
  410	swish_config:title(Options), !.
  411swish_title(_Options) -->
  412	html([ title('SWISH -- SWI-Prolog for SHaring'),
  413	       link([ rel('shortcut icon'),
  414		      href('/icons/favicon.ico')
  415		    ]),
  416	       link([ rel('apple-touch-icon'),
  417		      href('/icons/swish-touch-icon.png')
  418		    ])
  419	     ]).
 swish_logos(+Options)// is det
Emit the navbar branding logos at the top-left. Can be hooked using swish_logos//1.
  426swish_logos(Options) -->
  427	swish_config:logo(Options), !.
  428swish_logos(Options) -->
  429	pengine_logo(Options),
  430	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.
  446pengine_logo(_Options) -->
  447	{ http_absolute_location(root(.), HREF, [])
  448	},
  449	html(a([href(HREF), class('pengine-logo')], &(nbsp))).
  450swish_logo(_Options) -->
  451	{ http_absolute_location(swish(.), HREF, [])
  452	},
  453	html(a([href(HREF), class('swish-logo')], &(nbsp))).
  454
  455
  456		 /*******************************
  457		 *	     CONTENT		*
  458		 *******************************/
 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
  470swish_content(Options) -->
  471	{ document_type(Type, Options)
  472	},
  473	swish_resources,
  474	swish_config_hash(Options),
  475	swish_options(Options),
  476	html(div([id(content), class([container, 'tile-top'])],
  477		 [ div([class([tile, horizontal]), 'data-split'('50%')],
  478		       [ div([ class([editors, tabbed])
  479			     ],
  480			     [ \source(Type, Options),
  481			       \notebooks(Type, Options)
  482			     ]),
  483			 div([class([tile, vertical]), 'data-split'('70%')],
  484			     [ div(class('prolog-runners'), []),
  485			       div(class('prolog-query'), \query(Options))
  486			     ])
  487		       ]),
  488		   \background(Options),
  489		   \examples(Options)
  490		 ])).
 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.
  499swish_config_hash(Options) -->
  500	{ swish_config_hash(Hash, Options) },
  501	js_script({|javascript(Hash)||
  502		   window.swish = window.swish||{};
  503		   window.swish.config_hash = Hash;
  504		   |}).
 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.
  513swish_options(Options) -->
  514	js_script({|javascript||
  515		   window.swish = window.swish||{};
  516		   window.swish.option = window.swish.option||{};
  517		  |}),
  518	swish_options([show_beware, preserve_state], Options).
  519
  520swish_options([], _) --> [].
  521swish_options([H|T], Options) -->
  522	swish_option(H, Options),
  523	swish_options(T, Options).
  524
  525swish_option(Name, Options) -->
  526	{ Opt =.. [Name,Val],
  527	  option(Opt, Options),
  528	  JSVal = @(Val)
  529	}, !,
  530	js_script({|javascript(Name, JSVal)||
  531		   window.swish.option[Name] = JSVal;
  532		   |}).
  533swish_option(_, _) -->
  534	[].
 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.
  553source(pl, Options) -->
  554	{ (   option(code(Spec), Options)
  555	  ;   option(download(browser), Options)
  556          ),
  557          !,
  558          download_source(Spec, Source, Options),
  559	  phrase(source_data_attrs(Options), Extra),
  560          option(label(Label), Options, 'Program')
  561	},
  562	html(div([ class(['prolog-editor']),
  563		   'data-label'(Label)
  564		 ],
  565		 [ textarea([ class([source,prolog]),
  566			      style('display:none')
  567			    | Extra
  568			    ],
  569			    Source)
  570		 ])).
  571source(_, _) --> [].
  572
  573source_data_attrs(Options) -->
  574	(source_file_data(Options) -> [] ; []),
  575	(source_url_data(Options) -> [] ; []),
  576	(source_download_data(Options) -> [] ; []),
  577	(source_title_data(Options) -> [] ; []),
  578	(source_meta_data(Options) -> [] ; []),
  579	(source_st_type_data(Options) -> [] ; []),
  580	(source_chat_data(Options) -> [] ; []).
  581
  582source_file_data(Options) -->
  583	{ option(file(File), Options) },
  584	['data-file'(File)].
  585source_url_data(Options) -->
  586	{ option(url(URL), Options) },
  587	['data-url'(URL)].
  588source_download_data(Options) -->
  589	{ option(download(Who), Options) },
  590	['data-download'(Who)].
  591source_title_data(Options) -->
  592	{ option(title(File), Options) },
  593	['data-title'(File)].
  594source_st_type_data(Options) -->
  595	{ option(st_type(Type), Options) },
  596	['data-st_type'(Type)].
  597source_meta_data(Options) -->
  598	{ option(meta(Meta), Options), !,
  599	  atom_json_dict(Text, Meta, [])
  600	},
  601	['data-meta'(Text)].
  602source_chat_data(Options) -->
  603	{ option(chat_count(Count), Options),
  604	  atom_json_term(JSON, _{count:Count}, [as(string)])
  605	},
  606	['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.
  614background(Options) -->
  615	{ option(background(Spec), Options), !,
  616	  download_source(Spec, Source, Options)
  617	},
  618	html(textarea([ class([source,prolog,background]),
  619			style('display:none')
  620		      ],
  621		      Source)).
  622background(_) --> [].
  623
  624
  625examples(Options) -->
  626	{ option(examples(Examples), Options), !
  627	},
  628	html(textarea([ class([examples,prolog]),
  629			style('display:none')
  630		      ],
  631		      Examples)).
  632examples(_) --> [].
  633
  634
  635query(Options) -->
  636	{ option(q(Query), Options)
  637	}, !,
  638	html(textarea([ class([query,prolog]),
  639			style('display:none')
  640		      ],
  641		      Query)).
  642query(_) --> [].
 notebooks(+Type, +Options)//
We have opened a notebook. Embed the notebook data in the left-pane tab area.
  649notebooks(swinb, Options) -->
  650	{ option(code(Spec), Options),
  651	  download_source(Spec, NoteBookText, Options),
  652	  phrase(source_data_attrs(Options), Extra)
  653	},
  654	html(div([ class('notebook'),
  655		   'data-label'('Notebook')		% Use file?
  656		 ],
  657		 [ pre([ class('notebook-data'),
  658			 style('display:none')
  659		       | Extra
  660		       ],
  661		       NoteBookText)
  662		 ])).
  663notebooks(_, _) --> [].
 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.
  680download_source(_HREF, Source, Options) :-
  681	option(download(browser), Options),
  682	!,
  683        Source = "".
  684download_source(HREF, Source, Options) :-
  685	uri_is_global(HREF), !,
  686	download_href(HREF, Source, Options).
  687download_source(Source0, Source, Options) :-
  688	option(max_length(MaxLen), Options, 1_000_000),
  689	string_length(Source0, Len),
  690	(   Len =< MaxLen
  691	->  Source = Source0
  692	;   format(string(Source),
  693		   '% ERROR: Content too long (max ~D)~n', [MaxLen])
  694	).
  695
  696download_href(HREF, Source, Options) :-
  697	option(timeout(TMO), Options, 10),
  698	option(max_length(MaxLen), Options, 1_000_000),
  699	catch(call_with_time_limit(
  700		  TMO,
  701		  setup_call_cleanup(
  702		      http_open(HREF, In,
  703				[ cert_verify_hook(cert_accept_any)
  704				]),
  705		      read_source(In, MaxLen, Source, Options),
  706		      close(In))),
  707	      E, load_error(E, Source)).
  708
  709read_source(In, MaxLen, Source, Options) :-
  710	option(encoding(Enc), Options, utf8),
  711	set_stream(In, encoding(Enc)),
  712	ReadMax is MaxLen + 1,
  713	read_string(In, ReadMax, Source0),
  714	string_length(Source0, Len),
  715	(   Len =< MaxLen
  716	->  Source = Source0
  717	;   format(string(Source),
  718		   ' % ERROR: Content too long (max ~D)~n', [MaxLen])
  719	).
  720
  721load_error(E, Source) :-
  722	message_to_string(E, String),
  723	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
  731document_type(Type, Options) :-
  732	(   option(type(Type0), Options)
  733	->  Type = Type0
  734	;   option(meta(Meta), Options),
  735	    file_name_extension(_, Type0, Meta.name),
  736	    Type0 \== ''
  737	->  Type = Type0
  738	;   option(st_type(external), Options),
  739	    option(url(URL), Options),
  740	    file_name_extension(_, Ext, URL),
  741	    ext_type(Ext, Type)
  742	->  true
  743	;   Type = pl
  744	).
  745
  746ext_type(swinb, swinb).
  747
  748
  749		 /*******************************
  750		 *	     RESOURCES		*
  751		 *******************************/
 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.
  759swish_resources -->
  760	swish_css,
  761	swish_js.
  762
  763swish_js  --> html_post(head, \include_swish_js).
  764swish_css --> html_post(head, \include_swish_css).
  765
  766include_swish_js -->
  767	{ swish_resource(js, JS),
  768	  swish_resource(rjs, RJS),
  769	  http_absolute_location(swish(js/JS), SwishJS, []),
  770	  http_absolute_location(swish(RJS),   SwishRJS, [])
  771	},
  772	rjs_timeout(JS),
  773	html(script([ src(SwishRJS),
  774		      'data-main'(SwishJS)
  775		    ], [])).
  776
  777rjs_timeout('swish-min') --> !,
  778	js_script({|javascript||
  779// Override RequireJS timeout, until main file is loaded.
  780window.require = { waitSeconds: 0 };
  781		  |}).
  782rjs_timeout(_) --> [].
  783
  784
  785include_swish_css -->
  786	{ swish_resource(css, CSS),
  787	  http_absolute_location(swish(css/CSS), SwishCSS, [])
  788	},
  789	html(link([ rel(stylesheet),
  790		    href(SwishCSS)
  791		  ])).
  792
  793swish_resource(Type, ID) :-
  794	alt(Type, ID, File),
  795	(   File == (-)
  796	;   absolute_file_name(File, _P, [file_errors(fail), access(read)])
  797	), !.
  798
  799alt(js,  'swish-min',     swish_web('js/swish-min.js')) :-
  800	\+ debugging(nominified).
  801alt(js,  'swish',         swish_web('js/swish.js')).
  802alt(css, 'swish-min.css', swish_web('css/swish-min.css')) :-
  803	\+ debugging(nominified).
  804alt(css, 'swish.css',     swish_web('css/swish.css')).
  805alt(rjs, 'js/require.js', swish_web('js/require.js')) :-
  806	\+ debugging(nominified).
  807alt(rjs, 'node_modules/requirejs/require.js', -).
  808
  809
  810		 /*******************************
  811		 *	       REST		*
  812		 *******************************/
 swish_rest_reply(+Method, +Request, +Options) is det
Handle non-GET requests. Such requests may be used to modify source code.
  819swish_rest_reply(put, Request, Options) :-
  820	merge_options(Options, [alias(_)], Options1),
  821	source_file(Request, File, Options1), !,
  822	option(content_type(String), Request),
  823	http_parse_header_value(content_type, String, Type),
  824	read_data(Type, Request, Data, Meta),
  825	authorized(file(update(File,Meta)), Options1),
  826	setup_call_cleanup(
  827	    open(File, write, Out, [encoding(utf8)]),
  828	    format(Out, '~s', [Data]),
  829	    close(Out)),
  830	reply_json_dict(true).
  831
  832read_data(media(Type,_), Request, Data, Meta) :-
  833	http_json:json_type(Type), !,
  834	http_read_json_dict(Request, Dict),
  835	del_dict(data, Dict, Data, Meta).
  836read_data(media(text/_,_), Request, Data, _{}) :-
  837	http_read_data(Request, Data,
  838		       [ to(string),
  839			 input_encoding(utf8)
  840		       ])