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-2017, VU University Amsterdam
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(swish_page,
   36	  [ swish_reply/2,			% +Options, +Request
   37	    swish_page//1,			% +Options
   38
   39	    swish_navbar//1,			% +Options
   40	    swish_content//1,			% +Options
   41
   42	    pengine_logo//1,			% +Options
   43	    swish_logo//1,			% +Options
   44
   45	    swish_resources//0,
   46	    swish_js//0,
   47	    swish_css//0
   48	  ]).   49:- use_module(library(http/http_open)).   50:- use_module(library(http/http_dispatch)).   51:- use_module(library(http/http_parameters)).   52:- use_module(library(http/http_header)).   53:- use_module(library(http/html_write)).   54:- use_module(library(http/js_write)).   55:- use_module(library(http/json)).   56:- use_module(library(http/http_json)).   57:- use_module(library(http/http_path)).   58:- if(exists_source(library(http/http_ssl_plugin))).   59:- use_module(library(http/http_ssl_plugin)).   60:- endif.   61:- use_module(library(debug)).   62:- use_module(library(time)).   63:- use_module(library(lists)).   64:- use_module(library(option)).   65:- use_module(library(uri)).   66:- use_module(library(error)).   67:- use_module(library(http/http_client)).   68
   69:- use_module(config).   70:- use_module(help).   71:- use_module(search).   72:- use_module(chat).   73:- use_module(authenticate).   74:- 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. */

   83http:location(pldoc, swish(pldoc), [priority(100)]).
   84
   85:- http_handler(swish(.), swish_reply([]), [id(swish), prefix]).   86
   87:- multifile
   88	swish_config:logo//1,
   89	swish_config:source_alias/2,
   90	swish_config:reply_page/1,
   91	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 concrete source code.
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.
  111swish_reply(Options, Request) :-
  112	authenticate(Request, Auth),
  113	swish_reply2([identity(Auth)|Options], Request).
  114
  115swish_reply2(Options, Request) :-
  116	option(method(Method), Request),
  117	Method \== get, Method \== head, !,
  118	swish_rest_reply(Method, Request, Options).
  119swish_reply2(_, Request) :-
  120	serve_resource(Request), !.
  121swish_reply2(Options, Request) :-
  122	swish_reply_config(Request, Options), !.
  123swish_reply2(SwishOptions, Request) :-
  124	Params = [ code(_,	  [optional(true)]),
  125		   show_beware(_, [optional(true)]),
  126		   background(_,  [optional(true)]),
  127		   examples(_,    [optional(true)]),
  128		   q(_,           [optional(true)]),
  129		   format(_,      [oneof([swish,raw,json]), default(swish)])
  130		 ],
  131	http_parameters(Request, Params),
  132	params_options(Params, Options0),
  133	merge_options(Options0, SwishOptions, Options1),
  134	add_show_beware(Options1, Options2),
  135	source_option(Request, Options2, Options3),
  136	option(format(Format), Options3),
  137	swish_reply3(Format, Options3).
  138
  139swish_reply3(raw, Options) :-
  140	option(code(Code), Options), !,
  141	format('Content-type: text/x-prolog~n~n'),
  142	format('~s', [Code]).
  143swish_reply3(json, Options) :-
  144	option(code(Code), Options), !,
  145	option(meta(Meta), Options, _{}),
  146	option(chat_count(Count), Options, 0),
  147	reply_json_dict(json{data:Code, meta:Meta, chats:_{count:Count}}).
  148swish_reply3(_, Options) :-
  149	swish_config:reply_page(Options), !.
  150swish_reply3(_, Options) :-
  151	reply_html_page(
  152	    swish(main),
  153	    [ title('SWISH -- SWI-Prolog for SHaring'),
  154	      link([ rel('shortcut icon'),
  155		     href('/icons/favicon.ico')
  156		   ]),
  157	      link([ rel('apple-touch-icon'),
  158		     href('/icons/swish-touch-icon.png')
  159		   ])
  160	    ],
  161	    \swish_page(Options)).
  162
  163params_options([], []).
  164params_options([H0|T0], [H|T]) :-
  165	arg(1, H0, Value), nonvar(Value), !,
  166	functor(H0, Name, _),
  167	H =.. [Name,Value],
  168	params_options(T0, T).
  169params_options([_|T0], T) :-
  170	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.
  177add_show_beware(Options0, Options) :-
  178	implicit_no_show_beware(Options0), !,
  179	Options = [show_beware(false)|Options0].
  180add_show_beware(Options, Options).
  181
  182implicit_no_show_beware(Options) :-
  183	option(show_beware(_), Options), !,
  184	fail.
  185implicit_no_show_beware(Options) :-
  186	\+ option(format(swish), Options), !,
  187	fail.
  188implicit_no_show_beware(Options) :-
  189	option(code(_), Options).
  190implicit_no_show_beware(Options) :-
  191	option(q(_), Options).
  192implicit_no_show_beware(Options) :-
  193	option(examples(_), Options).
  194implicit_no_show_beware(Options) :-
  195	option(background(_), Options).
 source_option(+Request, +Options0, -Options)
If the data was requested as '/Alias/File', reply using file Alias(File).
  203source_option(_Request, Options0, Options) :-
  204	option(code(Code), Options0),
  205	option(format(swish), Options0), !,
  206	(   uri_is_global(Code)
  207	->  Options = [url(Code),st_type(external)|Options0]
  208	;   Options = Options0
  209	).
  210source_option(Request, Options0, Options) :-
  211	source_file(Request, File, Options0), !,
  212	option(path(Path), Request),
  213	(   source_data(File, String, Options1)
  214	->  append([ [code(String), url(Path), st_type(filesys)],
  215		     Options1,
  216		     Options0
  217		   ], Options)
  218	;   http_404([], Request)
  219	).
  220source_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.
  232source_file(Request, File, Options) :-
  233	option(path_info(PathInfo), Request), !,
  234	PathInfo \== 'index.html',
  235	(   path_info_file(PathInfo, File, Options)
  236	->  true
  237	;   http_404([], Request)
  238	).
  239
  240path_info_file(PathInfo, Path, Options) :-
  241	sub_atom(PathInfo, B, _, A, /),
  242	sub_atom(PathInfo, 0, B, _, Alias),
  243	sub_atom(PathInfo, _, A, 0, File),
  244	catch(swish_config:source_alias(Alias, AliasOptions), E,
  245	      (print_message(warning, E), fail)),
  246	Spec =.. [Alias,File],
  247	http_safe_file(Spec, []),
  248	absolute_file_name(Spec, Path,
  249			   [ access(read),
  250			     file_errors(fail)
  251			   ]),
  252	confirm_access(Path, AliasOptions), !,
  253	option(alias(Alias), Options, _).
  254
  255source_data(Path, Code, [title(Title), type(Ext), meta(Meta)]) :-
  256	setup_call_cleanup(
  257	    open(Path, read, In, [encoding(utf8)]),
  258	    read_string(In, _, Code),
  259	    close(In)),
  260	source_metadata(Path, Code, Meta),
  261	file_base_name(Path, File),
  262	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.
  277source_metadata(Path, Code, Meta) :-
  278	findall(Name-Value, source_metadata(Path, Code, Name, Value), Pairs),
  279	dict_pairs(Meta, meta, Pairs).
  280
  281source_metadata(Path, _Code, path, Path).
  282source_metadata(Path, _Code, last_modified, Modified) :-
  283	time_file(Path, Modified).
  284source_metadata(Path, _Code, loaded, true) :-
  285	source_file(Path).
  286source_metadata(Path, _Code, modified_since_loaded, true) :-
  287	source_file_property(Path, modified(ModifiedWhenLoaded)),
  288	time_file(Path, Modified),
  289	ModifiedWhenLoaded \== Modified.
  290source_metadata(Path, _Code, module, Module) :-
  291	file_name_extension(_, Ext, Path),
  292	user:prolog_file_type(Ext, prolog),
  293	xref_public_list(Path, _, [module(Module)]).
  294
  295confirm_access(Path, Options) :-
  296	option(if(Condition), Options), !,
  297	must_be(oneof([loaded]), Condition),
  298	eval_condition(Condition, Path).
  299confirm_access(_, _).
  300
  301eval_condition(loaded, Path) :-
  302	source_file(Path).
 serve_resource(+Request) is semidet
Serve /swish/Resource files.
  308serve_resource(Request) :-
  309	option(path_info(Info), Request),
  310	resource_prefix(Prefix),
  311	sub_atom(Info, 0, _, _, Prefix), !,
  312	http_reply_file(swish_web(Info), [], Request).
  313
  314resource_prefix('css/').
  315resource_prefix('help/').
  316resource_prefix('form/').
  317resource_prefix('icons/').
  318resource_prefix('js/').
  319resource_prefix('bower_components/').
 swish_page(+Options)//
Generate the entire SWISH default page.
  325swish_page(Options) -->
  326	swish_navbar(Options),
  327	swish_content(Options).
 swish_navbar(+Options)//
Generate the swish navigation bar.
  333swish_navbar(Options) -->
  334	swish_resources,
  335	html(nav([ class([navbar, 'navbar-default']),
  336		   role(navigation)
  337		 ],
  338		 [ div(class('navbar-header'),
  339		       [ \collapsed_button,
  340			 \swish_logos(Options)
  341		       ]),
  342		   div([ class([collapse, 'navbar-collapse']),
  343			 id(navbar)
  344		       ],
  345		       [ ul([class([nav, 'navbar-nav', menubar])], []),
  346			 ul([class([nav, 'navbar-nav', 'navbar-right'])],
  347			    [ li(\notifications(Options)),
  348			      li(\search_box(Options)),
  349			      \li_login_button(Options)
  350			    ])
  351		       ])
  352		 ])).
  353
  354li_login_button(Options) -->
  355	swish_config:li_login_button(Options).
  356li_login_button(_Options) -->
  357	[].
  358
  359collapsed_button -->
  360	html(button([type(button),
  361		     class('navbar-toggle'),
  362		     'data-toggle'(collapse),
  363		     'data-target'('#navbar')
  364		    ],
  365		    [ span(class('sr-only'), 'Toggle navigation'),
  366		      span(class('icon-bar'), []),
  367		      span(class('icon-bar'), []),
  368		      span(class('icon-bar'), [])
  369		    ])).
  370
  371swish_logos(Options) -->
  372	swish_config:logo(Options), !.
  373swish_logos(Options) -->
  374	pengine_logo(Options),
  375	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.
 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.
  390pengine_logo(_Options) -->
  391	{ http_absolute_location(root(.), HREF, [])
  392	},
  393	html(a([href(HREF), class('pengine-logo')], &(nbsp))).
  394swish_logo(_Options) -->
  395	{ http_absolute_location(swish(.), HREF, [])
  396	},
  397	html(a([href(HREF), class('swish-logo')], &(nbsp))).
 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
  410swish_content(Options) -->
  411	{ document_type(Type, Options)
  412	},
  413	swish_resources,
  414	swish_config_hash(Options),
  415	swish_options(Options),
  416	html(div([id(content), class([container, 'tile-top'])],
  417		 [ div([class([tile, horizontal]), 'data-split'('50%')],
  418		       [ div([ class([editors, tabbed])
  419			     ],
  420			     [ \source(Type, Options),
  421			       \notebooks(Type, Options)
  422			     ]),
  423			 div([class([tile, vertical]), 'data-split'('70%')],
  424			     [ div(class('prolog-runners'), []),
  425			       div(class('prolog-query'), \query(Options))
  426			     ])
  427		       ]),
  428		   \background(Options),
  429		   \examples(Options)
  430		 ])).
 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.
  439swish_config_hash(Options) -->
  440	{ swish_config_hash(Hash, Options) },
  441	js_script({|javascript(Hash)||
  442		   window.swish = window.swish||{};
  443		   window.swish.config_hash = Hash;
  444		   |}).
 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.
  453swish_options(Options) -->
  454	{ option(show_beware(Show), Options),
  455	  JSShow = @(Show)
  456	}, !,
  457	js_script({|javascript(JSShow)||
  458		   window.swish = window.swish||{};
  459		   window.swish.option = window.swish.options||{};
  460		   window.swish.option.show_beware = JSShow;
  461		   |}).
  462swish_options(_Options) -->
  463	[].
 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.
  482source(pl, Options) -->
  483	{ option(code(Spec), Options), !,
  484	  download_source(Spec, Source, Options),
  485	  phrase(source_data_attrs(Options), Extra)
  486	},
  487	html(div([ class(['prolog-editor']),
  488		   'data-label'('Program')
  489		 ],
  490		 [ textarea([ class([source,prolog]),
  491			      style('display:none')
  492			    | Extra
  493			    ],
  494			    Source)
  495		 ])).
  496source(_, _) --> [].
  497
  498source_data_attrs(Options) -->
  499	(source_file_data(Options) -> [] ; []),
  500	(source_url_data(Options) -> [] ; []),
  501	(source_title_data(Options) -> [] ; []),
  502	(source_meta_data(Options) -> [] ; []),
  503	(source_st_type_data(Options) -> [] ; []),
  504	(source_chat_data(Options) -> [] ; []).
  505
  506source_file_data(Options) -->
  507	{ option(file(File), Options) },
  508	['data-file'(File)].
  509source_url_data(Options) -->
  510	{ option(url(URL), Options) },
  511	['data-url'(URL)].
  512source_title_data(Options) -->
  513	{ option(title(File), Options) },
  514	['data-title'(File)].
  515source_st_type_data(Options) -->
  516	{ option(st_type(Type), Options) },
  517	['data-st_type'(Type)].
  518source_meta_data(Options) -->
  519	{ option(meta(Meta), Options), !,
  520	  atom_json_dict(Text, Meta, [])
  521	},
  522	['data-meta'(Text)].
  523source_chat_data(Options) -->
  524	{ option(chat_count(Count), Options),
  525	  atom_json_term(JSON, _{count:Count}, [as(string)])
  526	},
  527	['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.
  535background(Options) -->
  536	{ option(background(Spec), Options), !,
  537	  download_source(Spec, Source, Options)
  538	},
  539	html(textarea([ class([source,prolog,background]),
  540			style('display:none')
  541		      ],
  542		      Source)).
  543background(_) --> [].
  544
  545
  546examples(Options) -->
  547	{ option(examples(Examples), Options), !
  548	},
  549	html(textarea([ class([examples,prolog]),
  550			style('display:none')
  551		      ],
  552		      Examples)).
  553examples(_) --> [].
  554
  555
  556query(Options) -->
  557	{ option(q(Query), Options)
  558	}, !,
  559	html(textarea([ class([query,prolog]),
  560			style('display:none')
  561		      ],
  562		      Query)).
  563query(_) --> [].
 notebooks(+Type, +Options)//
We have opened a notebook. Embed the notebook data in the left-pane tab area.
  570notebooks(swinb, Options) -->
  571	{ option(code(Spec), Options),
  572	  download_source(Spec, NoteBookText, Options),
  573	  phrase(source_data_attrs(Options), Extra)
  574	},
  575	html(div([ class('notebook'),
  576		   'data-label'('Notebook')		% Use file?
  577		 ],
  578		 [ pre([ class('notebook-data'),
  579			 style('display:none')
  580		       | Extra
  581		       ],
  582		       NoteBookText)
  583		 ])).
  584notebooks(_, _) --> [].
 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.
  601download_source(HREF, Source, Options) :-
  602	uri_is_global(HREF), !,
  603	option(timeout(TMO), Options, 10),
  604	option(max_length(MaxLen), Options, 1_000_000),
  605	catch(call_with_time_limit(
  606		  TMO,
  607		  setup_call_cleanup(
  608		      http_open(HREF, In,
  609				[ cert_verify_hook(cert_accept_any)
  610				]),
  611		      read_source(In, MaxLen, Source, Options),
  612		      close(In))),
  613	      E, load_error(E, Source)).
  614download_source(Source0, Source, Options) :-
  615	option(max_length(MaxLen), Options, 1_000_000),
  616	string_length(Source0, Len),
  617	(   Len =< MaxLen
  618	->  Source = Source0
  619	;   format(string(Source),
  620		   '% ERROR: Content too long (max ~D)~n', [MaxLen])
  621	).
  622
  623read_source(In, MaxLen, Source, Options) :-
  624	option(encoding(Enc), Options, utf8),
  625	set_stream(In, encoding(Enc)),
  626	ReadMax is MaxLen + 1,
  627	read_string(In, ReadMax, Source0),
  628	string_length(Source0, Len),
  629	(   Len =< MaxLen
  630	->  Source = Source0
  631	;   format(string(Source),
  632		   ' % ERROR: Content too long (max ~D)~n', [MaxLen])
  633	).
  634
  635load_error(E, Source) :-
  636	message_to_string(E, String),
  637	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
  645document_type(Type, Options) :-
  646	(   option(type(Type0), Options)
  647	->  Type = Type0
  648	;   option(meta(Meta), Options),
  649	    file_name_extension(_, Type0, Meta.name),
  650	    Type0 \== ''
  651	->  Type = Type0
  652	;   option(st_type(external), Options),
  653	    option(url(URL), Options),
  654	    file_name_extension(_, Ext, URL),
  655	    ext_type(Ext, Type)
  656	->  true
  657	;   Type = pl
  658	).
  659
  660ext_type(swinb, swinb).
  661
  662
  663		 /*******************************
  664		 *	     RESOURCES		*
  665		 *******************************/
 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.
  673swish_resources -->
  674	swish_css,
  675	swish_js.
  676
  677swish_js  --> html_post(head, \include_swish_js).
  678swish_css --> html_post(head, \include_swish_css).
  679
  680include_swish_js -->
  681	{ swish_resource(js, JS),
  682	  swish_resource(rjs, RJS),
  683	  http_absolute_location(swish(js/JS), SwishJS, []),
  684	  http_absolute_location(swish(RJS),   SwishRJS, [])
  685	},
  686	rjs_timeout(JS),
  687	html(script([ src(SwishRJS),
  688		      'data-main'(SwishJS)
  689		    ], [])).
  690
  691rjs_timeout('swish-min') --> !,
  692	js_script({|javascript||
  693// Override RequireJS timeout, until main file is loaded.
  694window.require = { waitSeconds: 0 };
  695		  |}).
  696rjs_timeout(_) --> [].
  697
  698
  699include_swish_css -->
  700	{ swish_resource(css, CSS),
  701	  http_absolute_location(swish(css/CSS), SwishCSS, [])
  702	},
  703	html(link([ rel(stylesheet),
  704		    href(SwishCSS)
  705		  ])).
  706
  707swish_resource(Type, ID) :-
  708	alt(Type, ID, File),
  709	(   File == (-)
  710	;   absolute_file_name(File, _P, [file_errors(fail), access(read)])
  711	), !.
  712
  713alt(js,  'swish-min',     swish_web('js/swish-min.js')) :-
  714	\+ debugging(nominified).
  715alt(js,  'swish',         swish_web('js/swish.js')).
  716alt(css, 'swish-min.css', swish_web('css/swish-min.css')) :-
  717	\+ debugging(nominified).
  718alt(css, 'swish.css',     swish_web('css/swish.css')).
  719alt(rjs, 'js/require.js', swish_web('js/require.js')) :-
  720	\+ debugging(nominified).
  721alt(rjs, 'bower_components/requirejs/require.js', -).
  722
  723
  724		 /*******************************
  725		 *	       REST		*
  726		 *******************************/
 swish_rest_reply(+Method, +Request, +Options) is det
Handle non-GET requests. Such requests may be used to modify source code.
  733swish_rest_reply(put, Request, Options) :-
  734	merge_options(Options, [alias(_)], Options1),
  735	source_file(Request, File, Options1), !,
  736	option(content_type(String), Request),
  737	http_parse_header_value(content_type, String, Type),
  738	read_data(Type, Request, Data, Meta),
  739	authorized(file(update(File,Meta)), Options1),
  740	setup_call_cleanup(
  741	    open(File, write, Out),
  742	    format(Out, '~s', [Data]),
  743	    close(Out)),
  744	reply_json_dict(true).
  745
  746read_data(media(Type,_), Request, Data, Meta) :-
  747	http_json:json_type(Type), !,
  748	http_read_json_dict(Request, Dict),
  749	del_dict(data, Dict, Data, Meta).
  750read_data(media(text/_,_), Request, Data, _{}) :-
  751	http_read_data(Request, Data, [to(string)])