1/* Part of SWI-Prolog 2 3 Author: Jan Wielemaker 4 E-mail: J.Wielemaker@vu.nl 5 WWW: http://www.swi-prolog.org 6 Copyright (c) 2002-2023, University of Amsterdam, 7 VU University Amsterdam 8 SWI-Prolog Solutions b.v. 9 All rights reserved. 10 11 Redistribution and use in source and binary forms, with or without 12 modification, are permitted provided that the following conditions 13 are met: 14 15 1. Redistributions of source code must retain the above copyright 16 notice, this list of conditions and the following disclaimer. 17 18 2. Redistributions in binary form must reproduce the above copyright 19 notice, this list of conditions and the following disclaimer in 20 the documentation and/or other materials provided with the 21 distribution. 22 23 THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS 24 "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT 25 LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS 26 FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE 27 COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, 28 INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, 29 BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; 30 LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER 31 CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT 32 LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN 33 ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE 34 POSSIBILITY OF SUCH DAMAGE. 35*/ 36 37:- module(http_client, 38 [ http_get/3, % +URL, -Reply, +Options 39 http_delete/3, % +URL, -Reply, +Options 40 http_post/4, % +URL, +In, -Reply, +Options 41 http_put/4, % +URL, +In, -Reply, +Options 42 http_patch/4, % +URL, +In, -Reply, +Options 43 http_read_data/3, % +Header, -Data, :Options 44 http_disconnect/1 % +What 45 ]). 46:- autoload(http_header,[http_post_data/3]). 47:- autoload(http_stream,[http_chunked_open/3,stream_range_open/3]). 48:- autoload(library(error),[must_be/2]). 49:- autoload(library(lists),[delete/3,select/3]). 50:- autoload(library(memfile), 51 [ new_memory_file/1, open_memory_file/4, free_memory_file/1, 52 memory_file_to_atom/3, memory_file_to_string/3, 53 memory_file_to_codes/3, open_memory_file/3 54 ]). 55:- autoload(library(option), 56 [option/3,option/2,meta_options/3,select_option/3]). 57:- autoload(library(uri),[uri_query_components/2]). 58:- autoload(library(http/http_open), 59 [http_open/3,http_close_keep_alive/1]). 60 61:- meta_predicate 62 http_read_data( , , ). 63 64:- multifile 65 http_convert_data/4, % http_read_data plugin-hook 66 http:post_data_hook/3. 67 68:- predicate_options(http_get/3, 3, 69 [ pass_to(http_open/3, 3), 70 pass_to(http_read_data/3, 3) 71 ]). 72:- predicate_options(http_delete/3, 3, [pass_to(http_get/3, 3)]). 73:- predicate_options(http_post/4, 4, [pass_to(http_get/3, 3)]). 74:- predicate_options(http_put/4, 4, [pass_to(http_post/4, 4)]). 75:- predicate_options(http_read_data/3, 3, 76 [ to(any), 77 content_type(any), 78 form_data(oneof([form,mime])), 79 input_encoding(encoding), % multipart messages 80 on_filename(callable), 81 module(atom), % x-prolog data 82 variable_names(-list) 83 ]). 84 85 86/** <module> HTTP client library 87 88This library provides the four basic HTTP client actions: =GET=, 89=DELETE=, =POST= and =PUT=. In addition, it provides http_read_data/3, 90which is used by library(http/http_parameters) to decode =POST= data in 91server applications. 92 93This library is based on http_open/3, which opens a URL as a Prolog 94stream. The reply is processed by http_read_data/3. The following 95content-types are supported. Options passed to http_get/3 and friends 96are passed to http_read_data/3, which in turn passes them to the 97conversion predicates. Support for additional content types can be added 98by extending the multifile predicate http_client:http_convert_data/4. 99 100 - 'application/x-www-form-urlencoded' 101 Built in. Converts form-data into a list of `Name=Value` terms. 102 - 'application/x-prolog' 103 Built in. Reads a single Prolog term. 104 - 'multipart/form-data' 105 Processed if library(http/http_multipart_plugin) is loaded. This 106 format should be used to handle web forms that upload a file. 107 - 'text/html' | 'text/xml' 108 Processed if library(http/http_sgml_plugin) is loaded. See load_html/3 109 for details and load_xml/3 for details. The output is often processed 110 using xpath/3. 111 - 'application/json' | 'application/jsonrequest' 112 Processed if library(http/http_json) is loaded. The option 113 json_object(As) can be used to return a term json(Attributes) 114 (`As` is `term`) or a dict (`As` is `dict`). 115*/ 116 117 /******************************* 118 * GET * 119 *******************************/ 120 121%! http_get(+URL, -Data, +Options) is det. 122% 123% Get data from a URL server and convert it to a suitable Prolog 124% representation based on the =|Content-Type|= header and plugins. 125% This predicate is the common implementation of the HTTP client 126% operations. The predicates http_delete/3, http_post/4 and 127% http_put/4 call this predicate with an appropriate 128% method(+Method) option and ---for http_post/4 and http_put/4--- 129% a post(+Data) option. 130% 131% Options are passed to http_open/3 and http_read_data/3. Other 132% options: 133% 134% - reply_header(-Fields) 135% Synonym for headers(Fields) from http_open/3. Provided for 136% backward compatibility. Note that http_version(Major-Minor) 137% is missing in the new version. 138 139http_get(URL, Data, Options) :- 140 headers_option(Options, Options1, Headers), 141 option(reply_header(Headers), Options, _), 142 http_open(URL, In, Options1), 143 delete(Headers, transfer_encoding(_), Headers1), 144 call_cleanup( 145 http_read_data(In, Headers1, Data, Options), 146 close(In)). 147 148headers_option(Options, Options1, Headers) :- 149 option(headers(Headers), Options), 150 !, 151 Options1 = Options. 152headers_option(Options, [headers(Headers)|Options], Headers). 153 154 155%! http_delete(+URL, -Data, +Options) is det. 156% 157% Execute a =DELETE= method on the server. Arguments are the same 158% as for http_get/3. Typically one should pass the option 159% status_code(-Code) to assess and evaluate the returned status 160% code. Without, codes other than 200 are interpreted as an error. 161% 162% @tbd Properly map the 201, 202 and 204 replies. 163% @see Implemented on top of http_get/3. 164 165http_delete(URL, Data, Options) :- 166 http_get(URL, Data, [method(delete)|Options]). 167 168 169%! http_post(+URL, +Data, -Reply, +Options) is det. 170% 171% Issue an HTTP =POST= request. Data is posted using 172% http_post_data/3. The HTTP server reply is returned in Reply, 173% using the same rules as for http_get/3. 174% 175% @see Implemented on top of http_get/3. 176 177http_post(URL, Data, Reply, Options) :- 178 http_get(URL, Reply, 179 [ post(Data) 180 | Options 181 ]). 182 183%! http_put(+URL, +Data, -Reply, +Options) 184% 185% Issue an HTTP =PUT= request. Arguments are the same as for 186% http_post/4. 187% 188% @see Implemented on top of http_post/4. 189 190http_put(URL, In, Out, Options) :- 191 http_post(URL, In, Out, [method(put)|Options]). 192 193%! http_patch(+URL, +Data, -Reply, +Options) 194% 195% Issue an HTTP =PATCH= request. Arguments are the same as for 196% http_post/4. 197% 198% @see Implemented on top of http_post/4. 199 200http_patch(URL, In, Out, Options) :- 201 http_post(URL, In, Out, [method(patch)|Options]). 202 203%! http_read_data(+Request, -Data, +Options) is det. 204% 205% Read data from an HTTP connection and convert it according to 206% the supplied to(Format) option or based on the =|Content-type|= 207% in the Request. The following options are supported: 208% 209% * to(Format) 210% Convert data into Format. Values are: 211% - stream(+WriteStream)) 212% Append the content of the message to Stream 213% - atom 214% Return the reply as an atom 215% - string 216% Return the reply as a string 217% - codes 218% Return the reply as a list of codes 219% * form_data(AsForm) 220% * input_encoding(+Encoding) 221% * on_filename(:CallBack) 222% These options are implemented by the plugin 223% library(http/http_multipart_plugin) and apply to processing 224% =|multipart/form-data|= content. 225% * content_type(+Type) 226% Overrule the content-type that is part of Request as a 227% work-around for wrongly configured servers. 228% 229% Without plugins, this predicate handles 230% 231% * 'application/x-www-form-urlencoded' 232% Converts form-data into a list of `Name=Value` terms. 233% * 'application/x-prolog' 234% Converts data into a Prolog term. 235% 236% @param Request is a parsed HTTP request as returned by 237% http_read_request/2 or available from the HTTP server's request 238% dispatcher. Request must contain a term input(In) that provides 239% the input stream from the HTTP server. 240 241http_read_data(Fields, Data, QOptions) :- 242 meta_options(is_meta, QOptions, Options), 243 memberchk(input(In), Fields), 244 ( http_read_data(In, Fields, Data, Options) 245 -> true 246 ; throw(error(failed(http_read_data), _)) 247 ). 248 249is_meta(on_filename). 250 251http_read_data(_In, Fields, Data, _Options) :- 252 option(status_code(Code), Fields), 253 no_content_status(Code), 254 \+ ( option(content_length(Len), Fields), 255 Len > 0 256 ), 257 !, 258 Data = ''. 259http_read_data(In, Fields, Data, Options) :- % Transfer-encoding: chunked 260 select(transfer_encoding(chunked), Fields, RestFields), 261 !, 262 setup_call_cleanup( 263 http_chunked_open(In, DataStream, []), 264 http_read_data(DataStream, RestFields, Data, Options), 265 close(DataStream)). 266http_read_data(In, Fields, Data, Options) :- 267 option(to(X), Options), 268 !, 269 ( X = stream(Stream) 270 -> ( memberchk(content_length(Bytes), Fields) 271 -> copy_stream_data(In, Stream, Bytes) 272 ; copy_stream_data(In, Stream) 273 ) 274 ; must_be(oneof([atom,string,codes]), X), 275 setup_call_cleanup( 276 new_memory_file(MemFile), 277 ( setup_call_cleanup( 278 open_memory_file(MemFile, write, Stream, 279 [encoding(octet)]), 280 ( memberchk(content_length(Bytes), Fields) 281 -> copy_stream_data(In, Stream, Bytes) 282 ; copy_stream_data(In, Stream) 283 ), 284 close(Stream)), 285 encoding(Fields, Encoding, Options), 286 memory_file_to(X, MemFile, Encoding, Data0) 287 ), 288 free_memory_file(MemFile)), 289 Data = Data0 290 ). 291http_read_data(In, Fields, Data, _) :- 292 option(content_type(ContentType), Fields), 293 is_content_type(ContentType, 'application/x-www-form-urlencoded'), 294 !, 295 http_read_data(In, Fields, Codes, [to(string)]), 296 uri_query_components(Codes, Data). 297http_read_data(In, Fields, Data, Options) :- % call hook 298 ( select_option(content_type(Type), Options, Options1) 299 -> delete(Fields, content_type(_), Fields1), 300 http_convert_data(In, [content_type(Type)|Fields1], Data, Options1) 301 ; http_convert_data(In, Fields, Data, Options) 302 ), 303 !. 304http_read_data(In, Fields, Data, Options) :- 305 http_read_data(In, Fields, Data, [to(atom)|Options]). 306 307memory_file_to(atom, MemFile, Encoding, Data) :- 308 memory_file_to_atom(MemFile, Data, Encoding). 309memory_file_to(string, MemFile, Encoding, Data) :- 310 memory_file_to_string(MemFile, Data, Encoding). 311memory_file_to(codes, MemFile, Encoding, Data) :- 312 memory_file_to_codes(MemFile, Data, Encoding). 313 314 315encoding(_Fields, Encoding, Options) :- 316 option(input_encoding(Encoding), Options), 317 !. 318encoding(Fields, utf8, _) :- 319 memberchk(content_type(Type), Fields), 320 ( sub_atom(Type, _, _, _, 'UTF-8') 321 -> true 322 ; sub_atom(Type, _, _, _, 'utf-8') 323 ), 324 !. 325encoding(_, octet, _). 326 327is_content_type(ContentType, Check) :- 328 sub_atom(ContentType, 0, Len, After, Check), 329 ( After == 0 330 -> true 331 ; sub_atom(ContentType, Len, 1, _, ';') 332 ). 333 334%! no_content_status(+Code) is semidet. 335% 336% True when Code is an HTTP status code that carries no content. 337% 338% @see Issue#157 339 340no_content_status(Code) :- 341 between(100, 199, Code), 342 !. 343no_content_status(204). 344 345%! http_convert_data(+In, +Fields, -Data, +Options) is semidet. 346% 347% Multi-file hook to convert a HTTP payload according to the 348% _Content-Type_ header. The default implementation deals with 349% application/x-prolog. The HTTP framework provides 350% implementations for JSON (library(http/http_json)), HTML/XML 351% (library(http/http_sgml_plugin)) 352 353http_convert_data(In, Fields, Data, Options) :- 354 memberchk(content_type(Type), Fields), 355 is_content_type(Type, 'application/x-prolog'), 356 !, 357 ( memberchk(content_length(Bytes), Fields) 358 -> setup_call_cleanup( 359 ( stream_range_open(In, Range, [size(Bytes)]), 360 set_stream(Range, encoding(utf8)), 361 set_stream(Range, file_name('HTTP:DATA')) 362 ), 363 read_term(Range, Data, Options), 364 close(Range)) 365 ; set_stream(In, encoding(utf8)), 366 read_term(In, Data, Options) 367 ). 368 369%! http_disconnect(+Connections) is det. 370% 371% Close down some connections. Currently Connections must have the 372% value =all=, closing all connections. 373% 374% @deprecated New code should use http_close_keep_alive/1 from 375% library(http/http_open). 376 377http_disconnect(all) :- 378 http_close_keep_alive(_). 379 380%! http:post_data_hook(+Term, +Out, +Options) is semidet. 381% 382% Hook to extend the datatypes supported by the post(Data) option 383% of http_open/3. The default implementation supports 384% prolog(Term), sending a Prolog term as =|application/x-prolog|=. 385 386httppost_data_hook(prolog(Term), Out, HdrExtra) :- 387 setup_call_cleanup( 388 ( new_memory_file(MemFile), 389 open_memory_file(MemFile, write, Handle) 390 ), 391 ( format(Handle, 392 'Content-Type: application/x-prolog; charset=UTF-8~n~n', 393 []), 394 write_term(Handle, Term, 395 [ quoted(true), 396 ignore_ops(true), 397 fullstop(true), 398 nl(true) 399 ]) 400 ), 401 close(Handle)), 402 setup_call_cleanup( 403 open_memory_file(MemFile, read, RdHandle, 404 [ free_on_close(true) 405 ]), 406 http_post_data(cgi_stream(RdHandle), Out, HdrExtra), 407 close(RdHandle))