1/*  Part of ClioPatria
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@uva.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (C): 2010, University of Amsterdam,
    7			 VU University Amsterdam.
    8
    9    This program is free software; you can redistribute it and/or
   10    modify it under the terms of the GNU General Public License
   11    as published by the Free Software Foundation; either version 2
   12    of the License, or (at your option) any later version.
   13
   14    This program is distributed in the hope that it will be useful,
   15    but WITHOUT ANY WARRANTY; without even the implied warranty of
   16    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   17    GNU General Public License for more details.
   18
   19    You should have received a copy of the GNU General Public
   20    License along with this library; if not, write to the Free Software
   21    Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
   22
   23    As a special exception, if you link this library with other files,
   24    compiled with a Free Software compiler, to produce an executable, this
   25    library does not by itself cause the resulting executable to be covered
   26    by the GNU General Public License. This exception does not however
   27    invalidate any other reasons why the executable file might be covered by
   28    the GNU General Public License.
   29*/
   30
   31:- module(server_stats,
   32	  [ http_session_table//0,
   33	    http_server_statistics//0,
   34	    http_server_pool_table//0
   35	  ]).   36:- use_module(library(option)).   37:- use_module(library(pairs)).   38:- use_module(library(http/http_session)).   39:- use_module(library(http/http_dispatch)).   40:- use_module(library(http/http_stream)).   41:- use_module(library(http/thread_httpd)).   42:- use_module(library(http/html_write)).   43:- use_module(library(http/html_head)).   44
   45:- html_meta
   46	odd_even_row(+, -, html, ?, ?).

Server statistics components

*/

   52:- http_handler(root(stats),	server_stats, [id(stats)]).   53
   54server_stats(_Request) :-
   55	reply_html_page(title('SWI-Prolog server statistics'),
   56			[ \html_requires(css('stats.css')),
   57			  h1(class(wiki), 'Sessions'),
   58			  \http_session_table,
   59			  h1(class(wiki), 'Server statistics'),
   60			  \http_server_statistics,
   61			  h2(class(wiki), 'Pool statistics'),
   62			  \http_server_pool_table
   63			]).
 http_session_table//
HTML component that writes a table of current sessions.
   70http_session_table -->
   71	{ findall(S, session(S), Sessions0),
   72	  sort(Sessions0, Sessions),
   73	  Sessions \== [], !
   74	},
   75	html([ table([ class(block)
   76		     ],
   77		     [ tr([th('User'), th('Real Name'),
   78			   th('On since'), th('Idle'), th('From')])
   79		     | \sessions(Sessions, 1)
   80		     ])
   81	     ]).
   82http_session_table -->
   83	html(p('No users logged in')).
 session(-Session:s(Idle,User,SessionID,Peer)) is nondet
Enumerate all current HTTP sessions.
   89session(s(Idle, User, SessionID, Peer)) :-
   90	http_current_session(SessionID, peer(Peer)),
   91	http_current_session(SessionID, idle(Idle)),
   92	User = (-).
   93
   94sessions([], _) --> [].
   95sessions([H|T], Row) -->
   96	odd_even_row(Row, Next, \session(H)),
   97	sessions(T, Next).
   98
   99session(s(Idle, -, _SessionID, Peer)) -->
  100	html([td(-), td(-), td(-), td(\idle(Idle)), td(\ip(Peer))]).
  101session(s(Idle, User, _SessionID, Peer)) -->
  102	{  RealName = '?',
  103	   OnSince = 0
  104	},
  105	html([td(User), td(RealName), td(\date(OnSince)), td(\idle(Idle)), td(\ip(Peer))]).
  106
  107idle(Time) -->
  108	{ Secs is round(Time),
  109	  Min is Secs // 60,
  110	  Sec is Secs mod 60
  111	},
  112	html('~`0t~d~2|:~`0t~d~5|'-[Min, Sec]).
  113
  114date(Date) -->
  115	{ format_time(string(S), '%+', Date)
  116	},
  117	html(S).
  118
  119ip(ip(A,B,C,D)) --> !,
  120	html('~d.~d.~d.~d'-[A,B,C,D]).
  121ip(IP) -->
  122	html('~w'-[IP]).
 http_server_statistics//
HTML component showing statistics on the HTTP server
  129http_server_statistics -->
  130	{ findall(Port-ID, http_current_worker(Port, ID), Workers),
  131	  group_pairs_by_key(Workers, Servers)
  132	},
  133	html([ table([ class(block)
  134		     ],
  135		     [ \servers_stats(Servers)
  136		     ])
  137	     ]).
  138
  139servers_stats([]) --> [].
  140servers_stats([H|T]) -->
  141	server_stats(H), servers_stats(T).
  142
  143:- if(catch(statistics(process_cputime, _),_,fail)).  144cputime(CPU) :- statistics(process_cputime, CPU).
  145:- else.  146cputime(CPU) :- statistics(cputime, CPU).
  147:- endif.  148
  149server_stats(Port-Workers) -->
  150	{ length(Workers, NWorkers),
  151	  http_server_property(Port, start_time(StartTime)),
  152	  format_time(string(ST), '%+', StartTime),
  153	  cputime(CPU),
  154	  statistics(heapused, Heap)
  155	},
  156	html([ \server_stat('Port:', Port, odd),
  157	       \server_stat('Started:', ST, even),
  158	       \server_stat('Total CPU usage:', [\n('~2f',CPU), ' seconds'], odd),
  159	       \server_stat('Heap memory:', [ \n(human,Heap), ' bytes' ], even),
  160	       \request_statistics,
  161	       \server_stat('# worker threads:', NWorkers, odd),
  162	       tr(th(colspan(6), 'Statistics by worker')),
  163	       tr([ th('Thread'),
  164		    th('CPU'),
  165		    th(''),
  166		    th('Local'),
  167		    th('Global'),
  168		    th('Trail')
  169		  ]),
  170	       \http_workers(Workers, odd)
  171	     ]).
  172
  173server_stat(Name, Value, OE) -->
  174	html(tr(class(OE),
  175		[ th([class(p_name), colspan(3)], Name),
  176		  td([class(value),  colspan(3)], Value)
  177		])).
  178
  179
  180request_statistics -->
  181	{ cgi_statistics(requests(Count)),
  182	  cgi_statistics(bytes_sent(Sent))
  183	},
  184	server_stat('Requests processed:', \n(human, Count), odd),
  185	server_stat('Bytes sent:', \n(human, Sent), even).
  186
  187
  188http_workers([], _) -->
  189	[].
  190http_workers([H|T], OE) -->
  191	{ odd_even(OE, OE2) },
  192	http_worker(H, OE),
  193	http_workers(T, OE2).
  194
  195http_worker(H, OE) -->
  196	{ thread_statistics(H, locallimit, LL),
  197	  thread_statistics(H, globallimit, GL),
  198	  thread_statistics(H, traillimit, TL),
  199	  thread_statistics(H, localused, LU),
  200	  thread_statistics(H, globalused, GU),
  201	  thread_statistics(H, trailused, TU),
  202	  thread_statistics(H, cputime, CPU)
  203	},
  204	html([ tr(class(OE),
  205		  [ td(rowspan(2), H),
  206		    \nc('~3f', CPU, [rowspan(2)]),
  207		    th('In use'),
  208		    \nc(human, LU),
  209		    \nc(human, GU),
  210		    \nc(human, TU)
  211		  ]),
  212	       tr(class(OE),
  213		  [ th('Limit'),
  214		    \nc(human, LL),
  215		    \nc(human, GL),
  216		    \nc(human, TL)
  217		  ])
  218	     ]).
  219
  220odd_even(even, odd).
  221odd_even(odd, even).
  222
  223
  224		 /*******************************
  225		 *	      POOLS		*
  226		 *******************************/
 http_server_pool_table//
Display table with statistics on thread-pools.
  232http_server_pool_table -->
  233	{ findall(Pool, current_thread_pool(Pool), Pools),
  234	  sort(Pools, Sorted)
  235	},
  236	html(table([ id('http-server-pool'),
  237		     class(block)
  238		   ],
  239		   [ tr([th('Name'), th('Running'), th('Size'), th('Waiting'), th('Backlog')])
  240		   | \server_pools(Sorted, 1)
  241		   ])).
  242
  243server_pools([], _) --> [].
  244server_pools([H|T], Row) -->
  245	odd_even_row(Row, Next, \server_pool(H)),
  246	server_pools(T, Next).
  247
  248server_pool(Pool) -->
  249	{ findall(P, thread_pool_property(Pool, P), List),
  250	  memberchk(size(Size), List),
  251	  memberchk(running(Running), List),
  252	  memberchk(backlog(Waiting), List),
  253	  memberchk(options(Options), List),
  254	  option(backlog(MaxBackLog), Options, infinite)
  255	},
  256	html([ th(class(p_name), Pool),
  257	       \nc(human, Running),
  258	       \nc(human, Size),
  259	       \nc(human, Waiting),
  260	       \nc(human, MaxBackLog)
  261	     ]).
  262
  263
  264		 /*******************************
  265		 *	       BASICS		*
  266		 *******************************/
 n(+Format, +Value)//
HTML component to emit a number.
See also
- nc//2 for details.
  274n(Fmt, Value) -->
  275	{ number_html(Fmt, Value, HTML) },
  276	html(HTML).
  277
  278number_html(human, Value, HTML) :-
  279	integer(Value), !,
  280	human_count(Value, HTML).
  281number_html(Fmt, Value, HTML) :-
  282	number(Value), !,
  283	HTML = Fmt-[Value].
  284number_html(_, Value, '~p'-[Value]).
  285
  286
  287human_count(Number, HTML) :-
  288	Number < 1024, !,
  289	HTML = '~d'-[Number].
  290human_count(Number, HTML) :-
  291	Number < 1024*1024, !,
  292	KB is Number/1024,
  293	digits(KB, N),
  294	HTML = '~*fK'-[N, KB].
  295human_count(Number, HTML) :-
  296	Number < 1024*1024*1024, !,
  297	MB is Number/(1024*1024),
  298	digits(MB, N),
  299	HTML = '~*fM'-[N, MB].
  300human_count(Number, HTML) :-
  301	TB is Number/(1024*1024*1024),
  302	digits(TB, N),
  303	HTML = '~*fG'-[N, TB].
  304
  305digits(Count, N) :-
  306	(   Count < 100
  307	->  N = 1
  308	;   N = 0
  309	).
 nc(+Format, +Value)// is det
 nc(+Format, +Value, +Options)// is det
Numeric cell. The value is formatted using Format and right-aligned in a table cell (td).
Arguments:
Format- is a (numeric) format as described by format/2 or the constant human. Human formatting applies to integers and prints then in abreviated (K,M,T) form, e.g., 4.5M for 4.5 million.
Options- is passed as attributed to the td element. Default alignment is right.
  325nc(Fmt, Value) -->
  326	nc(Fmt, Value, []).
  327
  328nc(Fmt, Value, Options) -->
  329	{ class(Value, Class),
  330	  merge_options(Options,
  331			[ align(right),
  332			  class(Class)
  333			], Opts),
  334	  number_html(Fmt, Value, HTML)
  335	},
  336	html(td(Opts, HTML)).
  337
  338class(Value, Class) :-
  339	(   integer(Value)
  340	->  Class = int
  341	;   float(Value)
  342	->  Class = float
  343	;   Class = value
  344	).
 odd_even_row(+Row, -Next, :Content)//
Create odd/even alternating table rows from a DCG.
  350odd_even_row(Row, Next, Content) -->
  351	{ (   Row mod 2 =:= 0
  352	  ->  Class = even
  353	  ;   Class = odd
  354	  ),
  355	  Next is Row+1
  356	},
  357	html(tr(class(Class), Content))