35
36:- module(swish_debug,
37 [ pengine_stale_module/1, 38 pengine_stale_module/2, 39 stale_pengine/1, 40 swish_statistics/1, 41 start_swish_stat_collector/0,
42 swish_stats/2, 43 swish_died_thread/2 44 ]). 45:- use_module(library(pengines)). 46:- use_module(library(broadcast)). 47:- use_module(library(lists)). 48:- use_module(library(apply)). 49:- use_module(library(debug)). 50:- use_module(library(aggregate)). 51:- use_module(procps). 52:- use_module(highlight). 53:- if(exists_source(library(mallocinfo))). 54:- use_module(library(mallocinfo)). 55:- export(malloc_info/1). 56:- endif.
62stale_pengine(Pengine) :-
63 pengine_property(Pengine, thread(Thread)),
64 \+ catch(thread_property(Thread, status(running)), _, fail).
74pengine_stale_module(M) :-
75 current_module(M),
76 is_uuid(M),
77 \+ live_module(M),
78 \+ current_highlight_state(M, _).
79
80pengine_stale_module(M, State) :-
81 pengine_stale_module(M),
82 stale_module_state(M, State).
83
84live_module(M) :-
85 pengine_property(Pengine, module(M)),
86 pengine_property(Pengine, thread(Thread)),
87 catch(thread_property(Thread, status(running)), _, fail).
88
89stale_module_state(M, State) :-
90 findall(N-V, stale_module_property(M, N, V), Properties),
91 dict_create(State, stale, Properties).
92
93stale_module_property(M, pengine, Pengine) :-
94 pengine_property(Pengine, module(M)).
95stale_module_property(M, pengine_queue, Queue) :-
96 pengine_property(Pengine, module(M)),
97 member(G, pengines:pengine_queue(Pengine, Queue, _TimeOut, _Time)),
98 call(G). 99stale_module_property(M, pengine_pending_queue, Queue) :-
100 pengine_property(Pengine, module(M)),
101 member(G, [pengines:output_queue(Pengine, Queue, _Time)]),
102 call(G). 103stale_module_property(M, thread, Thread) :-
104 pengine_property(Pengine, module(M)),
105 member(G, [pengines:pengine_property(Pengine, thread(Thread))]),
106 call(G). 107stale_module_property(M, thread_status, Status) :-
108 pengine_property(Pengine, module(M)),
109 pengine_property(Pengine, thread(Thread)),
110 catch(thread_property(Thread, status(Status)), _, fail).
111stale_module_property(M, module_class, Class) :-
112 module_property(M, class(Class)).
113stale_module_property(M, program_space, Space) :-
114 module_property(M, program_space(Space)).
115stale_module_property(M, program_size, Size) :-
116 module_property(M, program_size(Size)).
117stale_module_property(M, predicates, List) :-
118 current_module(M),
119 findall(PI, pi_in_module(M, PI), List).
120stale_module_property(UUID, highlight_state, State) :-
121 current_highlight_state(UUID, State).
122
123pi_in_module(M, Name/Arity) :-
124 '$c_current_predicate'(_, M:Head),
125 functor(Head, Name, Arity).
131swish_statistics(highlight_states(Count)) :-
132 aggregate_all(count, current_highlight_state(_,_), Count).
133swish_statistics(pengines(Count)) :-
134 aggregate_all(count, pengine_property(_,thread(_)), Count).
135swish_statistics(remote_pengines(Count)) :-
136 aggregate_all(count, pengine_property(_,remote(_)), Count).
137swish_statistics(pengines_created(Count)) :-
138 ( flag(pengines_created, Old, Old)
139 -> Count = Old
140 ; Count = 0
141 ).
142
143:- listen(pengine(Action), swish_update_stats(Action)). 144
145swish_update_stats(create(_Pengine, _Application, _Options0)) :-
146 flag(pengines_created, Old, Old+1).
147swish_update_stats(send(_Pengine, _Event)).
154is_uuid(M) :-
155 atom(M),
156 atom_length(M, 36),
157 forall(sub_atom(M, S, 1, _, C),
158 uuid_code(S, C)).
159
160uuid_sep(8).
161uuid_sep(13).
162uuid_sep(18).
163uuid_sep(23).
164
165uuid_code(S, -) :- !, uuid_sep(S).
166uuid_code(_, X) :- char_type(X, xdigit(_)).
167
168 171
172:- if(current_predicate(http_unix_daemon:http_daemon/0)). 173:- use_module(library(broadcast)). 174:- listen(http(post_server_start), start_swish_stat_collector). 175:- else. 176:- initialization
177 start_swish_stat_collector. 178:- endif.
185start_swish_stat_collector :-
186 thread_property(_, alias(swish_stats)), !.
187start_swish_stat_collector :-
188 swish_stat_collector(swish_stats,
189 [ 60, 190 60, 191 24, 192 7, 193 52 194 ],
195 1).
196
197swish_stat_collector(Name, Dims, Interval) :-
198 atom(Name), !,
199 thread_create(stat_collect(Dims, Interval), _, [alias(Name)]).
200swish_stat_collector(Thread, Dims, Interval) :-
201 thread_create(stat_collect(Dims, Interval), Thread, []).
226swish_stats(Name, Stats) :-
227 stats_ring(Name, Ring),
228 swish_stats(swish_stats, Ring, Stats).
229
230stats_ring(minute, 1).
231stats_ring(hour, 2).
232stats_ring(day, 3).
233stats_ring(week, 4).
234stats_ring(year, 5).
235
236swish_stats(Name, Ring, Stats) :-
237 thread_self(Me),
238 catch(thread_send_message(Name, Me-get_stats(Ring)), E,
239 stats_died(Name, E)),
240 thread_get_message(get_stats(Ring, Stats)).
241
242stats_died(Alias, E) :-
243 print_message(error, E),
244 thread_join(Alias, Status),
245 print_message(error, swish_stats(died, Status)),
246 start_swish_stat_collector,
247 fail.
248
249stat_collect(Dims, Interval) :-
250 new_sliding_stats(Dims, SlidingStat),
251 get_time(Now),
252 ITime is floor(Now),
253 stat_loop(SlidingStat, _{}, ITime, Interval, [true]).
254
255stat_loop(SlidingStat, Stat0, StatTime, Interval, Wrap) :-
256 ( thread_self(Me),
257 thread_get_message(Me, Request,
258 [ deadline(StatTime)
259 ])
260 -> ( reply_stats_request(Request, SlidingStat)
261 -> true
262 ; debug(swish_stats, 'Failed to process ~p', [Request])
263 ),
264 stat_loop(SlidingStat, Stat0, StatTime, Interval, Wrap)
265 ; get_stats(Wrap, Stat1),
266 dif_stat(Stat1, Stat0, Stat),
267 push_sliding_stats(SlidingStat, Stat, Wrap1),
268 NextTime is StatTime+Interval,
269 stat_loop(SlidingStat, Stat1, NextTime, Interval, Wrap1)
270 ).
271
272dif_stat(Stat1, Stat0, Stat) :-
273 maplist(dif_field(Stat1, Stat0),
274 [ cpu - d_cpu,
275 pengines_created - d_pengines_created
276 ],
277 Fields), !,
278 dict_pairs(Extra, _, Fields),
279 put_dict(Extra, Stat1, Stat).
280dif_stat(Stat, _, Stat).
281
282dif_field(Stat1, Stat0, Key-DKey, DKey-DValue) :-
283 DValue is Stat1.get(Key) - Stat0.get(Key).
284
285reply_stats_request(Client-get_stats(Period), SlidingStat) :-
286 arg(Period, SlidingStat, Ring),
287 ring_values(Ring, Values),
288 thread_send_message(Client, get_stats(Period, Values)).
294get_stats(Wrap, Stats) :-
295 Stats0 = stats{ cpu:CPU,
296 rss:RSS,
297 stack:Stack,
298 pengines:Pengines,
299 threads:Threads,
300 pengines_created:PenginesCreated,
301 time:Time
302 },
303 get_time(Now),
304 Time is floor(Now),
305 statistics(process_cputime, PCPU),
306 statistics(cputime, MyCPU),
307 CPU is PCPU-MyCPU,
308 statistics(stack, Stack),
309 statistics(threads, Threads),
310 catch(procps_stat(Stat), _,
311 Stat = stat{rss:0}),
312 RSS = Stat.rss,
313 swish_statistics(pengines(Pengines)),
314 swish_statistics(pengines_created(PenginesCreated)),
315 add_fordblks(Wrap, Stats0, Stats1),
316 add_visitors(Stats1, Stats).
317
318:- if(current_predicate(mallinfo/1)). 319add_fordblks(Wrap, Stats0, Stats) :-
320 ( Wrap = [true|_]
321 -> member(G, [mallinfo(MallInfo)]),
322 call(G), 323 FordBlks = MallInfo.get(fordblks),
324 b_setval(fordblks, FordBlks)
325 ; nb_current(fordblks, FordBlks)
326 ), !,
327 Stats = Stats0.put(fordblks, FordBlks).
328:- endif. 329add_fordblks(_, Stats, Stats).
330
331add_visitors(Stats0, Stats) :-
332 broadcast_request(swish(visitor_count(C))), !,
333 Stats = Stats0.put(visitors, C).
334add_visitors(Stats, Stats).
335
336
341
342new_sliding_stats(Dims, Stats) :-
343 maplist(new_ring, Dims, Rings),
344 compound_name_arguments(Stats, sliding_stats, Rings).
345
346push_sliding_stats(Stats, Values, Wrap) :-
347 push_sliding_stats(1, Stats, Values, Wrap).
348
349push_sliding_stats(I, Stats, Values, [Wrap|WrapT]) :-
350 arg(I, Stats, Ring),
351 push_ring(Ring, Values, Wrap),
352 ( Wrap == true
353 -> average_ring(Ring, Avg),
354 I2 is I+1,
355 ( push_sliding_stats(I2, Stats, Avg, WrapT)
356 -> true
357 ; true
358 )
359 ; WrapT = []
360 ).
361
362new_ring(Dim, ring(0, Ring)) :-
363 compound_name_arity(Ring, [], Dim).
364
365push_ring(Ring, Value, Wrap) :-
366 Ring = ring(Here0, Data),
367 Here is Here0+1,
368 compound_name_arity(Data, _, Size),
369 Arg is (Here0 mod Size)+1,
370 ( Arg == Size
371 -> Wrap = true
372 ; Wrap = false
373 ),
374 nb_setarg(Arg, Data, Value),
375 nb_setarg(1, Ring, Here).
376
377ring_values(Ring, Values) :-
378 Ring = ring(Here, Data),
379 compound_name_arity(Data, _, Size),
380 Start is Here - 1,
381 End is Start - min(Here,Size),
382 read_ring(Start, End, Size, Data, Values).
383
384read_ring(End, End, _, _, []) :- !.
385read_ring(Here0, End, Size, Data, [H|T]) :-
386 A is (Here0 mod Size)+1,
387 arg(A, Data, H),
388 Here1 is Here0-1,
389 read_ring(Here1, End, Size, Data, T).
390
391average_ring(ring(_,Data), Avg) :-
392 compound_name_arguments(Data, _, Dicts),
393 average_dicts(Dicts, Avg).
394
395average_dicts(Dicts, Avg) :-
396 dicts_to_same_keys(Dicts, dict_fill(0), Dicts1),
397 Dicts1 = [H|_],
398 is_dict(H, Tag),
399 dict_keys(H, Keys),
400 length(Dicts1, Len),
401 maplist(avg_key(Dicts1, Len), Keys, Pairs),
402 dict_pairs(Avg, Tag, Pairs).
403
404avg_key(Dicts, Len, Key, Key-Avg) :-
405 maplist(get_dict(Key), Dicts, Values),
406 sum_list(Values, Sum),
407 Avg is Sum/Len.
415swish_died_thread(TID, Status) :-
416 findall(TID-Stat, (thread_property(Thread, status(Stat)),
417 Stat \== running,
418 thread_property(Thread, id(TID))), Pairs),
419 member(TID-Stat, Pairs),
420 status_message(Stat, Status).
421
422status_message(exception(Ex), Message) :- !,
423 message_to_string(Ex, Message0),
424 string_concat('ERROR: ', Message0, Message).
425status_message(Status, Status).
426
427
428 431
432:- multifile
433 sandbox:safe_primitive/1. 434
435sandbox:safe_primitive(swish_debug:pengine_stale_module(_)).
436sandbox:safe_primitive(swish_debug:pengine_stale_module(_,_)).
437sandbox:safe_primitive(swish_debug:stale_pengine(_)).
438sandbox:safe_primitive(swish_debug:swish_statistics(_)).
439sandbox:safe_primitive(swish_debug:swish_stats(_, _)).
440sandbox:safe_primitive(swish_debug:swish_died_thread(_, _)).
441:- if(current_predicate(malloc_info:malloc_info/1)). 442sandbox:safe_primitive(malloc_info:malloc_info(_)).
443:- endif.