Sfoglia il codice sorgente

Compiling the app before running it. (#6719)

* Compiling the app before running it.

* Adding 2 threads to ODBC

* Freeing ODBC Statement

* Primitive cache for template rendering

* Using module html_write for fortunes endpoint
vka 4 anni fa
parent
commit
4055390cb8

+ 35 - 10
frameworks/Prolog/SWI-Prolog/app/database.pl

@@ -6,13 +6,17 @@
 :- use_module(library(random)).
 
 :- dynamic cache/2.
+:- dynamic cache/3.
 
 top_id(10001).
 
 find_random_numbers(_Connection, 0, [], _Cached).
 find_random_numbers(Connection, N, Rows, Cached) :-
-    world_by_id_statement(Connection, Statement),
-    find_random_numbers_(Statement, N, Rows, Cached).
+    setup_call_cleanup(
+        world_by_id_statement(Connection, Statement),
+        find_random_numbers_(Statement, N, Rows, Cached),
+        odbc_free_statement(Statement)
+    ).
 
 find_random_numbers_(_Statement, 0, [], _Cached).
 find_random_numbers_(Statement, N, [Row|Rows], Cached) :-
@@ -24,13 +28,19 @@ find_random_numbers_(Statement, N, [Row|Rows], Cached) :-
     find_random_numbers_(Statement, N1, Rows, Cached).
 
 find_fortunes(Connection, Rows) :-
-    fortune_statement(Connection, Statement),
-    findall(Row, odbc_execute(Statement, [], Row), Rows).
+    setup_call_cleanup(
+        fortune_statement(Connection, Statement),
+        findall(Row, odbc_execute(Statement, [], Row), Rows),
+        odbc_free_statement(Statement)
+    ).
 
 update_random_numbers(_Connection, [], []).
 update_random_numbers(Connection, Rows0, Rows) :-
-    update_world_statement(Connection, Statement),
-    update_random_numbers_(Statement, Rows0, Rows).
+    setup_call_cleanup(
+        update_world_statement(Connection, Statement),
+        update_random_numbers_(Statement, Rows0, Rows),
+        odbc_free_statement(Statement)
+    ).
 
 update_random_numbers_(_Statement, [], []).
 update_random_numbers_(Statement, [row(Id0,_)|Rows0], [Row|Rows]) :-
@@ -43,13 +53,28 @@ update_random_numbers_(Statement, [row(Id0,_)|Rows0], [Row|Rows]) :-
 % ------------------------------------------------------------------------------------
 
 world_by_id_statement(Connection, Statement) :-
-    odbc_prepare(Connection, 'SELECT id, randomNumber FROM World WHERE id = ?', [integer], Statement).
-
+    odbc_prepare(
+        Connection, 
+        'SELECT id, randomNumber FROM World WHERE id = ?', 
+        [integer], 
+        Statement
+    ).
+    
 fortune_statement(Connection, Statement) :-
-    odbc_prepare(Connection, 'SELECT id, message FROM Fortune', [], Statement).
+    odbc_prepare(
+        Connection, 
+        'SELECT id, message FROM Fortune', 
+        [], 
+        Statement
+    ).
 
 update_world_statement(Connection, Statement) :-
-    odbc_prepare(Connection, 'UPDATE World SET randomNumber = ? WHERE id = ?', [integer, integer], Statement).
+    odbc_prepare(
+        Connection, 
+        'UPDATE World SET randomNumber = ? WHERE id = ?', 
+        [integer, integer], 
+        Statement
+    ).
 
 % ------------------------------------------------------------------------------------
 

+ 16 - 23
frameworks/Prolog/SWI-Prolog/app/server.pl

@@ -7,18 +7,15 @@
 :- use_module(library(http/http_json)).
 :- use_module(library(http/http_parameters)).
 :- use_module(library(http/http_unix_daemon)).
-:- use_module(library(st/st_render)).
 :- use_module(library(http/thread_httpd)).
-
+:- use_module(library(http/html_write)).
+:- use_module(library(dcg/high_order)).
 
 server(Port) :-
     odbc_set_option(connection_pooling(true)),
     current_prolog_flag(cpu_count, Cores),
-    Workers is Cores * 2,
-    server(Port, [workers(Workers)]).
-
-server(Port, Options) :-
-    http_server(http_dispatch, [port(Port),timeout(120)|Options]).
+    Workers is 8 * Cores,
+    http_server(http_dispatch, [workers(Workers), port(Port), timeout(30)]).
 
 
 :- http_handler('/plaintext',     plaintext_handler,     [chunked]).
@@ -54,12 +51,18 @@ queries_handler(Request) :-
 
 fortunes_handler(_Request) :-
     service:fortunes(Rows),
-    maplist(fortune_json, Rows, Items),
-    render_template(fortunes, _{ items: Items }, Payload, Len),
     format('Server: SWI-Prolog~n'),
-    format('Content-Type: text/html; charset=utf-8~n'),
-    format('Content-Length: ~d~n~n', [Len]),
-    format(Payload).
+    format('Content-Type: text/html; charset=utf-8~n~n'),
+    phrase(page([ head(title('Fortunes')),
+                  body(table(
+                      [tr([th('id'), th('message')]),
+                       \sequence(row, Rows)]))
+                ]),
+           Tokens),
+    print_html(Tokens).
+
+row(row(N, C)) -->
+    html(tr([td(N), td(C)])).
 
 updates_handler(Request) :-
     queries(Request, N),
@@ -82,7 +85,7 @@ queries(Request, Queries) :-
         ( http_parameters(Request, [queries(Value, [integer, optional(true), default(1)])])
         , cut_off(Value, 1, 500, Queries)
         ),
-        Caught,
+        _Caught,
         Queries = 1
     ).
 
@@ -91,13 +94,3 @@ cut_off(V, _, U, U) :- V > U.
 cut_off(V, _, _, V).
 
 world_json(row(Id, RandomNumber), _{ id: Id, randomNumber: RandomNumber }).
-
-fortune_json(row(Id, Message), _{ id: Id, message: Message }).
-
-render_template(Template, Data, Result, Len) :-
-    with_output_to(codes(Codes), (
-        current_output(Out),
-        st_render_file(Template, Data, Out, _{ cache: true })
-    )),
-    length(Codes, Len),
-    string_codes(Result, Codes).

+ 6 - 18
frameworks/Prolog/SWI-Prolog/config/odbc.ini

@@ -1,19 +1,7 @@
 [benchmark]
-Description         = Benchmark Database
-Driver              = /usr/lib/x86_64-linux-gnu/odbc/psqlodbcw.so
-Trace               = Yes
-TraceFile           = sql.log
-Servername          = tfb-database
-Database            = hello_world
-UserName            = benchmarkdbuser
-Password            = benchmarkdbpass
-Port                = 5432
-Protocol            = 13.3
-ReadOnly            = No
-RowVersioning       = No
-ShowSystemTables    = No
-ShowOidColumn       = No
-FakeOidIndex        = No
-ConnSettings        =
-MaxVarcharSize      = 4096
-Pooling             = Yes
+Driver     = postgresql
+Servername = tfb-database
+Database   = hello_world
+UserName   = benchmarkdbuser
+Password   = benchmarkdbpass
+Port       = 5432

+ 14 - 0
frameworks/Prolog/SWI-Prolog/config/odbcinst.ini

@@ -0,0 +1,14 @@
+[postgresql]
+Driver           = /usr/lib/x86_64-linux-gnu/odbc/psqlodbcw.so
+Trace            = No
+Debug            = No
+Threading        = 1
+Protocol         = 13.3
+ReadOnly         = No
+RowVersioning    = No
+ShowSystemTables = No
+ShowOidColumn    = No
+FakeOidIndex     = No
+ConnSettings     =
+MaxVarcharSize   = 4096
+Pooling          = Yes

+ 10 - 4
frameworks/Prolog/SWI-Prolog/swi-prolog.dockerfile

@@ -6,13 +6,19 @@ RUN echo 'debconf debconf/frontend select Noninteractive' | debconf-set-selectio
 RUN apt update -yqq && apt-get install -y software-properties-common
 RUN apt-add-repository ppa:swi-prolog/stable -y
 RUN apt-get update -y && apt-get install -y --no-install-recommends swi-prolog swi-prolog-odbc odbc-postgresql
-RUN swipl -g 'pack_install(simple_template, [interactive(false), silent(true)]).'
 
 EXPOSE 8080
 
 WORKDIR /app
 
-CMD [ "swipl", "server.pl", "--user=daemon", "--fork=false", "--port=8080" ]
-
+COPY ./config/odbcinst.ini /etc/odbcinst.ini
 COPY ./config/odbc.ini /etc/odbc.ini
-COPY app .
+COPY app .
+
+RUN swipl --stand_alone=true \
+          -g 'server(8080)' \
+          -O \
+          -o server \
+          -c server.pl
+
+CMD [ "/app/server", "--user=daemon", "--fork=false" ]