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