37
38:- module(prolog_statistics,
39 [ statistics/0,
40 statistics/1, 41 thread_statistics/2, 42 time/1, 43 call_time/2, 44 call_time/3 45 ]). 46:- autoload(library(pairs),[map_list_to_pairs/3]). 47
48:- set_prolog_flag(generate_debug_info, false). 49
50:- meta_predicate
51 time(0),
52 call_time(0, -, -),
53 call_time(0, -). 54
63
69
70statistics :-
71 phrase(collect_stats, Stats),
72 print_message(information, statistics(Stats)).
73
82
83statistics(Stats) :-
84 phrase(collect_stats, [CoreStats|StatList]),
85 dict_pairs(CoreStats, _, CorePairs),
86 map_list_to_pairs(dict_key, StatList, ExtraPairs),
87 append(CorePairs, ExtraPairs, Pairs),
88 dict_pairs(Stats, statistics, Pairs).
89
90dict_key(Dict, Key) :-
91 gc{type:atom} :< Dict,
92 !,
93 Key = agc.
94dict_key(Dict, Key) :-
95 gc{type:clause} :< Dict,
96 !,
97 Key = cgc.
98dict_key(Dict, Key) :-
99 is_dict(Dict, Key).
100
101collect_stats -->
102 core_statistics,
103 gc_statistics,
104 agc_statistics,
105 cgc_statistics,
106 shift_statistics,
107 thread_counts,
108 engine_counts.
109
110core_statistics -->
111 { statistics(process_cputime, Cputime),
112 statistics(process_epoch, Epoch),
113 statistics(inferences, Inferences),
114 statistics(atoms, Atoms),
115 statistics(functors, Functors),
116 statistics(predicates, Predicates),
117 statistics(modules, Modules),
118 statistics(codes, Codes),
119 thread_self(Me),
120 thread_stack_statistics(Me, Stacks)
121 },
122 [ core{ time:time{cpu:Cputime, inferences:Inferences, epoch:Epoch},
123 data:counts{atoms:Atoms, functors:Functors,
124 predicates:Predicates, modules:Modules,
125 vm_codes:Codes},
126 stacks:Stacks
127 }
128 ].
129
130:- if(\+current_predicate(thread_statistics/3)). 131thread_statistics(_Thread, Key, Value) :- 132 statistics(Key, Value).
133:- endif. 134
135thread_stack_statistics(Thread,
136 stacks{local:stack{name:local,
137 allocated:Local,
138 usage:LocalUsed},
139 global:stack{name:global,
140 allocated:Global,
141 usage:GlobalUsed},
142 trail:stack{name:trail,
143 allocated:Trail,
144 usage:TrailUsed},
145 total:stack{name:stacks,
146 limit:StackLimit,
147 allocated:StackAllocated,
148 usage:StackUsed}
149 }) :-
150 thread_statistics(Thread, trail, Trail),
151 thread_statistics(Thread, trailused, TrailUsed),
152 thread_statistics(Thread, local, Local),
153 thread_statistics(Thread, localused, LocalUsed),
154 thread_statistics(Thread, global, Global),
155 thread_statistics(Thread, globalused, GlobalUsed),
156 thread_statistics(Thread, stack_limit, StackLimit), 157 StackUsed is LocalUsed+GlobalUsed+TrailUsed,
158 StackAllocated is Local+Global+Trail.
159
160gc_statistics -->
161 { statistics(collections, Collections),
162 Collections > 0,
163 !,
164 statistics(collected, Collected),
165 statistics(gctime, GcTime)
166 },
167 [ gc{type:stack, unit:byte,
168 count:Collections, time:GcTime, gained:Collected } ].
169gc_statistics --> [].
170
171agc_statistics -->
172 { catch(statistics(agc, Agc), _, fail),
173 Agc > 0,
174 !,
175 statistics(agc_gained, Gained),
176 statistics(agc_time, Time)
177 },
178 [ gc{type:atom, unit:atom,
179 count:Agc, time:Time, gained:Gained} ].
180agc_statistics --> [].
181
182cgc_statistics -->
183 { catch(statistics(cgc, Cgc), _, fail),
184 Cgc > 0,
185 !,
186 statistics(cgc_gained, Gained),
187 statistics(cgc_time, Time)
188 },
189 [ gc{type:clause, unit:clause,
190 count:Cgc, time:Time, gained:Gained} ].
191cgc_statistics --> [].
192
193shift_statistics -->
194 { statistics(local_shifts, LS),
195 statistics(global_shifts, GS),
196 statistics(trail_shifts, TS),
197 ( LS > 0
198 ; GS > 0
199 ; TS > 0
200 ),
201 !,
202 statistics(shift_time, Time)
203 },
204 [ shift{local:LS, global:GS, trail:TS, time:Time} ].
205shift_statistics --> [].
206
207thread_counts -->
208 { current_prolog_flag(threads, true),
209 statistics(threads, Active),
210 statistics(threads_created, Created),
211 Created > 1,
212 !,
213 statistics(thread_cputime, CpuTime),
214 Finished is Created - Active
215 },
216 [ thread{count:Active, finished:Finished, time:CpuTime} ].
217thread_counts --> [].
218
219engine_counts -->
220 { current_prolog_flag(threads, true),
221 statistics(engines, Active),
222 statistics(engines_created, Created),
223 Created > 0,
224 !,
225 Finished is Created - Active
226 },
227 [ engine{count:Active, finished:Finished} ].
228engine_counts --> [].
229
230
238
239thread_statistics(Thread, Stats) :-
240 thread_property(Thread, status(Status)),
241 human_thread_id(Thread, Id),
242 Error = error(_,_),
243 ( catch(thread_stats(Thread, Stacks, Time), Error, fail)
244 -> Stats = thread{id:Id,
245 status:Status,
246 time:Time,
247 stacks:Stacks}
248 ; Stats = thread{id:Thread,
249 status:Status}
250 ).
251
252human_thread_id(Thread, Id) :-
253 atom(Thread),
254 !,
255 Id = Thread.
256human_thread_id(Thread, Id) :-
257 thread_property(Thread, id(Id)).
258
259thread_stats(Thread, Stacks,
260 time{cpu:CpuTime,
261 inferences:Inferences,
262 epoch:Epoch
263 }) :-
264 thread_statistics(Thread, cputime, CpuTime),
265 thread_statistics(Thread, inferences, Inferences),
266 thread_statistics(Thread, epoch, Epoch),
267 thread_stack_statistics(Thread, Stacks).
268
269
284
285time(Goal) :-
286 time_state(State0),
287 ( call_cleanup(catch(Goal, E, (report(State0,10), throw(E))),
288 Det = true),
289 time_true_report(State0),
290 ( Det == true
291 -> !
292 ; true
293 )
294 ; report(State0, 11),
295 fail
296 ).
297
323
324call_time(Goal, Time) :-
325 call_time(Goal, Time, Result),
326 call(Result).
327
328call_time(Goal, Time, Result) :-
329 time_state(State0),
330 ( call_cleanup(catch(Goal, E, true),
331 Det = true),
332 time_true_used(State0, Time),
333 ( var(E)
334 -> Result = true,
335 ( Det == true
336 -> !
337 ; true
338 )
339 ; !,
340 Result = throw(E)
341 )
342 ; time_used(State0, 11, Time),
343 Result = false
344 ).
345
346report(State0, Sub) :-
347 time_used(State0, Sub, time{wall:Wall, cpu:Time, inferences:Inferences}),
348 ( Time =:= 0
349 -> Lips = 'Infinite'
350 ; Lips is integer(Inferences/Time)
351 ),
352 print_message(information, time(Inferences, Time, Wall, Lips)).
353
354time_used(time{wall:OldWall, cpu:OldTime, inferences:OldInferences}, Sub,
355 time{wall:Wall, cpu:Time, inferences:Inferences}) :-
356 time_state(time{wall:NewWall, cpu:NewTime, inferences:NewInferences}),
357 Time is NewTime - OldTime,
358 Inferences is NewInferences - OldInferences - Sub,
359 Wall is NewWall - OldWall.
360
361time_state(time{wall:Wall, cpu:Time, inferences:Inferences}) :-
362 get_time(Wall),
363 statistics(cputime, Time),
364 statistics(inferences, Inferences).
365
366time_true_report(State) :- 367 report(State, 12).
368time_true_report(State) :-
369 time_true(State).
370
371time_true_used(State, Time) :- 372 time_used(State, 12, Time).
373time_true_used(State, _) :-
374 time_true(State).
375
376
377time_true(State) :-
378 get_time(Wall),
379 statistics(cputime, Time),
380 statistics(inferences, Inferences0),
381 Inferences is Inferences0 - 5,
382 nb_set_dict(wall, State, Wall),
383 nb_set_dict(cpu, State, Time),
384 nb_set_dict(inferences, State, Inferences),
385 fail.
386
387
388 391
392:- multifile
393 prolog:message/3. 394
397
398prolog:message(time(UsedInf, UsedTime, Wall, Lips)) -->
399 [ '~D inferences, ~3f CPU in ~3f seconds (~w% CPU, ~w Lips)'-
400 [UsedInf, UsedTime, Wall, Perc, Lips] ],
401 { Wall > 0
402 -> Perc is round(100*UsedTime/Wall)
403 ; Perc = ?
404 }.
405prolog:message(statistics(List)) -->
406 msg_statistics(List).
407
408msg_statistics([]) --> [].
409msg_statistics([H|T]) -->
410 { is_dict(H, Tag) },
411 msg_statistics(Tag, H),
412 ( { T == [] }
413 -> []
414 ; [nl], msg_statistics(T)
415 ).
416
417msg_statistics(core, S) -->
418 { get_dict(time, S, Time),
419 get_dict(data, S, Data),
420 get_dict(stacks, S, Stacks)
421 },
422 time_stats(Time), [nl],
423 data_stats(Data), [nl,nl],
424 stacks_stats(Stacks).
425msg_statistics(gc, S) -->
426 { ( get_dict(type, S, stack)
427 -> Label = ''
428 ; get_dict(type, S, Type),
429 string_concat(Type, " ", Label)
430 ),
431 get_dict(count, S, Count),
432 get_dict(gained, S, Gained),
433 get_dict(unit, S, Unit),
434 get_dict(time, S, Time)
435 },
436 [ '~D ~wgarbage collections gained ~D ~ws in ~3f seconds.'-
437 [ Count, Label, Gained, Unit, Time]
438 ].
439msg_statistics(shift, S) -->
440 { get_dict(local, S, Local),
441 get_dict(global, S, Global),
442 get_dict(trail, S, Trail),
443 get_dict(time, S, Time)
444 },
445 [ 'Stack shifts: ~D local, ~D global, ~D trail in ~3f seconds'-
446 [ Local, Global, Trail, Time ]
447 ].
448msg_statistics(thread, S) -->
449 { get_dict(count, S, Count),
450 get_dict(finished, S, Finished),
451 get_dict(time, S, Time)
452 },
453 [ '~D threads, ~D finished threads used ~3f seconds'-
454 [Count, Finished, Time]
455 ].
456msg_statistics(engine, S) -->
457 { get_dict(count, S, Count),
458 get_dict(finished, S, Finished)
459 },
460 [ '~D engines, ~D finished engines'-
461 [Count, Finished]
462 ].
463
464time_stats(T) -->
465 { get_dict(epoch, T, Epoch),
466 format_time(string(EpochS), '%+', Epoch),
467 get_dict(cpu, T, CPU),
468 get_dict(inferences, T, Inferences)
469 },
470 [ 'Started at ~s'-[EpochS], nl,
471 '~3f seconds cpu time for ~D inferences'-
472 [ CPU, Inferences ]
473 ].
474data_stats(C) -->
475 { get_dict(atoms, C, Atoms),
476 get_dict(functors, C, Functors),
477 get_dict(predicates, C, Predicates),
478 get_dict(modules, C, Modules),
479 get_dict(vm_codes, C, VMCodes)
480 },
481 [ '~D atoms, ~D functors, ~D predicates, ~D modules, ~D VM-codes'-
482 [ Atoms, Functors, Predicates, Modules, VMCodes]
483 ].
484stacks_stats(S) -->
485 { get_dict(local, S, Local),
486 get_dict(global, S, Global),
487 get_dict(trail, S, Trail),
488 get_dict(total, S, Total)
489 },
490 [ '~|~tLimit~25+~tAllocated~12+~tIn use~12+'-[], nl ],
491 stack_stats('Local', Local), [nl],
492 stack_stats('Global', Global), [nl],
493 stack_stats('Trail', Trail), [nl],
494 stack_stats('Total', Total), [nl].
495
496stack_stats('Total', S) -->
497 { dict_human_bytes(limit, S, Limit),
498 dict_human_bytes(allocated, S, Allocated),
499 dict_human_bytes(usage, S, Usage)
500 },
501 !,
502 [ '~|~tTotal:~13+~t~s~12+ ~t~s~12+ ~t~s~12+'-
503 [Limit, Allocated, Usage]
504 ].
505stack_stats(Stack, S) -->
506 { dict_human_bytes(allocated, S, Allocated),
507 dict_human_bytes(usage, S, Usage)
508 },
509 [ '~|~w ~tstack:~13+~t~w~12+ ~t~s~12+ ~t~s~12+'-
510 [Stack, -, Allocated, Usage]
511 ].
512
513dict_human_bytes(Key, Dict, String) :-
514 get_dict(Key, Dict, Bytes),
515 human_bytes(Bytes, String).
516
517human_bytes(Bytes, String) :-
518 Bytes < 20_000,
519 !,
520 format(string(String), '~D b', [Bytes]).
521human_bytes(Bytes, String) :-
522 Bytes < 20_000_000,
523 !,
524 Kb is (Bytes+512) // 1024,
525 format(string(String), '~D Kb', [Kb]).
526human_bytes(Bytes, String) :-
527 Bytes < 20_000_000_000,
528 !,
529 Mb is (Bytes+512*1024) // (1024*1024),
530 format(string(String), '~D Mb', [Mb]).
531human_bytes(Bytes, String) :-
532 Gb is (Bytes+512*1024*1024) // (1024*1024*1024),
533 format(string(String), '~D Gb', [Gb]).
534
535
536:- multifile sandbox:safe_primitive/1. 537
538sandbox:safe_primitive(prolog_statistics:statistics(_)).
539sandbox:safe_primitive(prolog_statistics:statistics).
540sandbox:safe_meta_predicate(prolog_statistics:profile/1).
541sandbox:safe_meta_predicate(prolog_statistics:profile/2)