View source with raw comments or as raw
    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:- use_module(library(debug),[debug/3]).   47:- use_module(library(http/http_dispatch),[http_switch_protocol/2]).   48
   49:- autoload(library(base64),[base64//1]).   50:- autoload(library(error),
   51	    [permission_error/3,must_be/2,type_error/2,domain_error/2]).   52:- autoload(library(lists),[member/2]).   53:- autoload(library(option),[select_option/3,option/2,option/3]).   54:- autoload(library(sha),[sha_hash/3]).   55:- autoload(library(http/http_open),[http_open/3]).   56:- autoload(library(http/json),[json_write_dict/2,json_read_dict/3]).   57
   58:- meta_predicate
   59    http_upgrade_to_websocket(1, +, +).   60
   61:- predicate_options(http_open_websocket/3, 3,
   62                     [ subprotocols(list(atom)),
   63                       pass_to(http_open:http_open/3, 3)
   64                     ]).   65:- predicate_options(http_upgrade_to_websocket/3, 2,
   66                     [ guarded(boolean),
   67                       subprotocols(list(atom))
   68                     ]).   69
   70:- use_foreign_library(foreign(websocket)).

WebSocket support

WebSocket is a lightweight message oriented protocol on top of TCP/IP streams. It is typically used as an upgrade of an HTTP connection to provide bi-directional communication, but can also be used in isolation over arbitrary (Prolog) streams.

The SWI-Prolog interface is based on streams and provides ws_open/3 to create a websocket stream from any Prolog stream. Typically, both an input and output stream are wrapped and then combined into a single object using stream_pair/3.

The high-level interface provides http_upgrade_to_websocket/3 to realise a websocket inside the HTTP server infrastructure and http_open_websocket/3 as a layer over http_open/3 to realise a client connection. After establishing a connection, ws_send/2 and ws_receive/2 can be used to send and receive messages. The predicate ws_close/3 is provided to perform the closing handshake and dispose of the stream objects.

See also
- RFC 6455, http://tools.ietf.org/html/rfc6455
To be done
- Deal with protocol extensions. */
   98                 /*******************************
   99                 *         HTTP SUPPORT         *
  100                 *******************************/
 http_open_websocket(+URL, -WebSocket, +Options) is det
Establish a client websocket connection. This predicate calls http_open/3 with additional headers to negotiate a websocket connection. In addition to the options processed by http_open/3, the following options are recognised:
subprotocols(+List)
List of subprotocols that are acceptable. The selected protocol is available as ws_property(WebSocket, subprotocol(Protocol).

Note that clients often provide an Origin header and some servers require this field. See RFC 6455 for details. By default this predicate does not set Origin. It may be set using the request_header option of http_open/3, e.g. by passing this in the Options list:

request_header('Origin' = 'https://www.swi-prolog.org')

The following example exchanges a message with the html5rocks.websocket.org echo service:

?- URL = 'ws://html5rocks.websocket.org/echo',
   http_open_websocket(URL, WS, []),
   ws_send(WS, text('Hello World!')),
   ws_receive(WS, Reply),
   ws_close(WS, 1000, "Goodbye").
URL = 'ws://html5rocks.websocket.org/echo',
WS = <stream>(0xe4a440,0xe4a610),
Reply = websocket{data:"Hello World!", opcode:text}.
Arguments:
WebSocket- is a stream pair (see stream_pair/3)
  138http_open_websocket(URL, WebSocket, Options) :-
  139    phrase(base64(`___SWI-Prolog___`), Bytes),
  140    string_codes(Key, Bytes),
  141    add_subprotocols(Options, Options1),
  142    http_open(URL, In,
  143              [ status_code(Status),
  144                output(Out),
  145                header(sec_websocket_protocol, Selected),
  146                header(sec_websocket_accept, AcceptedKey),
  147                connection('Keep-alive, Upgrade'),
  148                request_header('Upgrade' = websocket),
  149                request_header('Sec-WebSocket-Key' = Key),
  150                request_header('Sec-WebSocket-Version' = 13)
  151              | Options1
  152              ]),
  153    (   Status == 101,
  154        sec_websocket_accept(_{key:Key}, AcceptedKey)
  155    ->  ws_client_options(Selected, WsOptions),
  156        stream_pair(In,  Read, Write),      % Old API: In and Out
  157        stream_pair(Out, Read, Write),      % New API: In == Out (= pair)
  158        ws_open(Read,  WsIn,  WsOptions),
  159        ws_open(Write, WsOut, WsOptions),
  160        stream_pair(WebSocket, WsIn, WsOut)
  161    ;   close(Out),
  162        close(In),
  163        permission_error(open, websocket, URL)
  164    ).
  165
  166ws_client_options('',          [mode(client)]) :- !.
  167ws_client_options(null,        [mode(client)]) :- !.
  168ws_client_options(Subprotocol, [mode(client), subprotocol(Subprotocol)]).
  169
  170add_subprotocols(OptionsIn, OptionsOut) :-
  171    select_option(subprotocols(Subprotocols), OptionsIn, Options1),
  172    !,
  173    must_be(list(atom), Subprotocols),
  174    atomic_list_concat(Subprotocols, ', ', Value),
  175    OptionsOut = [ request_header('Sec-WebSocket-Protocol' = Value)
  176                 | Options1
  177                 ].
  178add_subprotocols(Options, Options).
 http_upgrade_to_websocket(:Goal, +Options, +Request)
Create a websocket connection running call(Goal, WebSocket), where WebSocket is a socket-pair. Options:
guarded(+Boolean)
If true (default), guard the execution of Goal and close the websocket on both normal and abnormal termination of Goal. If false, Goal itself is responsible for the created websocket if Goal succeeds. The websocket is closed if Goal fails or raises an exception. This can be used to create a single thread that manages multiple websockets using I/O multiplexing. See library(http/hub).
subprotocols(+List)
List of acceptable subprotocols.
timeout(+TimeOut)
Timeout to apply to the input stream. Default is infinite.

Note that the Request argument is the last for cooperation with http_handler/3. A simple echo server that can be accessed at =/ws/= can be implemented as:

:- use_module(library(http/websocket)).
:- use_module(library(http/thread_httpd)).
:- use_module(library(http/http_dispatch)).

:- http_handler(root(ws),
                http_upgrade_to_websocket(echo, []),
                [spawn([])]).

echo(WebSocket) :-
    ws_receive(WebSocket, Message),
    (   Message.opcode == close
    ->  true
    ;   ws_send(WebSocket, Message),
        echo(WebSocket)
    ).
throws
- switching_protocols(Goal, Options). The recovery from this exception causes the HTTP infrastructure to call call(Goal, WebSocket).
See also
- http_switch_protocol/2.
  228http_upgrade_to_websocket(Goal, Options, Request) :-
  229    request_websocket_info(Request, Info),
  230    debug(websocket(open), 'Websocket request: ~p', [Info]),
  231    sec_websocket_accept(Info, AcceptKey),
  232    choose_subprotocol(Info, Options, SubProtocol, ExtraHeaders),
  233    debug(websocket(open), 'Subprotocol: ~p', [SubProtocol]),
  234    http_switch_protocol(
  235        open_websocket(Goal, SubProtocol, Options),
  236        [ headers([ upgrade(websocket),
  237                    connection('Upgrade'),
  238                    sec_websocket_accept(AcceptKey)
  239                  | ExtraHeaders
  240                  ])
  241        ]).
  242
  243choose_subprotocol(Info, Options, SubProtocol, ExtraHeaders) :-
  244    HdrValue = Info.get(subprotocols),
  245    option(subprotocols(ServerProtocols), Options),
  246    split_string(HdrValue, ",", " ", RequestProtocols),
  247    member(Protocol, RequestProtocols),
  248    member(SubProtocol, ServerProtocols),
  249    atom_string(SubProtocol, Protocol),
  250    !,
  251    ExtraHeaders = [ 'Sec-WebSocket-Protocol'(SubProtocol) ].
  252choose_subprotocol(_, _, null, []).
  253
  254open_websocket(Goal, SubProtocol, Options, HTTPIn, HTTPOut) :-
  255    option(timeout(TimeOut), Options, infinite),
  256    set_stream(HTTPIn, timeout(TimeOut)),
  257    WsOptions = [mode(server), subprotocol(SubProtocol)],
  258    ws_open(HTTPIn, WsIn, WsOptions),
  259    ws_open(HTTPOut, WsOut, WsOptions),
  260    stream_pair(WebSocket, WsIn, WsOut),
  261    guard_websocket_server(Goal, WebSocket, Options).
  262
  263guard_websocket_server(Goal, WebSocket, Options) :-
  264    (   catch(call(Goal, WebSocket), E, true)
  265    ->  (   var(E)
  266        ->  (   option(guarded(false), Options, true)
  267            ->  Close = false
  268            ;   Msg = bye, Code = 1000
  269            )
  270        ;   message_to_string(E, Msg),
  271            Code = 1011
  272        )
  273    ;   Msg = "goal failed", Code = 1011
  274    ),
  275    (   Close == false
  276    ->  true
  277    ;   catch(ws_close(WebSocket, Code, Msg), Error,
  278              print_message(error, Error))
  279    ).
  280
  281
  282request_websocket_info(Request, Info) :-
  283    option(upgrade(Websocket), Request),
  284    downcase_atom(Websocket, websocket),
  285    option(connection(Connection), Request),
  286    connection_contains_upgrade(Connection),
  287    option(sec_websocket_key(ClientKey), Request),
  288    option(sec_websocket_version(Version), Request),
  289    Info0 = _{key:ClientKey, version:Version},
  290    add_option(origin,                   Request, origin,       Info0, Info1),
  291    add_option(sec_websocket_protocol,   Request, subprotocols, Info1, Info2),
  292    add_option(sec_websocket_extensions, Request, extensions,   Info2, Info).
  293
  294connection_contains_upgrade(Connection) :-
  295    split_string(Connection, ",", " ", Tokens),
  296    member(Token, Tokens),
  297    string_lower(Token, "upgrade"),
  298    !.
  299
  300add_option(OptionName, Request, Key, Dict0, Dict) :-
  301    Option =.. [OptionName,Value],
  302    option(Option, Request),
  303    !,
  304    Dict = Dict0.put(Key,Value).
  305add_option(_, _, _, Dict, Dict).
 sec_websocket_accept(+Info, -AcceptKey) is det
Compute the accept key as per 4.2.2., point 5.4
  311sec_websocket_accept(Info, AcceptKey) :-
  312    string_concat(Info.key, "258EAFA5-E914-47DA-95CA-C5AB0DC85B11", Str),
  313    sha_hash(Str, Hash, [ algorithm(sha1) ]),
  314    phrase(base64(Hash), Encoded),
  315    string_codes(AcceptKey, Encoded).
  316
  317
  318                 /*******************************
  319                 *     HIGH LEVEL INTERFACE     *
  320                 *******************************/
 ws_send(+WebSocket, +Message) is det
Send a message over a websocket. The following terms are allowed for Message:
text(+Text)
Send a text message. Text is serialized using write/1.
binary(+Content)
As text(+Text), but all character codes produced by Content must be in the range [0..255]. Typically, Content will be an atom or string holding binary data.
prolog(+Term)
Send a Prolog term as a text message. Text is serialized using write_canonical/1.
json(+JSON)
Send the Prolog representation of a JSON term using json_write_dict/2.
string(+Text)
Same as text(+Text), provided for consistency.
close(+Code, +Text)
Send a close message. Code is 1000 for normal close. See websocket documentation for other values.
Dict
A dict that minimally contains an opcode key. Other keys used are:
format:Format
Serialization format used for Message.data. Format is one of string, prolog or json. See ws_receive/3.
data:Term
If this key is present, it is serialized according to Message.format. Otherwise it is serialized using write/1, which implies that string and atoms are just sent verbatim.

Note that ws_start_message/3 does not unlock the stream. This is done by ws_send/1. This implies that multiple threads can use ws_send/2 and the messages are properly serialized.

To be done
- Provide serialization details using options.
  364ws_send(WsStream, Message) :-
  365    message_opcode(Message, OpCode),
  366    setup_call_cleanup(
  367        ws_start_message(WsStream, OpCode, 0),
  368        write_message_data(WsStream, Message),
  369        ws_send(WsStream)).
  370
  371message_opcode(Message, OpCode) :-
  372    is_dict(Message),
  373    !,
  374    to_opcode(Message.opcode, OpCode).
  375message_opcode(Message, OpCode) :-
  376    functor(Message, Name, _),
  377    (   text_functor(Name)
  378    ->  to_opcode(text, OpCode)
  379    ;   to_opcode(Name, OpCode)
  380    ).
  381
  382text_functor(json).
  383text_functor(string).
  384text_functor(prolog).
  385
  386write_message_data(Stream, Message) :-
  387    is_dict(Message),
  388    !,
  389    (   _{code:Code, data:Data} :< Message
  390    ->  write_message_data(Stream, close(Code, Data))
  391    ;   _{format:prolog, data:Data} :< Message
  392    ->  format(Stream, '~k .~n', [Data])
  393    ;   _{format:json, data:Data} :< Message
  394    ->  json_write_dict(Stream, Data)
  395    ;   _{data:Data} :< Message
  396    ->  format(Stream, '~w', Data)
  397    ;   true
  398    ).
  399write_message_data(Stream, Message) :-
  400    functor(Message, Format, 1),
  401    !,
  402    arg(1, Message, Data),
  403    (   text_functor(Format)
  404    ->  write_text_message(Format, Stream, Data)
  405    ;   format(Stream, '~w', [Data])
  406    ).
  407write_message_data(_, Message) :-
  408    atom(Message),
  409    !.
  410write_message_data(Stream, close(Code, Data)) :-
  411    !,
  412    High is (Code >> 8) /\ 0xff,
  413    Low  is Code /\ 0xff,
  414    put_byte(Stream, High),
  415    put_byte(Stream, Low),
  416    stream_pair(Stream, _, Out),
  417    set_stream(Out, encoding(utf8)),
  418    format(Stream, '~w', [Data]).
  419write_message_data(_, Message) :-
  420    type_error(websocket_message, Message).
  421
  422write_text_message(json, Stream, Data) :-
  423    !,
  424    json_write_dict(Stream, Data).
  425write_text_message(prolog, Stream, Data) :-
  426    !,
  427    format(Stream, '~k .', [Data]).
  428write_text_message(_, Stream, Data) :-
  429    format(Stream, '~w', [Data]).
 ws_receive(+WebSocket, -Message:dict) is det
 ws_receive(+WebSocket, -Message:dict, +Options) is det
Receive the next message from WebSocket. Message is a dict containing the following keys:
opcode:OpCode
OpCode of the message. This is an atom for known opcodes and an integer for unknown ones. If the peer closed the stream, OpCode is bound to close and data to the atom end_of_file.
data:String
The data, represented as a string. This field is always present. String is the empty string if there is no data in the message.
rsv:RSV
Present if the WebSocket RSV header is not 0. RSV is an integer in the range [1..7].

If ping message is received and WebSocket is a stream pair, ws_receive/1 replies with a pong and waits for the next message.

The predicate ws_receive/3 processes the following options:

format(+Format)
Defines how text messages are parsed. Format is one of
string
Data is returned as a Prolog string (default)
json
Data is parsed using json_read_dict/3, which also receives Options.
prolog
Data is parsed using read_term/3, which also receives Options.
To be done
- Add a hook to allow for more data formats?
  471ws_receive(WsStream, Message) :-
  472    ws_receive(WsStream, Message, []).
  473
  474ws_receive(WsStream, Message, Options) :-
  475    ws_read_header(WsStream, Code, RSV),
  476    debug(websocket, 'ws_receive(~p): OpCode=~w, RSV=~w',
  477          [WsStream, Code, RSV]),
  478    (   Code == end_of_file
  479    ->  Message = websocket{opcode:close, data:end_of_file}
  480    ;   (   ws_opcode(OpCode, Code)
  481        ->  true
  482        ;   OpCode = Code
  483        ),
  484        read_data(OpCode, WsStream, Data, Options),
  485        (   OpCode == ping,
  486            reply_pong(WsStream, Data.data)
  487        ->  ws_receive(WsStream, Message, Options)
  488        ;   (   RSV == 0
  489            ->  Message = Data
  490            ;   Message = Data.put(rsv, RSV)
  491            )
  492        )
  493    ),
  494    debug(websocket, 'ws_receive(~p) --> ~p', [WsStream, Message]).
  495
  496read_data(close, WsStream,
  497          websocket{opcode:close, code:Code, format:string, data:Data}, _Options) :-
  498    !,
  499    get_byte(WsStream, High),
  500    (   High == -1
  501    ->  Code = 1000,
  502        Data = ""
  503    ;   get_byte(WsStream, Low),
  504        Code is High<<8 \/ Low,
  505        stream_pair(WsStream, In, _),
  506        set_stream(In, encoding(utf8)),
  507        read_string(WsStream, _Len, Data)
  508    ).
  509read_data(text, WsStream, Data, Options) :-
  510    !,
  511    option(format(Format), Options, string),
  512    read_text_data(Format, WsStream, Data, Options).
  513read_data(OpCode, WsStream, websocket{opcode:OpCode, format:string, data:Data}, _Options) :-
  514    read_string(WsStream, _Len, Data).
 read_text_data(+Format, +WsStream, -Dict, +Options) is det
Read a websocket message into a dict websocket{opcode:OpCode, data:Data}, where Data is parsed according to Format.
  521read_text_data(string, WsStream,
  522          websocket{opcode:text, format:string, data:Data}, _Options) :-
  523    !,
  524    read_string(WsStream, _Len, Data).
  525read_text_data(json, WsStream,
  526          websocket{opcode:text, format:json,   data:Data}, Options) :-
  527    !,
  528    json_read_dict(WsStream, Data, Options).
  529read_text_data(prolog, WsStream,
  530          websocket{opcode:text, format:prolog, data:Data}, Options) :-
  531    !,
  532    read_term(WsStream, Data, Options).
  533read_text_data(Format, _, _, _) :-
  534    domain_error(format, Format).
  535
  536reply_pong(WebSocket, Data) :-
  537    stream_pair(WebSocket, _In, Out),
  538    is_stream(Out),
  539    ws_send(Out, pong(Data)).
 ws_close(+WebSocket:stream_pair, +Code, +Data) is det
Close a WebSocket connection by sending a close message if this was not already sent and wait for the close reply.
Arguments:
Code- is the numerical code indicating the close status. This is 16-bit integer. The codes are defined in section 7.4.1. Defined Status Codes of RFC6455. Notably, 1000 indicates a normal closure.
Data- is currently interpreted as text.
Errors
- websocket_error(unexpected_message, Reply) if the other side did not send a close message in reply.
  555ws_close(WebSocket, Code, Data) :-
  556    setup_call_cleanup(
  557        true,
  558        ws_close_(WebSocket, Code, Data),
  559        close(WebSocket)).
  560
  561ws_close_(WebSocket, Code, Data) :-
  562    stream_pair(WebSocket, In, Out),
  563    (   (   var(Out)
  564        ;   ws_property(Out, status, closed)
  565        )
  566    ->  debug(websocket(close),
  567              'Output stream of ~p already closed', [WebSocket])
  568    ;   ws_send(WebSocket, close(Code, Data)),
  569        close(Out),
  570        debug(websocket(close), '~p: closed output', [WebSocket]),
  571        (   (   var(In)
  572            ;   ws_property(In, status, closed)
  573            )
  574        ->  debug(websocket(close),
  575                  'Input stream of ~p already closed', [WebSocket])
  576        ;   ws_receive(WebSocket, Reply),
  577            (   Reply.opcode == close
  578            ->  debug(websocket(close), '~p: close confirmed', [WebSocket])
  579            ;   throw(error(websocket_error(unexpected_message, Reply), _))
  580            )
  581        )
  582    ).
 ws_open(+Stream, -WSStream, +Options) is det
Turn a raw TCP/IP (or any other binary stream) into a websocket stream. Stream can be an input stream, output stream or a stream pair. Options includes
mode +Mode
One of server or client. If client, messages are sent as masked.
buffer_size(+Count)
Send partial messages for each Count bytes or when flushing the output. The default is to buffer the entire message before it is sent.
close_parent(+Boolean)
If true (default), closing WSStream also closes Stream.
subprotocol(+Protocol)
Set the subprotocol property of WsStream. This value can be retrieved using ws_property/2. Protocol is an atom. See also the subprotocols option of http_open_websocket/3 and http_upgrade_to_websocket/3.

A typical sequence to turn a pair of streams into a WebSocket is here:

    ...,
    Options = [mode(server), subprotocol(chat)],
    ws_open(Input, WsInput, Options),
    ws_open(Output, WsOutput, Options),
    stream_pair(WebSocket, WsInput, WsOutput).
 ws_start_message(+WSStream, +OpCode) is det
 ws_start_message(+WSStream, +OpCode, +RSV) is det
Prepare for sending a new message. OpCode is one of text, binary, close, ping or pong. RSV is reserved for extensions. After this call, the application usually writes data to WSStream and uses ws_send/1 to complete the message. Depending on OpCode, the stream is switched to binary (for OpCode is binary) or text using utf8 encoding (all other OpCode values). For example, to a JSON message can be send using:
ws_send_json(WSStream, JSON) :-
   ws_start_message(WSStream, text),
   json_write(WSStream, JSON),
   ws_send(WSStream).
 ws_send(+WSStream) is det
Complete and send the WebSocket message. If the OpCode of the message is close, close the stream.
 ws_read_header(+WSStream, -OpCode, -RSV) is det
Read the header of the WebSocket next message. After this call, WSStream is switched to the appropriate encoding and reading from the stream will signal end-of-file at the end of the message. Note that this end-of-file does not invalidate WSStream. Reading may perform various tasks on the background:

If not all data has been read for the previous message, it will first read the remainder of the message. This input is silently discarded. This allows for trailing white space after proper text messages such as JSON, Prolog or XML terms. For example, to read a JSON message, use:

ws_read_json(WSStream, JSON) :-
    ws_read_header(WSStream, OpCode, RSV),
    (   OpCode == text,
        RSV == 0
    ->  json_read(WSStream, JSON)
    ;   OpCode == close
    ->  JSON = end_of_file
    ).
 ws_property(+WebSocket, ?Property) is nondet
True if Property is a property WebSocket. Defined properties are:
subprotocol(Protocol)
Protocol is the negotiated subprotocol. This is typically set as a property of the websocket by ws_open/3.
  688ws_property(WebSocket, Property) :-
  689    ws_property_(Property, WebSocket).
  690
  691ws_property_(subprotocol(Protocol), WebSocket) :-
  692    ws_property(WebSocket, subprotocol, Protocol).
 to_opcode(+Spec, -OpCode:int) is det
Convert a specification of an opcode into the numeric opcode.
  698to_opcode(In, Code) :-
  699    integer(In),
  700    !,
  701    must_be(between(0, 15), In),
  702    Code = In.
  703to_opcode(Name, Code) :-
  704    must_be(atom, Name),
  705    (   ws_opcode(Name, Code)
  706    ->  true
  707    ;   domain_error(ws_opcode, Name)
  708    ).
 ws_opcode(?Name, ?Code)
Define symbolic names for the WebSocket opcodes.
  714ws_opcode(continuation, 0).
  715ws_opcode(text,         1).
  716ws_opcode(binary,       2).
  717ws_opcode(close,        8).
  718ws_opcode(ping,         9).
  719ws_opcode(pong,         10).
 ws_mask(-Mask)
Produce a good random number of the mask of a client message.
  726:- public ws_mask/1.  727
  728ws_mask(Mask) :-
  729    Mask is 1+random(1<<32-1)