Slow calculations, use websockets to refresh webpage when finished (original) (raw)

I want to display the results of some rather slow calculations on a webpage. While busy, some message is shown, and the webpage is updated when finished.

  1. Simple solution using repetitive page refreshes.
:- use_module(library(http/http_server)).
:- use_module(library(main)).

:- initialization(main, main).

main(_Argv) :-
    http_server([port(8001)]),
    thread_create(solve, _, []),
    thread_get_message(quit).

:- http_handler(root(.), home, []).

home(_Request) :-
    reply_html_page(
      [ title("Not pretty"), \refresh ],
      \status).

refresh -->
    { result(_) },
    !.

refresh -->
    html(meta(['http-equiv'(refresh), content(2)])).

status -->
    { result(R) },
    !,
    html(p("Result is ~w"-R)).

status -->
    html(p("Still busy")).

:- dynamic result/1.

solve :-
    sleep(10),
    assert(result(42)).

Invoke swipl refresh.pl and then open http://localhost:8001/ in your browser.

  1. Nice solution that sends a refresh message via a websocket.
:- use_module(library(http/websocket)).
:- use_module(library(http/http_server)).
:- use_module(library(http/thread_httpd)).
:- use_module(library(http/html_write)).
:- use_module(library(http/js_write)).

server :-
    thread_create(solve, _, [alias(solver)]),
    http_server([port(8001)]).

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

wait(Socket) :-
    thread_wait(result(_), [wait_preds([+(result/1)])]),
    ws_send(Socket, websocket{data:"refresh", format:string, opcode:text}).

:- http_handler(root(.), home, []).

home(_Request) :-
    reply_html_page(
      [ title("Pretty"), \refresh ],
      \status).

refresh
--> { result(_) },
    !.

refresh
--> js_script({|javascript||
      var connection;

      function openWebSocket()
      {
        connection = new WebSocket("ws://" + window.location.host + "/wait");

        connection.onmessage = function(e)
        { 
          if(e.data == 'refresh')
          {
            location.reload();
          } 
        }
      }

      window.addEventListener("DOMContentLoaded", openWebSocket, false);
    |}).

status
--> { result(R) },
    !,
    html(p("Result is ~w"-R)).

status
--> html(p("Still busy")).

:- dynamic result/1.

solve :-
    sleep(20),
    assert(result(42)).

Is there anything I can improve (other than the turbopascalian indentation)?

Edit: Changed thread_join/1 to thread_wait/2 to allow for multiple requests within the busy time. The result is now available after 20 s. If the browser is closed and reopened again, we get error messages about broken pipes. How do I avoid or catch/3 these?

Here’s a version in which slow calculations are started at the beginning of each http session. That’s unfortunately my use case.

:- use_module(library(http/websocket)).
:- use_module(library(http/http_server)).
:- use_module(library(http/thread_httpd)).
:- use_module(library(http/html_write)).
:- use_module(library(http/js_write)).
:- use_module(library(http/http_session)).
:- use_module(library(broadcast)).

server :-
    http_server([port(8001)]).

http_upgrade_to_websocket1(Goal, Options, Request) :-
    http_session_id(Session),
    Goal =.. [Wait | Args],
    Goal1 =.. [Wait, Session | Args],
    http_upgrade_to_websocket(Goal1, Options, Request).

:- http_handler(root(wait),
    http_upgrade_to_websocket1(wait, [subprotocols([wait])]), [spawn([])]).

wait(Session, Socket) :-
    thread_wait(result(Session, _), [wait_preds([+(result/2)])]),
    ws_send(Socket, websocket{data:"refresh", format:string, opcode:text}).

:- http_handler(root(.), home, []).

home(_Request) :-
    reply_html_page(
      [ title("Dynamic"), \refresh ],
      \status).

refresh
--> { http_session_id(Session),
      result(Session, _)
    }, !.

refresh
--> js_script({|javascript||
      var connection;

      function openWebSocket()
      {
        connection = new WebSocket("ws://" + window.location.host + "/wait");

        connection.onmessage = function(e)
        {
          if(e.data == "refresh")
            location.reload();
        }
      }

      window.addEventListener("DOMContentLoaded", openWebSocket, false);
    |}).

status
--> { http_session_id(Session),
      result(Session, R) },
    !,
    html(p("Session ~w, Result is ~w"-[Session, R])).

status
--> { http_session_id(Session) },
    html(p("Session ~w still busy"-[Session])).

:- listen(http_session(begin(Session, _Peer)), begin_session(Session)).

begin_session(Session) :-
    thread_create(solve(Session), _).

:- dynamic result/2.

solve(Session) :-
    sleep(10),
    assert(result(Session, 42)).

:- listen(http_session(end(Session, _Peer)), end_session(Session)).

end_session(Session) :-
    retractall(result(Session, _)).
  1. I used the dynamic result/2 instead of http_session_data/1 because thread_wait/2 can then be triggered by the assertion of result/2 (see option wait_preds) and does not need to do polling.
  2. The goal in http_upgrade_to_websocket/3 does not seem to be aware of the http session id, therefore the extra step via http_upgrade_to_websocket1/3.

One more version with htmx that replaces an element using an “SSE”, server sent event. No websockets involved.

:- use_module(library(http/http_server)).
:- use_module(library(http/html_write)).
:- use_module(library(http/htmx)).
:- use_module(library(main)).

:- initialization(main, main).

main(_Argv) :-
    thread_create(solve, _, [alias(solver)]),
    http_server([port(8001)]),
    thread_get_message(quit).

:- http_handler(root(.), home, []).

home(_Request) :-
    reply_html_page(
      [ title('HTMX demo'),
        script(
          [ src("https://unpkg.com/htmx.org@2.0.4"),
            integrity("sha384-HGfztofotfshcF7+8n44JQL2oJmowVChPTg48S+jvZoztPfvwD79OC/LTtG6dMp+"),
            crossorigin(anonymous)
          ], []),
        script(
          [ src("https://unpkg.com/htmx-ext-sse@2.2.3"),
            integrity("sha384-Y4gc0CK6Kg+hmulDc6rZPJu0tqvk7EWlih0Oh+2OkAi1ZDlCbBDCQEE2uVk472Ky"),
            crossorigin(anonymous)
          ], [])
      ],
      [ p("Some static text"),
        \result
      ]
    ).

result
--> { result(X) },
    !,
    html(p("Result is ~w."-[X])).

result
--> html(div(id(sse),
      div(['hx-ext'(sse), 'sse-connect'('/sse'), 'sse-swap'(message), 'hx-target'('#sse')],
        p("Still busy...")
      ))).

:- http_handler(root(sse), sse, []).

sse(_Request) :-
    thread_wait(result(_), [wait_preds([+(result/1)])]),
    phrase(html(\result), Tokens),
    with_output_to_chars(print_html(Tokens), Codes),
    exclude(=(10), Codes, NoN), % remove newlines :-/
    string_codes(String, NoN),
    format('X-Accel-Buffering: no~n', []),
    format('Content-Type: text/event-stream~n', []),
    format('Cache-Control: no-cache~n~n', []),
    format('event: message~n'),
    format('data: ~w~n~n', [String]).

:- dynamic result/1.

solve :-
    sleep(5),
    assert(result(42)).

The slightly cumbersome reply is needed because SSE does not like newlines in the reply :-/

Edit: see below for an improved solution to this problem.

If you would want newline you probably have to use <br/>
instead of 0x0A. This Pyhon code does such a replace:

   token = self.story_tokens_queue.get().replace("\n", "<br/>")
   return f"data: {token}\n\n"

https://stackoverflow.com/q/77387165/17524790

But this only works if get() gives you text/plain, since text/html
allows newline inside tags, and when the parent element is in

layout collapse mode as irrelevant. In such cases the
replace would make it invalid or change the content.

P.S.: Smells like HTMX is heading towards the
poorly designed web frameworks graveyard.

The newlines do not carry any meaning, they are inserted by print_html/2 to improve clarity of the output:

?- phrase(html(p(123)), Tokens), print_html(Tokens).


<p>
123</p>
Tokens = [nl(2), <, p, >, nl(1), 123, </, p, >].

Well not all parent elements have layout collapse,
for example the textarea element in HTML:

<textarea name="story" rows="5" cols="33">
You may write me down in history
With your bitter, twisted lies,
You may trod me in the very dirt
But still, like dust, I'll rise.
</textarea>

It is similar to <![CDATA[]> in SGML. It will render like this:

image

if you remove the newline it will be rendered like this:

image

If you replace newline by <br/> it will be rendered like this:

image

So neither of the two modification methods, i.e Prolog exclude(=(10),
Codes, NoN) or Python replace("\n", "<br/>"), would work for this
example. But I don’t know what HTMX suggests for such a payload.

One can actually have multiple data lines. This is the updated example (with session-specific calculations, as above):

:- use_module(library(http/http_server)).
:- use_module(library(http/html_write)).
:- use_module(library(http/htmx)).
:- use_module(library(http/http_session)).
:- use_module(library(broadcast)).
:- use_module(library(main)).

:- initialization(main, main).

main(_Argv) :-
    http_server([port(8001)]),
    thread_get_message(quit).

:- http_handler(root(.), home, []).

home(_Request) :-
    reply_html_page(
      [ title('HTMX demo'),
        script(
          [ src("https://unpkg.com/htmx.org@2.0.4"),
            integrity("sha384-HGfztofotfshcF7+8n44JQL2oJmowVChPTg48S+jvZoztPfvwD79OC/LTtG6dMp+"),
            crossorigin(anonymous)
          ], []),
        script(
          [ src("https://unpkg.com/htmx-ext-sse@2.2.3"),
            integrity("sha384-Y4gc0CK6Kg+hmulDc6rZPJu0tqvk7EWlih0Oh+2OkAi1ZDlCbBDCQEE2uVk472Ky"),
            crossorigin(anonymous)
          ], [])
      ],
      [ p("Some static text"),
        \status
      ]
    ).

status
--> { http_session_id(Session),
      result(Session, X)
    },
    !,
    html(pre("Session: ~w.\n\n  (indented) Result is ~w.\n"-[Session, X])).

status
--> { http_session_id(Session) },
    html(div(id(sse),
      div(['hx-ext'(sse), 'sse-connect'('/sse'), 'sse-swap'(message), 'hx-target'('#sse')],
        p("Session: ~w. Still busy..."-[Session])
      ))).

:- http_handler(root(sse), sse, []).

sse(_Request) :-
    http_session_id(Session),
    thread_wait(result(Session, _), [wait_preds([+(result/2)])]),
    phrase(html(\status), Tokens),
    % replace \n by multiline data: fields
    with_output_to(string(NL), print_html(Tokens)),
    split_string(NL, "\n", "", L),
    atomics_to_string(L, "\ndata: ", String),
    format('X-Accel-Buffering: no~n', []),
    format('Content-Type: text/event-stream~n', []),
    format('Cache-Control: no-cache~n~n', []),
    format('event: message~n'),
    format('data: ~w~n~n', [String]).

:- listen(http_session(begin(Session, _Peer)), begin_session(Session)).

begin_session(Session) :-
    thread_create(solve(Session), _).

:- dynamic result/2.

solve(Session) :-
    sleep(10),
    assert(result(Session, 42)).

:- listen(http_session(end(Session, _Peer)), end_session(Session)).

end_session(Session) :-
    retractall(result(Session, _)).

For the same reasons as stated above (thread_wait/3 being triggered by an assertion of result/2), I did not use http_session_data/_ and friends.

true. The double ~n at the end of the message reminds of a recently discovered bug in sendmail.