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