View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        jan@swi-prolog.org
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2024 SWI-Prolog Solutions b.v.
    7
    8    This program is free software; you can redistribute it and/or
    9    modify it under the terms of the GNU General Public License
   10    as published by the Free Software Foundation; either version 2
   11    of the License, or (at your option) any later version.
   12
   13    This program is distributed in the hope that it will be useful,
   14    but WITHOUT ANY WARRANTY; without even the implied warranty of
   15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   16    GNU General Public License for more details.
   17
   18    You should have received a copy of the GNU General Public
   19    License along with this library; if not, write to the Free Software
   20    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   21
   22    As a special exception, if you link this library with other files,
   23    compiled with a Free Software compiler, to produce an executable, this
   24    library does not by itself cause the resulting executable to be covered
   25    by the GNU General Public License. This exception does not however
   26    invalidate any other reasons why the executable file might be covered by
   27    the GNU General Public License.
   28*/
   29
   30:- module(http_server_health,
   31          [ server_health/1             % +Request
   32          ]).   33:- autoload(library(lists), [member/2]).   34:- autoload(library(aggregate), [aggregate_all/3, aggregate_all/4]).   35:- autoload(library(apply), [maplist/3]).   36:- autoload(library(option), [option/2]).   37:- autoload(library(http/http_dispatch), [http_handler/3]).   38:- autoload(library(http/http_json), [reply_json/1]).   39:- autoload(library(http/http_parameters), [http_parameters/2]).   40:- autoload(library(http/thread_httpd), [http_server_property/2, http_workers/2]).   41:- autoload(library(http/http_stream), [cgi_statistics/1]).   42:- use_module(library(http/http_cors), [cors_enable/2, cors_enable/0]).   43
   44:- http_handler(root(health), server_health, [id(server_health), priority(-10)]).   45
   46/** <module> HTTP Server health statistics
   47
   48This module defines an HTTP handler for ``/health``. The handler returns
   49a JSON document  with  elementary  health   statistics  on  the  running
   50instance. The location can be changed  using http_handler/3. Keys may be
   51added using additional clauses for health/2 or hidden using hide/1.
   52
   53This  library  defines  an  HTTP  handler   and  defines  two  multifile
   54predicates (health/2 and hide/1) to control the information presented.
   55*/
   56
   57%!  server_health(+Request)
   58%
   59%   HTTP handler that replies with  the   overall  health of the server.
   60%   Returns a JSON object from all solutions of health/2.
   61%
   62%   Processes an optional parameter `fields` to  specify the fields that
   63%   should be returned.  The  fields  content   is  ","  or  white space
   64%   delimited.
   65
   66server_health(Request) :-
   67    option(method(options), Request), !,
   68    cors_enable(Request,
   69                [ methods([get])
   70                ]),
   71    format('~n').
   72server_health(Request) :-
   73    http_parameters(Request,
   74                    [ fields(FieldSpec, [ optional(true) ])
   75                    ]),
   76    cors_enable,
   77    (   var(FieldSpec)
   78    ->  true
   79    ;   split_string(FieldSpec, ", \t\r\n", " \t\r\n", Strings),
   80        maplist(atom_string, Fields, Strings)
   81    ),
   82    get_server_health(Health, Fields),
   83    reply_json(Health).
   84
   85get_server_health(Health, Fields) :-
   86    var(Fields),
   87    !,
   88    findall(Key-Value, health(Key, Value), Pairs),
   89    dict_pairs(Health, health, Pairs).
   90get_server_health(Health, Fields) :-
   91    findall(Key-Value, (member(Key,Fields),health(Key, Value)), Pairs),
   92    dict_pairs(Health, health, Pairs).
   93
   94%!  health(-Key, -Value) is nondet.
   95%
   96%   Multifile extensible. True when  Key/Value  can   be  reported  as a
   97%   health statistics. Keys may  be  added   by  adding  clauses to this
   98%   multifile predicate. Keys may be   filtered using hide/1. Predefined
   99%   Key values are:
  100%
  101%     - up
  102%       Defined to be `true`.
  103%     - epoch
  104%       Starting time of the server in seconds after Jan 1, 1970 UTC.
  105%     - cpu_time
  106%       Total process CPU usage in seconds.
  107%     - threads
  108%       Number of active threads
  109%     - workers
  110%       Number of HTTP _worker_ threads.
  111%     - requests
  112%       Number of HTTP requests processed.
  113%     - bytes_sent
  114%       Number of bytes send in reply to HTTP requests.
  115%     - open_files
  116%       Number of open file streams.  This includes physical files as
  117%       well as sockets (except for Windows).  On Linux we count the
  118%       file handles in ``/proc/self/fd``.  Otherwise we use
  119%       stream_property/2 with the file_no(Fd) property.
  120%     - loadavg
  121%       An array holding the load average over the last [1,5,15]
  122%       minutes.  This key is only supported on Linux machines.  It
  123%       is based on ``/proc/loadavg``
  124%     - heap
  125%       When compiled with TCMalloc, this provides two properties:
  126%       - inuse: Bytes
  127%         Total amount of in-use memory in bytes
  128%       - size: Bytes
  129%         Same as `inuse`, but including the TCMalloc overhead and
  130%         (thus) memory that has been freed and is not (yet) reused.
  131%
  132%   @arg Key is the name of the JSON key.  Must be an atom
  133%   @arg Value is the Prolog representation for a JSON (dict) value.
  134
  135:- multifile health/2.  136
  137term_expansion((health(Key,Value) :- Body),
  138               (health(Key,Value) :- \+ hide(Key), Body)).
  139
  140health(up, true) :-
  141    true.
  142health(epoch, Epoch) :-
  143    http_server_property(_, start_time(Epoch)).
  144health(cpu_time, Time) :-
  145    statistics(process_cputime, Time).
  146health(threads, Count) :-
  147    statistics(threads, Count).
  148health(workers, Count) :-
  149    aggregate_all(sum(N), http_workers(_,N), Count).
  150health(requests, RequestCount) :-
  151    cgi_statistics(requests(RequestCount)).
  152health(bytes_sent, BytesSent) :-
  153    cgi_statistics(bytes_sent(BytesSent)).
  154:- if(exists_directory('/proc/self/fd')).  155health(open_files, Streams) :-
  156    directory_files('/proc/self/fd', FDs),
  157    length(FDs, Files),
  158    Streams is Files - 2.               % Ignore . and ..
  159:- else.  160health(open_files, Streams) :-
  161    findall(N, stream_property(_, file_no(N)), FDs),
  162    sort(FDs, Unique),
  163    length(Unique, Streams).
  164:- endif.  165health(loadavg, LoadAVG) :-
  166    access_file('/proc/loadavg', exist),
  167    catch(setup_call_cleanup(
  168              open('/proc/loadavg', read, In),
  169              read_string(In, _, String),
  170              close(In)),
  171	      _, fail),
  172    split_string(String, " ", " ", [One,Five,Fifteen|_]),
  173    maplist(number_string, LoadAVG, [One,Five,Fifteen]).
  174:- if(current_predicate(malloc_property/1)).  175health(heap, json{inuse:InUse, size:Size}) :-
  176    malloc_property('generic.current_allocated_bytes'(InUse)),
  177    malloc_property('generic.heap_size'(Size)).
  178:- endif.  179
  180%!  hide(?Key) is nondet.
  181%
  182%   Multifile hook. If true for  a   specific  Key, hide this statistics
  183%   from the output. This may be used to hide keys that are considered a
  184%   security risk.
  185
  186:- multifile hide/1.