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 profile/1, 46 profile/2, 47 show_profile/1, 48 profile_data/1, 49 profile_procedure_data/2 50 ]). 51:- autoload(library(error),[must_be/2]). 52:- autoload(library(lists),[append/3,member/2]). 53:- autoload(library(option),[option/3]). 54:- autoload(library(pairs),[map_list_to_pairs/3,pairs_values/2]). 55:- autoload(library(prolog_code),
56 [predicate_sort_key/2,predicate_label/2]). 57
58:- set_prolog_flag(generate_debug_info, false). 59
60:- meta_predicate
61 time(0),
62 call_time(0, -, -),
63 call_time(0, -),
64 profile(0),
65 profile(0, +),
66 profile_procedure_data(:, -). 67
76
82
83statistics :-
84 phrase(collect_stats, Stats),
85 print_message(information, statistics(Stats)).
86
95
96statistics(Stats) :-
97 phrase(collect_stats, [CoreStats|StatList]),
98 dict_pairs(CoreStats, _, CorePairs),
99 map_list_to_pairs(dict_key, StatList, ExtraPairs),
100 append(CorePairs, ExtraPairs, Pairs),
101 dict_pairs(Stats, statistics, Pairs).
102
103dict_key(Dict, Key) :-
104 gc{type:atom} :< Dict,
105 !,
106 Key = agc.
107dict_key(Dict, Key) :-
108 gc{type:clause} :< Dict,
109 !,
110 Key = cgc.
111dict_key(Dict, Key) :-
112 is_dict(Dict, Key).
113
114collect_stats -->
115 core_statistics,
116 gc_statistics,
117 agc_statistics,
118 cgc_statistics,
119 shift_statistics,
120 thread_counts,
121 engine_counts.
122
123core_statistics -->
124 { statistics(process_cputime, Cputime),
125 statistics(process_epoch, Epoch),
126 statistics(inferences, Inferences),
127 statistics(atoms, Atoms),
128 statistics(functors, Functors),
129 statistics(predicates, Predicates),
130 statistics(modules, Modules),
131 statistics(codes, Codes),
132 thread_self(Me),
133 thread_stack_statistics(Me, Stacks)
134 },
135 [ core{ time:time{cpu:Cputime, inferences:Inferences, epoch:Epoch},
136 data:counts{atoms:Atoms, functors:Functors,
137 predicates:Predicates, modules:Modules,
138 vm_codes:Codes},
139 stacks:Stacks
140 }
141 ].
142
143:- if(\+current_predicate(thread_statistics/3)). 144thread_statistics(_Thread, Key, Value) :- 145 statistics(Key, Value).
146:- endif. 147
148thread_stack_statistics(Thread,
149 stacks{local:stack{name:local,
150 allocated:Local,
151 usage:LocalUsed},
152 global:stack{name:global,
153 allocated:Global,
154 usage:GlobalUsed},
155 trail:stack{name:trail,
156 allocated:Trail,
157 usage:TrailUsed},
158 total:stack{name:stacks,
159 limit:StackLimit,
160 allocated:StackAllocated,
161 usage:StackUsed}
162 }) :-
163 thread_statistics(Thread, trail, Trail),
164 thread_statistics(Thread, trailused, TrailUsed),
165 thread_statistics(Thread, local, Local),
166 thread_statistics(Thread, localused, LocalUsed),
167 thread_statistics(Thread, global, Global),
168 thread_statistics(Thread, globalused, GlobalUsed),
169 thread_statistics(Thread, stack_limit, StackLimit), 170 StackUsed is LocalUsed+GlobalUsed+TrailUsed,
171 StackAllocated is Local+Global+Trail.
172
173gc_statistics -->
174 { statistics(collections, Collections),
175 Collections > 0,
176 !,
177 statistics(collected, Collected),
178 statistics(gctime, GcTime)
179 },
180 [ gc{type:stack, unit:byte,
181 count:Collections, time:GcTime, gained:Collected } ].
182gc_statistics --> [].
183
184agc_statistics -->
185 { catch(statistics(agc, Agc), _, fail),
186 Agc > 0,
187 !,
188 statistics(agc_gained, Gained),
189 statistics(agc_time, Time)
190 },
191 [ gc{type:atom, unit:atom,
192 count:Agc, time:Time, gained:Gained} ].
193agc_statistics --> [].
194
195cgc_statistics -->
196 { catch(statistics(cgc, Cgc), _, fail),
197 Cgc > 0,
198 !,
199 statistics(cgc_gained, Gained),
200 statistics(cgc_time, Time)
201 },
202 [ gc{type:clause, unit:clause,
203 count:Cgc, time:Time, gained:Gained} ].
204cgc_statistics --> [].
205
206shift_statistics -->
207 { statistics(local_shifts, LS),
208 statistics(global_shifts, GS),
209 statistics(trail_shifts, TS),
210 ( LS > 0
211 ; GS > 0
212 ; TS > 0
213 ),
214 !,
215 statistics(shift_time, Time)
216 },
217 [ shift{local:LS, global:GS, trail:TS, time:Time} ].
218shift_statistics --> [].
219
220thread_counts -->
221 { current_prolog_flag(threads, true),
222 statistics(threads, Active),
223 statistics(threads_created, Created),
224 Created > 1,
225 !,
226 statistics(thread_cputime, CpuTime),
227 Finished is Created - Active
228 },
229 [ thread{count:Active, finished:Finished, time:CpuTime} ].
230thread_counts --> [].
231
232engine_counts -->
233 { current_prolog_flag(threads, true),
234 statistics(engines, Active),
235 statistics(engines_created, Created),
236 Created > 0,
237 !,
238 Finished is Created - Active
239 },
240 [ engine{count:Active, finished:Finished} ].
241engine_counts --> [].
242
243
251
252thread_statistics(Thread, Stats) :-
253 thread_property(Thread, status(Status)),
254 human_thread_id(Thread, Id),
255 Error = error(_,_),
256 ( catch(thread_stats(Thread, Stacks, Time), Error, fail)
257 -> Stats = thread{id:Id,
258 status:Status,
259 time:Time,
260 stacks:Stacks}
261 ; Stats = thread{id:Thread,
262 status:Status}
263 ).
264
265human_thread_id(Thread, Id) :-
266 atom(Thread),
267 !,
268 Id = Thread.
269human_thread_id(Thread, Id) :-
270 thread_property(Thread, id(Id)).
271
272thread_stats(Thread, Stacks,
273 time{cpu:CpuTime,
274 inferences:Inferences,
275 epoch:Epoch
276 }) :-
277 thread_statistics(Thread, cputime, CpuTime),
278 thread_statistics(Thread, inferences, Inferences),
279 thread_statistics(Thread, epoch, Epoch),
280 thread_stack_statistics(Thread, Stacks).
281
282
297
298time(Goal) :-
299 time_state(State0),
300 ( call_cleanup(catch(Goal, E, (report(State0,10), throw(E))),
301 Det = true),
302 time_true_report(State0),
303 ( Det == true
304 -> !
305 ; true
306 )
307 ; report(State0, 11),
308 fail
309 ).
310
324
325call_time(Goal, Time) :-
326 call_time(Goal, Time, true).
327call_time(Goal, Time, Result) :-
328 time_state(State0),
329 ( call_cleanup(catch(Goal, E, (report(State0,10), throw(E))),
330 Det = true),
331 Result = true,
332 time_true_used(State0, Time),
333 ( Det == true
334 -> !
335 ; true
336 )
337 ; time_used(State0, 11, Time),
338 Result = false
339 ).
340
341report(State0, Sub) :-
342 time_used(State0, Sub, time{wall:Wall, cpu:Time, inferences:Inferences}),
343 ( Time =:= 0
344 -> Lips = 'Infinite'
345 ; Lips is integer(Inferences/Time)
346 ),
347 print_message(information, time(Inferences, Time, Wall, Lips)).
348
349time_used(time{wall:OldWall, cpu:OldTime, inferences:OldInferences}, Sub,
350 time{wall:Wall, cpu:Time, inferences:Inferences}) :-
351 time_state(time{wall:NewWall, cpu:NewTime, inferences:NewInferences}),
352 Time is NewTime - OldTime,
353 Inferences is NewInferences - OldInferences - Sub,
354 Wall is NewWall - OldWall.
355
356time_state(time{wall:Wall, cpu:Time, inferences:Inferences}) :-
357 get_time(Wall),
358 statistics(cputime, Time),
359 statistics(inferences, Inferences).
360
361time_true_report(State) :- 362 report(State, 12).
363time_true_report(State) :-
364 time_true(State).
365
366time_true_used(State, Time) :- 367 time_used(State, 12, Time).
368time_true_used(State, _) :-
369 time_true(State).
370
371
372time_true(State) :-
373 get_time(Wall),
374 statistics(cputime, Time),
375 statistics(inferences, Inferences0),
376 Inferences is Inferences0 - 5,
377 nb_set_dict(wall, State, Wall),
378 nb_set_dict(cpu, State, Time),
379 nb_set_dict(inferences, State, Inferences),
380 fail.
381
382
383 386
394
395:- multifile
396 prolog:show_profile_hook/1. 397
410
411profile(Goal) :-
412 profile(Goal, []).
413
414profile(Goal0, Options) :-
415 option(time(Which), Options, cpu),
416 time_name(Which, How),
417 expand_goal(Goal0, Goal),
418 call_cleanup('$profile'(Goal, How),
419 prolog_statistics:show_profile(Options)).
420
421time_name(cpu, cputime) :- !.
422time_name(wall, walltime) :- !.
423time_name(cputime, cputime) :- !.
424time_name(walltime, walltime) :- !.
425time_name(Time, _) :-
426 must_be(oneof([cpu,wall]), Time).
427
437
438show_profile(N) :-
439 integer(N),
440 !,
441 show_profile([top(N)]).
442show_profile(Options) :-
443 profiler(Old, false),
444 show_profile_(Options),
445 profiler(_, Old).
446
447show_profile_(Options) :-
448 prolog:show_profile_hook(Options),
449 !.
450show_profile_(Options) :-
451 prof_statistics(Stat),
452 sort_on(Options, SortKey),
453 findall(Node, profile_procedure_data(_:_, Node), Nodes),
454 sort_prof_nodes(SortKey, Nodes, Sorted),
455 format('~`=t~69|~n'),
456 format('Total time: ~3f seconds~n', [Stat.time]),
457 format('~`=t~69|~n'),
458 format('~w~t~w =~45|~t~w~60|~t~w~69|~n',
459 [ 'Predicate', 'Box Entries', 'Calls+Redos', 'Time'
460 ]),
461 format('~`=t~69|~n'),
462 option(top(N), Options, 25),
463 show_plain(Sorted, N, Stat, SortKey).
464
465sort_on(Options, ticks_self) :-
466 option(cumulative(false), Options, false),
467 !.
468sort_on(_, ticks).
469
470sort_prof_nodes(ticks, Nodes, Sorted) :-
471 !,
472 map_list_to_pairs(key_ticks, Nodes, Keyed),
473 sort(1, >=, Keyed, KeySorted),
474 pairs_values(KeySorted, Sorted).
475sort_prof_nodes(Key, Nodes, Sorted) :-
476 sort(Key, >=, Nodes, Sorted).
477
478key_ticks(Node, Ticks) :-
479 Ticks is Node.ticks_self + Node.ticks_siblings.
480
481show_plain([], _, _, _).
482show_plain(_, 0, _, _) :- !.
483show_plain([H|T], N, Stat, Key) :-
484 show_plain(H, Stat, Key),
485 N2 is N - 1,
486 show_plain(T, N2, Stat, Key).
487
488show_plain(Node, Stat, Key) :-
489 value(label, Node, Pred),
490 value(call, Node, Call),
491 value(redo, Node, Redo),
492 value(time(Key, percentage, Stat), Node, Percent),
493 IntPercent is round(Percent*10),
494 Entry is Call + Redo,
495 format('~w~t~D =~45|~t~D+~55|~D ~t~1d%~69|~n',
496 [Pred, Entry, Call, Redo, IntPercent]).
497
498
499 502
537
538profile_data(Data) :-
539 setup_call_cleanup(
540 profiler(Old, false),
541 profile_data_(Data),
542 profiler(_, Old)).
543
544profile_data_(profile{summary:Summary, nodes:Nodes}) :-
545 prof_statistics(Summary),
546 findall(Node, profile_procedure_data(_:_, Node), Nodes).
547
553
554prof_statistics(summary{samples:Samples, ticks:Ticks,
555 accounting:Account, time:Time, nodes:Nodes}) :-
556 '$prof_statistics'(Samples, Ticks, Account, Time, Nodes).
557
563
564profile_procedure_data(Pred, Node) :-
565 Node = node{predicate:Pred,
566 ticks_self:TicksSelf, ticks_siblings:TicksSiblings,
567 call:Call, redo:Redo, exit:Exit,
568 callers:Parents, callees:Siblings},
569 ( specified(Pred)
570 -> true
571 ; profiled_predicates(Preds),
572 member(Pred, Preds)
573 ),
574 '$prof_procedure_data'(Pred,
575 TicksSelf, TicksSiblings,
576 Call, Redo, Exit,
577 Parents, Siblings).
578
579specified(Module:Head) :-
580 atom(Module),
581 callable(Head).
582
583profiled_predicates(Preds) :-
584 setof(Pred, prof_impl(Pred), Preds).
585
586prof_impl(Pred) :-
587 prof_node_id(Node),
588 node_id_pred(Node, Pred).
589
590prof_node_id(N) :-
591 prof_node_id_below(N, -).
592
593prof_node_id_below(N, Root) :-
594 '$prof_sibling_of'(N0, Root),
595 ( N = N0
596 ; prof_node_id_below(N, N0)
597 ).
598
599node_id_pred(Node, Pred) :-
600 '$prof_node'(Node, Pred, _Calls, _Redos, _Exits, _Recur,
601 _Ticks, _SiblingTicks).
602
606
607value(name, Data, Name) :-
608 !,
609 predicate_sort_key(Data.predicate, Name).
610value(label, Data, Label) :-
611 !,
612 predicate_label(Data.predicate, Label).
613value(ticks, Data, Ticks) :-
614 !,
615 Ticks is Data.ticks_self + Data.ticks_siblings.
616value(time(Key, percentage, Stat), Data, Percent) :-
617 !,
618 value(Key, Data, Ticks),
619 Total = Stat.ticks,
620 Account = Stat.accounting,
621 ( Total-Account > 0
622 -> Percent is 100 * (Ticks/(Total-Account))
623 ; Percent is 0.0
624 ).
625value(Name, Data, Value) :-
626 Value = Data.Name.
627
628
629 632
633:- multifile
634 prolog:message/3. 635
638
639prolog:message(time(UsedInf, UsedTime, Wall, Lips)) -->
640 [ '~D inferences, ~3f CPU in ~3f seconds (~w% CPU, ~w Lips)'-
641 [UsedInf, UsedTime, Wall, Perc, Lips] ],
642 { Wall > 0
643 -> Perc is round(100*UsedTime/Wall)
644 ; Perc = ?
645 }.
646prolog:message(statistics(List)) -->
647 msg_statistics(List).
648
649msg_statistics([]) --> [].
650msg_statistics([H|T]) -->
651 { is_dict(H, Tag) },
652 msg_statistics(Tag, H),
653 ( { T == [] }
654 -> []
655 ; [nl], msg_statistics(T)
656 ).
657
658msg_statistics(core, S) -->
659 { get_dict(time, S, Time),
660 get_dict(data, S, Data),
661 get_dict(stacks, S, Stacks)
662 },
663 time_stats(Time), [nl],
664 data_stats(Data), [nl,nl],
665 stacks_stats(Stacks).
666msg_statistics(gc, S) -->
667 { ( get_dict(type, S, stack)
668 -> Label = ''
669 ; get_dict(type, S, Type),
670 string_concat(Type, " ", Label)
671 ),
672 get_dict(count, S, Count),
673 get_dict(gained, S, Gained),
674 get_dict(unit, S, Unit),
675 get_dict(time, S, Time)
676 },
677 [ '~D ~wgarbage collections gained ~D ~ws in ~3f seconds.'-
678 [ Count, Label, Gained, Unit, Time]
679 ].
680msg_statistics(shift, S) -->
681 { get_dict(local, S, Local),
682 get_dict(global, S, Global),
683 get_dict(trail, S, Trail),
684 get_dict(time, S, Time)
685 },
686 [ 'Stack shifts: ~D local, ~D global, ~D trail in ~3f seconds'-
687 [ Local, Global, Trail, Time ]
688 ].
689msg_statistics(thread, S) -->
690 { get_dict(count, S, Count),
691 get_dict(finished, S, Finished),
692 get_dict(time, S, Time)
693 },
694 [ '~D threads, ~D finished threads used ~3f seconds'-
695 [Count, Finished, Time]
696 ].
697msg_statistics(engine, S) -->
698 { get_dict(count, S, Count),
699 get_dict(finished, S, Finished)
700 },
701 [ '~D engines, ~D finished engines'-
702 [Count, Finished]
703 ].
704
705time_stats(T) -->
706 { get_dict(epoch, T, Epoch),
707 format_time(string(EpochS), '%+', Epoch),
708 get_dict(cpu, T, CPU),
709 get_dict(inferences, T, Inferences)
710 },
711 [ 'Started at ~s'-[EpochS], nl,
712 '~3f seconds cpu time for ~D inferences'-
713 [ CPU, Inferences ]
714 ].
715data_stats(C) -->
716 { get_dict(atoms, C, Atoms),
717 get_dict(functors, C, Functors),
718 get_dict(predicates, C, Predicates),
719 get_dict(modules, C, Modules),
720 get_dict(vm_codes, C, VMCodes)
721 },
722 [ '~D atoms, ~D functors, ~D predicates, ~D modules, ~D VM-codes'-
723 [ Atoms, Functors, Predicates, Modules, VMCodes]
724 ].
725stacks_stats(S) -->
726 { get_dict(local, S, Local),
727 get_dict(global, S, Global),
728 get_dict(trail, S, Trail),
729 get_dict(total, S, Total)
730 },
731 [ '~|~tLimit~25+~tAllocated~12+~tIn use~12+'-[], nl ],
732 stack_stats('Local', Local), [nl],
733 stack_stats('Global', Global), [nl],
734 stack_stats('Trail', Trail), [nl],
735 stack_stats('Total', Total), [nl].
736
737stack_stats('Total', S) -->
738 { dict_human_bytes(limit, S, Limit),
739 dict_human_bytes(allocated, S, Allocated),
740 dict_human_bytes(usage, S, Usage)
741 },
742 !,
743 [ '~|~tTotal:~13+~t~s~12+ ~t~s~12+ ~t~s~12+'-
744 [Limit, Allocated, Usage]
745 ].
746stack_stats(Stack, S) -->
747 { dict_human_bytes(allocated, S, Allocated),
748 dict_human_bytes(usage, S, Usage)
749 },
750 [ '~|~w ~tstack:~13+~t~w~12+ ~t~s~12+ ~t~s~12+'-
751 [Stack, -, Allocated, Usage]
752 ].
753
754dict_human_bytes(Key, Dict, String) :-
755 get_dict(Key, Dict, Bytes),
756 human_bytes(Bytes, String).
757
758human_bytes(Bytes, String) :-
759 Bytes < 20_000,
760 !,
761 format(string(String), '~D b', [Bytes]).
762human_bytes(Bytes, String) :-
763 Bytes < 20_000_000,
764 !,
765 Kb is (Bytes+512) // 1024,
766 format(string(String), '~D Kb', [Kb]).
767human_bytes(Bytes, String) :-
768 Bytes < 20_000_000_000,
769 !,
770 Mb is (Bytes+512*1024) // (1024*1024),
771 format(string(String), '~D Mb', [Mb]).
772human_bytes(Bytes, String) :-
773 Gb is (Bytes+512*1024*1024) // (1024*1024*1024),
774 format(string(String), '~D Gb', [Gb]).
775
776
777:- multifile sandbox:safe_primitive/1. 778
779sandbox:safe_primitive(prolog_statistics:statistics(_)).
780sandbox:safe_primitive(prolog_statistics:statistics).
781sandbox:safe_meta_predicate(prolog_statistics:profile/1).
782sandbox:safe_meta_predicate(prolog_statistics:profile/2)