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) 2014-2015, 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(websocket, 36 [ http_open_websocket/3, % +URL, -WebSocket, +Options 37 http_upgrade_to_websocket/3, % :Goal, +Options, +Request 38 ws_send/2, % +WebSocket, +Message 39 ws_receive/2, % +WebSocket, -Message 40 ws_receive/3, % +WebSocket, -Message, +Options 41 ws_close/3, % +WebSocket, +Code, +Message 42 % Low level interface 43 ws_open/3, % +Stream, -WebSocket, +Options 44 ws_property/2 % +WebSocket, ?Property 45 ]). 46:- autoload(library(base64),[base64//1]). 47:- autoload(library(debug),[debug/3]). 48:- autoload(library(error), 49 [permission_error/3,must_be/2,type_error/2,domain_error/2]). 50:- autoload(library(lists),[member/2]). 51:- autoload(library(option),[select_option/3,option/2,option/3]). 52:- autoload(library(sha),[sha_hash/3]). 53:- autoload(library(http/http_dispatch),[http_switch_protocol/2]). 54:- autoload(library(http/http_open),[http_open/3]). 55:- autoload(library(http/json),[json_write_dict/2,json_read_dict/3]). 56 57:- meta_predicate 58 http_upgrade_to_websocket( , , ). 59 60:- predicate_options(http_open_websocket/3, 3, 61 [ subprotocols(list(atom)), 62 pass_to(http_open:http_open/3, 3) 63 ]). 64:- predicate_options(http_upgrade_to_websocket/3, 2, 65 [ guarded(boolean), 66 subprotocols(list(atom)) 67 ]). 68 69:- use_foreign_library(foreign(websocket)). 70 71/** <module> WebSocket support 72 73WebSocket is a lightweight message oriented protocol on top of TCP/IP 74streams. It is typically used as an _upgrade_ of an HTTP connection to 75provide bi-directional communication, but can also be used in isolation 76over arbitrary (Prolog) streams. 77 78The SWI-Prolog interface is based on _streams_ and provides ws_open/3 to 79create a _websocket stream_ from any Prolog stream. Typically, both an 80input and output stream are wrapped and then combined into a single 81object using stream_pair/3. 82 83The high-level interface provides http_upgrade_to_websocket/3 to realise 84a websocket inside the HTTP server infrastructure and 85http_open_websocket/3 as a layer over http_open/3 to realise a client 86connection. After establishing a connection, ws_send/2 and ws_receive/2 87can be used to send and receive messages. The predicate ws_close/3 is 88provided to perform the closing handshake and dispose of the stream 89objects. 90 91@see RFC 6455, http://tools.ietf.org/html/rfc6455 92@tbd Deal with protocol extensions. 93*/ 94 95 96 97 /******************************* 98 * HTTP SUPPORT * 99 *******************************/ 100 101%! http_open_websocket(+URL, -WebSocket, +Options) is det. 102% 103% Establish a client websocket connection. This predicate calls 104% http_open/3 with additional headers to negotiate a websocket 105% connection. In addition to the options processed by http_open/3, the 106% following options are recognised: 107% 108% - subprotocols(+List) 109% List of subprotocols that are acceptable. The selected 110% protocol is available as ws_property(WebSocket, 111% subprotocol(Protocol). 112% 113% Note that clients often provide an `Origin` header and some servers 114% require this field. See RFC 6455 for details. By default this 115% predicate does not set `Origin`. It may be set using the 116% `request_header` option of http_open/3, e.g. by passing this in the 117% Options list: 118% 119% request_header('Origin' = 'https://www.swi-prolog.org') 120% 121% The following example exchanges a message with the 122% html5rocks.websocket.org echo service: 123% 124% ``` 125% ?- URL = 'ws://html5rocks.websocket.org/echo', 126% http_open_websocket(URL, WS, []), 127% ws_send(WS, text('Hello World!')), 128% ws_receive(WS, Reply), 129% ws_close(WS, 1000, "Goodbye"). 130% URL = 'ws://html5rocks.websocket.org/echo', 131% WS = <stream>(0xe4a440,0xe4a610), 132% Reply = websocket{data:"Hello World!", opcode:text}. 133% ``` 134% 135% @arg WebSocket is a stream pair (see stream_pair/3) 136 137http_open_websocket(URL, WebSocket, Options) :- 138 phrase(base64(`___SWI-Prolog___`), Bytes), 139 string_codes(Key, Bytes), 140 add_subprotocols(Options, Options1), 141 http_open(URL, In, 142 [ status_code(Status), 143 output(Out), 144 header(sec_websocket_protocol, Selected), 145 header(sec_websocket_accept, AcceptedKey), 146 connection('Keep-alive, Upgrade'), 147 request_header('Upgrade' = websocket), 148 request_header('Sec-WebSocket-Key' = Key), 149 request_header('Sec-WebSocket-Version' = 13) 150 | Options1 151 ]), 152 ( Status == 101, 153 sec_websocket_accept(_{key:Key}, AcceptedKey) 154 -> ws_client_options(Selected, WsOptions), 155 stream_pair(In, Read, Write), % Old API: In and Out 156 stream_pair(Out, Read, Write), % New API: In == Out (= pair) 157 ws_open(Read, WsIn, WsOptions), 158 ws_open(Write, WsOut, WsOptions), 159 stream_pair(WebSocket, WsIn, WsOut) 160 ; close(Out), 161 close(In), 162 permission_error(open, websocket, URL) 163 ). 164 165ws_client_options('', [mode(client)]) :- !. 166ws_client_options(null, [mode(client)]) :- !. 167ws_client_options(Subprotocol, [mode(client), subprotocol(Subprotocol)]). 168 169add_subprotocols(OptionsIn, OptionsOut) :- 170 select_option(subprotocols(Subprotocols), OptionsIn, Options1), 171 !, 172 must_be(list(atom), Subprotocols), 173 atomic_list_concat(Subprotocols, ', ', Value), 174 OptionsOut = [ request_header('Sec-WebSocket-Protocol' = Value) 175 | Options1 176 ]. 177add_subprotocols(Options, Options). 178 179 180%! http_upgrade_to_websocket(:Goal, +Options, +Request) 181% 182% Create a websocket connection running call(Goal, WebSocket), 183% where WebSocket is a socket-pair. Options: 184% 185% * guarded(+Boolean) 186% If =true= (default), guard the execution of Goal and close 187% the websocket on both normal and abnormal termination of Goal. 188% If =false=, Goal itself is responsible for the created 189% websocket. This can be used to create a single thread that 190% manages multiple websockets using I/O multiplexing. 191% 192% * subprotocols(+List) 193% List of acceptable subprotocols. 194% 195% * timeout(+TimeOut) 196% Timeout to apply to the input stream. Default is =infinite=. 197% 198% Note that the Request argument is the last for cooperation with 199% http_handler/3. A simple _echo_ server that can be accessed at 200% =/ws/= can be implemented as: 201% 202% == 203% :- use_module(library(http/websocket)). 204% :- use_module(library(http/thread_httpd)). 205% :- use_module(library(http/http_dispatch)). 206% 207% :- http_handler(root(ws), 208% http_upgrade_to_websocket(echo, []), 209% [spawn([])]). 210% 211% echo(WebSocket) :- 212% ws_receive(WebSocket, Message), 213% ( Message.opcode == close 214% -> true 215% ; ws_send(WebSocket, Message), 216% echo(WebSocket) 217% ). 218% == 219% 220% @see http_switch_protocol/2. 221% @throws switching_protocols(Goal, Options). The recovery from 222% this exception causes the HTTP infrastructure to call 223% call(Goal, WebSocket). 224 225http_upgrade_to_websocket(Goal, Options, Request) :- 226 request_websocket_info(Request, Info), 227 debug(websocket(open), 'Websocket request: ~p', [Info]), 228 sec_websocket_accept(Info, AcceptKey), 229 choose_subprotocol(Info, Options, SubProtocol, ExtraHeaders), 230 debug(websocket(open), 'Subprotocol: ~p', [SubProtocol]), 231 http_switch_protocol( 232 open_websocket(Goal, SubProtocol, Options), 233 [ header([ upgrade(websocket), 234 connection('Upgrade'), 235 sec_websocket_accept(AcceptKey) 236 | ExtraHeaders 237 ]) 238 ]). 239 240choose_subprotocol(Info, Options, SubProtocol, ExtraHeaders) :- 241 HdrValue = Info.get(subprotocols), 242 option(subprotocols(ServerProtocols), Options), 243 split_string(HdrValue, ",", " ", RequestProtocols), 244 member(Protocol, RequestProtocols), 245 member(SubProtocol, ServerProtocols), 246 atom_string(SubProtocol, Protocol), 247 !, 248 ExtraHeaders = [ 'Sec-WebSocket-Protocol'(SubProtocol) ]. 249choose_subprotocol(_, _, null, []). 250 251open_websocket(Goal, SubProtocol, Options, HTTPIn, HTTPOut) :- 252 option(timeout(TimeOut), Options, infinite), 253 set_stream(HTTPIn, timeout(TimeOut)), 254 WsOptions = [mode(server), subprotocol(SubProtocol)], 255 ws_open(HTTPIn, WsIn, WsOptions), 256 ws_open(HTTPOut, WsOut, WsOptions), 257 stream_pair(WebSocket, WsIn, WsOut), 258 ( option(guarded(true), Options, true) 259 -> guard_websocket_server(Goal, WebSocket) 260 ; call(Goal, WebSocket) 261 ). 262 263guard_websocket_server(Goal, WebSocket) :- 264 ( catch(call(Goal, WebSocket), E, true) 265 -> ( var(E) 266 -> Msg = bye, Code = 1000 267 ; message_to_string(E, Msg), 268 Code = 1011 269 ) 270 ; Msg = "goal failed", Code = 1011 271 ), 272 catch(ws_close(WebSocket, Code, Msg), Error, 273 print_message(error, Error)). 274 275 276request_websocket_info(Request, Info) :- 277 option(upgrade(Websocket), Request), 278 downcase_atom(Websocket, websocket), 279 option(connection(Connection), Request), 280 connection_contains_upgrade(Connection), 281 option(sec_websocket_key(ClientKey), Request), 282 option(sec_websocket_version(Version), Request), 283 Info0 = _{key:ClientKey, version:Version}, 284 add_option(origin, Request, origin, Info0, Info1), 285 add_option(sec_websocket_protocol, Request, subprotocols, Info1, Info2), 286 add_option(sec_websocket_extensions, Request, extensions, Info2, Info). 287 288connection_contains_upgrade(Connection) :- 289 split_string(Connection, ",", " ", Tokens), 290 member(Token, Tokens), 291 string_lower(Token, "upgrade"), 292 !. 293 294add_option(OptionName, Request, Key, Dict0, Dict) :- 295 Option =.. [OptionName,Value], 296 option(Option, Request), 297 !, 298 Dict = Dict0.put(Key,Value). 299add_option(_, _, _, Dict, Dict). 300 301%! sec_websocket_accept(+Info, -AcceptKey) is det. 302% 303% Compute the accept key as per 4.2.2., point 5.4 304 305sec_websocket_accept(Info, AcceptKey) :- 306 string_concat(Info.key, "258EAFA5-E914-47DA-95CA-C5AB0DC85B11", Str), 307 sha_hash(Str, Hash, [ algorithm(sha1) ]), 308 phrase(base64(Hash), Encoded), 309 string_codes(AcceptKey, Encoded). 310 311 312 /******************************* 313 * HIGH LEVEL INTERFACE * 314 *******************************/ 315 316%! ws_send(+WebSocket, +Message) is det. 317% 318% Send a message over a websocket. The following terms are allowed 319% for Message: 320% 321% - text(+Text) 322% Send a text message. Text is serialized using write/1. 323% - binary(+Content) 324% As text(+Text), but all character codes produced by Content 325% must be in the range [0..255]. Typically, Content will be 326% an atom or string holding binary data. 327% - prolog(+Term) 328% Send a Prolog term as a text message. Text is serialized 329% using write_canonical/1. 330% - json(+JSON) 331% Send the Prolog representation of a JSON term using 332% json_write_dict/2. 333% - string(+Text) 334% Same as text(+Text), provided for consistency. 335% - close(+Code, +Text) 336% Send a close message. Code is 1000 for normal close. See 337% websocket documentation for other values. 338% - Dict 339% A dict that minimally contains an =opcode= key. Other keys 340% used are: 341% 342% - format:Format 343% Serialization format used for Message.data. Format is 344% one of =string=, =prolog= or =json=. See ws_receive/3. 345% 346% - data:Term 347% If this key is present, it is serialized according 348% to Message.format. Otherwise it is serialized using 349% write/1, which implies that string and atoms are just 350% sent verbatim. 351% 352% Note that ws_start_message/3 does not unlock the stream. This is 353% done by ws_send/1. This implies that multiple threads can use 354% ws_send/2 and the messages are properly serialized. 355% 356% @tbd Provide serialization details using options. 357 358ws_send(WsStream, Message) :- 359 message_opcode(Message, OpCode), 360 setup_call_cleanup( 361 ws_start_message(WsStream, OpCode, 0), 362 write_message_data(WsStream, Message), 363 ws_send(WsStream)). 364 365message_opcode(Message, OpCode) :- 366 is_dict(Message), 367 !, 368 to_opcode(Message.opcode, OpCode). 369message_opcode(Message, OpCode) :- 370 functor(Message, Name, _), 371 ( text_functor(Name) 372 -> to_opcode(text, OpCode) 373 ; to_opcode(Name, OpCode) 374 ). 375 376text_functor(json). 377text_functor(string). 378text_functor(prolog). 379 380write_message_data(Stream, Message) :- 381 is_dict(Message), 382 !, 383 ( _{code:Code, data:Data} :< Message 384 -> write_message_data(Stream, close(Code, Data)) 385 ; _{format:prolog, data:Data} :< Message 386 -> format(Stream, '~k .~n', [Data]) 387 ; _{format:json, data:Data} :< Message 388 -> json_write_dict(Stream, Data) 389 ; _{data:Data} :< Message 390 -> format(Stream, '~w', Data) 391 ; true 392 ). 393write_message_data(Stream, Message) :- 394 functor(Message, Format, 1), 395 !, 396 arg(1, Message, Data), 397 ( text_functor(Format) 398 -> write_text_message(Format, Stream, Data) 399 ; format(Stream, '~w', [Data]) 400 ). 401write_message_data(_, Message) :- 402 atom(Message), 403 !. 404write_message_data(Stream, close(Code, Data)) :- 405 !, 406 High is (Code >> 8) /\ 0xff, 407 Low is Code /\ 0xff, 408 put_byte(Stream, High), 409 put_byte(Stream, Low), 410 stream_pair(Stream, _, Out), 411 set_stream(Out, encoding(utf8)), 412 format(Stream, '~w', [Data]). 413write_message_data(_, Message) :- 414 type_error(websocket_message, Message). 415 416write_text_message(json, Stream, Data) :- 417 !, 418 json_write_dict(Stream, Data). 419write_text_message(prolog, Stream, Data) :- 420 !, 421 format(Stream, '~k .', [Data]). 422write_text_message(_, Stream, Data) :- 423 format(Stream, '~w', [Data]). 424 425 426 427%! ws_receive(+WebSocket, -Message:dict) is det. 428%! ws_receive(+WebSocket, -Message:dict, +Options) is det. 429% 430% Receive the next message from WebSocket. Message is a dict 431% containing the following keys: 432% 433% - opcode:OpCode 434% OpCode of the message. This is an atom for known opcodes 435% and an integer for unknown ones. If the peer closed the 436% stream, OpCode is bound to =close= and data to the atom 437% =end_of_file=. 438% - data:String 439% The data, represented as a string. This field is always 440% present. String is the empty string if there is no data 441% in the message. 442% - rsv:RSV 443% Present if the WebSocket RSV header is not 0. RSV is an 444% integer in the range [1..7]. 445% 446% If =ping= message is received and WebSocket is a stream pair, 447% ws_receive/1 replies with a =pong= and waits for the next 448% message. 449% 450% The predicate ws_receive/3 processes the following options: 451% 452% - format(+Format) 453% Defines how _text_ messages are parsed. Format is one of 454% - string 455% Data is returned as a Prolog string (default) 456% - json 457% Data is parsed using json_read_dict/3, which also receives 458% Options. 459% - prolog 460% Data is parsed using read_term/3, which also receives 461% Options. 462% 463% @tbd Add a hook to allow for more data formats? 464 465ws_receive(WsStream, Message) :- 466 ws_receive(WsStream, Message, []). 467 468ws_receive(WsStream, Message, Options) :- 469 ws_read_header(WsStream, Code, RSV), 470 debug(websocket, 'ws_receive(~p): OpCode=~w, RSV=~w', 471 [WsStream, Code, RSV]), 472 ( Code == end_of_file 473 -> Message = websocket{opcode:close, data:end_of_file} 474 ; ( ws_opcode(OpCode, Code) 475 -> true 476 ; OpCode = Code 477 ), 478 read_data(OpCode, WsStream, Data, Options), 479 ( OpCode == ping, 480 reply_pong(WsStream, Data.data) 481 -> ws_receive(WsStream, Message, Options) 482 ; ( RSV == 0 483 -> Message = Data 484 ; Message = Data.put(rsv, RSV) 485 ) 486 ) 487 ), 488 debug(websocket, 'ws_receive(~p) --> ~p', [WsStream, Message]). 489 490read_data(close, WsStream, 491 websocket{opcode:close, code:Code, format:string, data:Data}, _Options) :- 492 !, 493 get_byte(WsStream, High), 494 ( High == -1 495 -> Code = 1000, 496 Data = "" 497 ; get_byte(WsStream, Low), 498 Code is High<<8 \/ Low, 499 stream_pair(WsStream, In, _), 500 set_stream(In, encoding(utf8)), 501 read_string(WsStream, _Len, Data) 502 ). 503read_data(text, WsStream, Data, Options) :- 504 !, 505 option(format(Format), Options, string), 506 read_text_data(Format, WsStream, Data, Options). 507read_data(OpCode, WsStream, websocket{opcode:OpCode, format:string, data:Data}, _Options) :- 508 read_string(WsStream, _Len, Data). 509 510%! read_text_data(+Format, +WsStream, -Dict, +Options) is det. 511% 512% Read a websocket message into a dict websocket{opcode:OpCode, 513% data:Data}, where Data is parsed according to Format. 514 515read_text_data(string, WsStream, 516 websocket{opcode:text, format:string, data:Data}, _Options) :- 517 !, 518 read_string(WsStream, _Len, Data). 519read_text_data(json, WsStream, 520 websocket{opcode:text, format:json, data:Data}, Options) :- 521 !, 522 json_read_dict(WsStream, Data, Options). 523read_text_data(prolog, WsStream, 524 websocket{opcode:text, format:prolog, data:Data}, Options) :- 525 !, 526 read_term(WsStream, Data, Options). 527read_text_data(Format, _, _, _) :- 528 domain_error(format, Format). 529 530reply_pong(WebSocket, Data) :- 531 stream_pair(WebSocket, _In, Out), 532 is_stream(Out), 533 ws_send(Out, pong(Data)). 534 535 536%! ws_close(+WebSocket:stream_pair, +Code, +Data) is det. 537% 538% Close a WebSocket connection by sending a =close= message if 539% this was not already sent and wait for the close reply. 540% 541% @arg Code is the numerical code indicating the close status. 542% This is 16-bit integer. The codes are defined in 543% section _|7.4.1. Defined Status Codes|_ of RFC6455. 544% Notably, 1000 indicates a normal closure. 545% @arg Data is currently interpreted as text. 546% @error websocket_error(unexpected_message, Reply) if 547% the other side did not send a close message in reply. 548 549ws_close(WebSocket, Code, Data) :- 550 setup_call_cleanup( 551 true, 552 ws_close_(WebSocket, Code, Data), 553 close(WebSocket)). 554 555ws_close_(WebSocket, Code, Data) :- 556 stream_pair(WebSocket, In, Out), 557 ( ( var(Out) 558 ; ws_property(Out, status, closed) 559 ) 560 -> debug(websocket(close), 561 'Output stream of ~p already closed', [WebSocket]) 562 ; ws_send(WebSocket, close(Code, Data)), 563 close(Out), 564 debug(websocket(close), '~p: closed output', [WebSocket]), 565 ( ( var(In) 566 ; ws_property(In, status, closed) 567 ) 568 -> debug(websocket(close), 569 'Input stream of ~p already closed', [WebSocket]) 570 ; ws_receive(WebSocket, Reply), 571 ( Reply.opcode == close 572 -> debug(websocket(close), '~p: close confirmed', [WebSocket]) 573 ; throw(error(websocket_error(unexpected_message, Reply), _)) 574 ) 575 ) 576 ). 577 578 579%! ws_open(+Stream, -WSStream, +Options) is det. 580% 581% Turn a raw TCP/IP (or any other binary stream) into a websocket 582% stream. Stream can be an input stream, output stream or a stream 583% pair. Options includes 584% 585% * mode(+Mode) 586% One of =server= or =client=. If =client=, messages are sent 587% as _masked_. 588% 589% * buffer_size(+Count) 590% Send partial messages for each Count bytes or when flushing 591% the output. The default is to buffer the entire message before 592% it is sent. 593% 594% * close_parent(+Boolean) 595% If =true= (default), closing WSStream also closes Stream. 596% 597% * subprotocol(+Protocol) 598% Set the subprotocol property of WsStream. This value can be 599% retrieved using ws_property/2. Protocol is an atom. See 600% also the =subprotocols= option of http_open_websocket/3 and 601% http_upgrade_to_websocket/3. 602% 603% A typical sequence to turn a pair of streams into a WebSocket is 604% here: 605% 606% == 607% ..., 608% Options = [mode(server), subprotocol(chat)], 609% ws_open(Input, WsInput, Options), 610% ws_open(Output, WsOutput, Options), 611% stream_pair(WebSocket, WsInput, WsOutput). 612% == 613 614%! ws_start_message(+WSStream, +OpCode) is det. 615%! ws_start_message(+WSStream, +OpCode, +RSV) is det. 616% 617% Prepare for sending a new message. OpCode is one of =text=, 618% =binary=, =close=, =ping= or =pong=. RSV is reserved for 619% extensions. After this call, the application usually writes data 620% to WSStream and uses ws_send/1 to complete the message. 621% Depending on OpCode, the stream is switched to _binary_ (for 622% OpCode is =binary=) or _text_ using =utf8= encoding (all other 623% OpCode values). For example, to a JSON message can be send 624% using: 625% 626% == 627% ws_send_json(WSStream, JSON) :- 628% ws_start_message(WSStream, text), 629% json_write(WSStream, JSON), 630% ws_send(WSStream). 631% == 632 633%! ws_send(+WSStream) is det. 634% 635% Complete and send the WebSocket message. If the OpCode of the 636% message is =close=, close the stream. 637 638%! ws_read_header(+WSStream, -OpCode, -RSV) is det. 639% 640% Read the header of the WebSocket next message. After this call, 641% WSStream is switched to the appropriate encoding and reading 642% from the stream will signal end-of-file at the end of the 643% message. Note that this end-of-file does *not* invalidate 644% WSStream. Reading may perform various tasks on the background: 645% 646% - If the message has _Fin_ is =false=, it will wait for an 647% additional message. 648% - If a =ping= is received, it will reply with a =pong= on the 649% matching output stream. 650% - If a =pong= is received, it will be ignored. 651% - If a =close= is received and a partial message is read, 652% it generates an exception (TBD: which?). If no partial 653% message is received, it unified OpCode with =close= and 654% replies with a =close= message. 655% 656% If not all data has been read for the previous message, it will 657% first read the remainder of the message. This input is silently 658% discarded. This allows for trailing white space after proper 659% text messages such as JSON, Prolog or XML terms. For example, to 660% read a JSON message, use: 661% 662% == 663% ws_read_json(WSStream, JSON) :- 664% ws_read_header(WSStream, OpCode, RSV), 665% ( OpCode == text, 666% RSV == 0 667% -> json_read(WSStream, JSON) 668% ; OpCode == close 669% -> JSON = end_of_file 670% ). 671% == 672 673%! ws_property(+WebSocket, ?Property) is nondet. 674% 675% True if Property is a property WebSocket. Defined properties 676% are: 677% 678% * subprotocol(Protocol) 679% Protocol is the negotiated subprotocol. This is typically set 680% as a property of the websocket by ws_open/3. 681 682ws_property(WebSocket, Property) :- 683 ws_property_(Property, WebSocket). 684 685ws_property_(subprotocol(Protocol), WebSocket) :- 686 ws_property(WebSocket, subprotocol, Protocol). 687 688%! to_opcode(+Spec, -OpCode:int) is det. 689% 690% Convert a specification of an opcode into the numeric opcode. 691 692to_opcode(In, Code) :- 693 integer(In), 694 !, 695 must_be(between(0, 15), In), 696 Code = In. 697to_opcode(Name, Code) :- 698 must_be(atom, Name), 699 ( ws_opcode(Name, Code) 700 -> true 701 ; domain_error(ws_opcode, Name) 702 ). 703 704%! ws_opcode(?Name, ?Code) 705% 706% Define symbolic names for the WebSocket opcodes. 707 708ws_opcode(continuation, 0). 709ws_opcode(text, 1). 710ws_opcode(binary, 2). 711ws_opcode(close, 8). 712ws_opcode(ping, 9). 713ws_opcode(pong, 10). 714 715 716%! ws_mask(-Mask) 717% 718% Produce a good random number of the mask of a client message. 719 720:- public ws_mask/1. 721 722ws_mask(Mask) :- 723 Mask is 1+random(1<<32-1)