View source with raw comments or as raw
    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_statistics,
   32	  [ rdf_call_statistics_table//0,
   33	    http_session_table//0,
   34	    http_server_statistics//0,
   35	    http_server_pool_table//0
   36	  ]).   37:- use_module(library(option)).   38:- use_module(library(pairs)).   39:- use_module(library(semweb/rdf_db)).   40:- use_module(library(http/http_session)).   41:- use_module(library(http/thread_httpd)).   42:- use_module(library(http/html_write)).   43:- use_module(library(http/html_head)).   44:- use_module(user(user_db)).   45:- use_module(components(basics)).

Server statistics components

*/

 rdf_call_statistics_table//
Display table with RDF-call statistics
   56rdf_call_statistics_table -->
   57	{ rdf_call_stats(Lookup),
   58	  (   Lookup = [rdf(_,_,_)-_|_]
   59	  ->  Cols = 3
   60	  ;   Cols = 4
   61	  )
   62	},
   63	html(table([ class(block)
   64		   ],
   65		   [ tr([ th(colspan(Cols), 'Indexed (SOPG)'),
   66			  th('Calls')
   67			]),
   68		     \lookup_statistics(Lookup, 1)
   69		   ])).
   70
   71rdf_call_stats(Lookup) :-
   72	findall(Index-Count,
   73		rdf_statistics(lookup(Index, Count)),
   74		Lookup).
   75
   76lookup_statistics([], _) -->
   77	[].
   78lookup_statistics([H|T], Row) -->
   79	odd_even_row(Row, Next, \lookup_row(H)),
   80	lookup_statistics(T, Next).
   81
   82lookup_row(rdf(S,P,O)-Count) -->
   83	html([ \i(S), \i(P), \i(O), \nc(human, Count)]).
   84lookup_row(rdf(S,P,O,G)-Count) -->
   85	html([\i(S), \i(P), \i(O), \i(G), \nc(human, Count)]).
   86
   87
   88i(I) -->
   89	html(td(class(instantiated), I)).
 http_session_table//
HTML component that writes a table of currently logged on users.
   96http_session_table -->
   97	{ findall(S, session(S), Sessions0),
   98	  sort(Sessions0, Sessions),
   99	  Sessions \== [], !
  100	},
  101	html([ table([ class(block)
  102		     ],
  103		     [ tr([th('User'), th('Real Name'),
  104			   th('On since'), th('Idle'), th('From')])
  105		     | \sessions(Sessions, 1)
  106		     ])
  107	     ]).
  108http_session_table -->
  109	html(p('No users logged in')).
 session(-Session:s(Idle,User,SessionID,Peer)) is nondet
Enumerate all current HTTP sessions.
  115session(s(Idle, User, SessionID, Peer)) :-
  116	http_current_session(SessionID, peer(Peer)),
  117	http_current_session(SessionID, idle(Idle)),
  118	(   user_property(User, session(SessionID))
  119	->  true
  120	;   User = (-)
  121	).
  122
  123sessions([], _) --> [].
  124sessions([H|T], Row) -->
  125	odd_even_row(Row, Next, \session(H)),
  126	sessions(T, Next).
  127
  128session(s(Idle, -, _SessionID, Peer)) -->
  129	html([td(-), td(-), td(-), td(\idle(Idle)), td(\ip(Peer))]).
  130session(s(Idle, User, _SessionID, Peer)) -->
  131	{  (   user_property(User, realname(RealName))
  132	   ->  true
  133	   ;   RealName = '?'
  134	   ),
  135	   (   user_property(User, connection(OnSince, _Idle))
  136	   ->  true
  137	   ;   OnSince = 0
  138	   )
  139	},
  140	html([td(User), td(RealName), td(\date(OnSince)), td(\idle(Idle)), td(\ip(Peer))]).
  141
  142idle(Time) -->
  143	{ Secs is round(Time),
  144	  Min is Secs // 60,
  145	  Sec is Secs mod 60
  146	},
  147	html('~`0t~d~2|:~`0t~d~5|'-[Min, Sec]).
  148
  149date(Date) -->
  150	{ format_time(string(S), '%+', Date)
  151	},
  152	html(S).
  153
  154ip(ip(A,B,C,D)) --> !,
  155	html('~d.~d.~d.~d'-[A,B,C,D]).
  156ip(IP) -->
  157	html('~w'-[IP]).
 http_server_statistics//
HTML component showing statistics on the HTTP server
  164http_server_statistics -->
  165	{ findall(Port-ID, http_current_worker(Port, ID), Workers),
  166	  group_pairs_by_key(Workers, Servers)
  167	},
  168	html([ table([ class(block)
  169		     ],
  170		     [ \servers_stats(Servers)
  171		     ])
  172	     ]).
  173
  174servers_stats([]) --> [].
  175servers_stats([H|T]) -->
  176	server_stats(H), servers_stats(T).
  177
  178:- if(catch(statistics(process_cputime, _),_,fail)).  179cputime(CPU) :- statistics(process_cputime, CPU).
  180:- else.  181cputime(CPU) :- statistics(cputime, CPU).
  182:- endif.  183
  184server_stats(Port-Workers) -->
  185	{ length(Workers, NWorkers),
  186	  http_server_property(Port, start_time(StartTime)),
  187	  format_time(string(ST), '%+', StartTime),
  188	  cputime(CPU)
  189	},
  190	html([ \server_stat('Port:', Port, odd),
  191	       \server_stat('Started:', ST, even),
  192	       \server_stat('Total CPU usage:', [\n('~2f',CPU), ' seconds'], odd),
  193	       \request_statistics,
  194	       \server_stat('# worker threads:', NWorkers, odd),
  195	       tr(th(colspan(6), 'Statistics by worker')),
  196	       tr([ th(rowspan(2), 'Thread'),
  197		    th(rowspan(2), 'CPU'),
  198		    th(colspan(3), 'Stack usage')
  199		  ]),
  200	       tr([ th('Local'),
  201		    th('Global'),
  202		    th('Trail')
  203		  ]),
  204	       \http_workers(Workers, odd)
  205	     ]).
  206
  207server_stat(Name, Value, OE) -->
  208	html(tr(class(OE),
  209		[ th([class(p_name), colspan(3)], Name),
  210		  td([class(value),  colspan(3)], Value)
  211		])).
  212
  213
  214:- if(source_exports(library(http/http_stream), cgi_statistics/1)).  215:- use_module(library(http/http_stream)).  216request_statistics -->
  217	{ cgi_statistics(requests(Count)),
  218	  cgi_statistics(bytes_sent(Sent))
  219	},
  220	server_stat('Requests processed:', \n(human, Count), odd),
  221	server_stat('Bytes sent:', \n(human, Sent), even).
  222:- else.  223request_statistics --> [].
  224:- endif.  225
  226
  227http_workers([], _) -->
  228	[].
  229http_workers([H|T], OE) -->
  230	{ odd_even(OE, OE2) },
  231	http_worker(H, OE),
  232	http_workers(T, OE2).
  233
  234http_worker(H, OE) -->
  235	{ thread_statistics(H, localused, LU),
  236	  thread_statistics(H, globalused, GU),
  237	  thread_statistics(H, trailused, TU),
  238	  thread_statistics(H, cputime, CPU)
  239	},
  240	html([ tr(class(OE),
  241		  [ td(H),
  242		    \nc('~3f', CPU),
  243		    \nc(human, LU),
  244		    \nc(human, GU),
  245		    \nc(human, TU)
  246		  ])
  247	     ]).
  248
  249odd_even(even, odd).
  250odd_even(odd, even).
  251
  252
  253		 /*******************************
  254		 *	      POOLS		*
  255		 *******************************/
 http_server_pool_table//
Display table with statistics on thread-pools.
  261http_server_pool_table -->
  262	{ findall(Pool, current_thread_pool(Pool), Pools),
  263	  sort(Pools, Sorted)
  264	},
  265	html(table([ id('http-server-pool'),
  266		     class(block)
  267		   ],
  268		   [ tr([th('Name'), th('Running'), th('Size'), th('Waiting'), th('Backlog')])
  269		   | \server_pools(Sorted, 1)
  270		   ])).
  271
  272server_pools([], _) --> [].
  273server_pools([H|T], Row) -->
  274	odd_even_row(Row, Next, \server_pool(H)),
  275	server_pools(T, Next).
  276
  277server_pool(Pool) -->
  278	{ findall(P, thread_pool_property(Pool, P), List),
  279	  memberchk(size(Size), List),
  280	  memberchk(running(Running), List),
  281	  memberchk(backlog(Waiting), List),
  282	  memberchk(options(Options), List),
  283	  option(backlog(MaxBackLog), Options, infinite)
  284	},
  285	html([ th(class(p_name), Pool),
  286	       \nc(human, Running),
  287	       \nc(human, Size),
  288	       \nc(human, Waiting),
  289	       \nc(human, MaxBackLog)
  290	     ])