server.pl 2.9 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596
  1. :- module(server, [server/1]).
  2. :- use_module(service).
  3. :- use_module(library(http/http_dispatch)).
  4. :- use_module(library(http/http_dyn_workers)).
  5. :- use_module(library(http/http_json)).
  6. :- use_module(library(http/http_parameters)).
  7. :- use_module(library(http/http_unix_daemon)).
  8. :- use_module(library(http/thread_httpd)).
  9. :- use_module(library(http/html_write)).
  10. :- use_module(library(dcg/high_order)).
  11. server(Port) :-
  12. odbc_set_option(connection_pooling(true)),
  13. current_prolog_flag(cpu_count, Cores),
  14. Workers is 64 * Cores,
  15. http_server(http_dispatch, [workers(Workers), port(Port), timeout(30)]).
  16. :- http_handler('/plaintext', plaintext_handler, [chunked]).
  17. :- http_handler('/json', json_handler, [chunked]).
  18. :- http_handler('/db', db_handler, [chunked]).
  19. :- http_handler('/queries', queries_handler, [chunked]).
  20. :- http_handler('/fortunes', fortunes_handler, [chunked]).
  21. :- http_handler('/updates', updates_handler, [chunked]).
  22. :- http_handler('/cached-worlds', cached_worlds_handler, [chunked]).
  23. plaintext_handler(_Request) :-
  24. format('Server: SWI-Prolog~n'),
  25. format('Content-Type: text/plain~n~n'),
  26. format('Hello, World!').
  27. json_handler(_Request) :-
  28. format('Server: SWI-Prolog~n'),
  29. reply_json_dict(_{message: 'Hello, World!'}).
  30. db_handler(_Request) :-
  31. service:random_number(Row),
  32. world_json(Row, Json),
  33. format('Server: SWI-Prolog~n'),
  34. reply_json_dict(Json).
  35. queries_handler(Request) :-
  36. queries(Request, N),
  37. service:random_numbers(N, Rows),
  38. maplist(world_json, Rows, Json),
  39. format('Server: SWI-Prolog~n'),
  40. reply_json_dict(Json).
  41. fortunes_handler(_Request) :-
  42. service:fortunes(Rows),
  43. format('Server: SWI-Prolog~n'),
  44. format('Content-Type: text/html; charset=utf-8~n~n'),
  45. phrase(page([ head(title('Fortunes')),
  46. body(table(
  47. [tr([th('id'), th('message')]),
  48. \sequence(row, Rows)]))
  49. ]),
  50. Tokens),
  51. print_html(Tokens).
  52. row(row(N, C)) -->
  53. html(tr([td(N), td(C)])).
  54. updates_handler(Request) :-
  55. queries(Request, N),
  56. service:update(N, Rows),
  57. maplist(world_json, Rows, Json),
  58. format('Server: SWI-Prolog~n'),
  59. reply_json_dict(Json).
  60. cached_worlds_handler(Request) :-
  61. queries(Request, N),
  62. service:random_numbers_cached(N, Rows),
  63. maplist(world_json, Rows, Json),
  64. format('Server: SWI-Prolog~n'),
  65. reply_json_dict(Json).
  66. % -----------------------------------------------------------------------
  67. queries(Request, Queries) :-
  68. catch(
  69. ( http_parameters(Request, [queries(Value, [integer, optional(true), default(1)])])
  70. , cut_off(Value, 1, 500, Queries)
  71. ),
  72. _Caught,
  73. Queries = 1
  74. ).
  75. cut_off(V, L, _, L) :- V < L.
  76. cut_off(V, _, U, U) :- V > U.
  77. cut_off(V, _, _, V).
  78. world_json(row(Id, RandomNumber), _{ id: Id, randomNumber: RandomNumber }).