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