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