36
37:- module(prolog_statistics,
38 [ statistics/0,
39 statistics/1, 40 thread_statistics/2, 41 time/1, 42 profile/1, 43 profile/2, 44 show_profile/1 45 ]). 46:- use_module(library(lists)). 47:- use_module(library(pairs)). 48:- use_module(library(option)). 49:- use_module(library(error)). 50:- set_prolog_flag(generate_debug_info, false). 51
52:- meta_predicate
53 time(0),
54 profile(0),
55 profile(0, +). 56
65
71
72statistics :-
73 phrase(collect_stats, Stats),
74 print_message(information, statistics(Stats)).
75
84
85statistics(Stats) :-
86 phrase(collect_stats, [CoreStats|StatList]),
87 dict_pairs(CoreStats, _, CorePairs),
88 map_list_to_pairs(dict_key, StatList, ExtraPairs),
89 append(CorePairs, ExtraPairs, Pairs),
90 dict_pairs(Stats, statistics, Pairs).
91
92dict_key(Dict, Key) :-
93 gc{type:atom} :< Dict,
94 !,
95 Key = agc.
96dict_key(Dict, Key) :-
97 gc{type:clause} :< Dict,
98 !,
99 Key = cgc.
100dict_key(Dict, Key) :-
101 is_dict(Dict, Key).
102
103collect_stats -->
104 core_statistics,
105 gc_statistics,
106 agc_statistics,
107 cgc_statistics,
108 shift_statistics,
109 thread_counts,
110 engine_counts.
111
112core_statistics -->
113 { statistics(process_cputime, Cputime),
114 statistics(process_epoch, Epoch),
115 statistics(inferences, Inferences),
116 statistics(atoms, Atoms),
117 statistics(functors, Functors),
118 statistics(predicates, Predicates),
119 statistics(modules, Modules),
120 statistics(codes, Codes),
121 thread_self(Me),
122 thread_stack_statistics(Me, Stacks)
123 },
124 [ core{ time:time{cpu:Cputime, inferences:Inferences, epoch:Epoch},
125 data:counts{atoms:Atoms, functors:Functors,
126 predicates:Predicates, modules:Modules,
127 vm_codes:Codes},
128 stacks:Stacks
129 }
130 ].
131
132:- if(\+current_predicate(thread_statistics/3)). 133thread_statistics(_Thread, Key, Value) :- 134 statistics(Key, Value).
135:- endif. 136
137thread_stack_statistics(Thread,
138 stacks{local:stack{name:local,
139 allocated:Local,
140 usage:LocalUsed},
141 global:stack{name:global,
142 allocated:Global,
143 usage:GlobalUsed},
144 trail:stack{name:trail,
145 allocated:Trail,
146 usage:TrailUsed},
147 total:stack{name:stacks,
148 limit:StackLimit,
149 allocated:StackAllocated,
150 usage:StackUsed}
151 }) :-
152 thread_statistics(Thread, trail, Trail),
153 thread_statistics(Thread, trailused, TrailUsed),
154 thread_statistics(Thread, local, Local),
155 thread_statistics(Thread, localused, LocalUsed),
156 thread_statistics(Thread, global, Global),
157 thread_statistics(Thread, globalused, GlobalUsed),
158 thread_statistics(Thread, stack_limit, StackLimit), 159 StackUsed is LocalUsed+GlobalUsed+TrailUsed,
160 StackAllocated is Local+Global+Trail.
161
162gc_statistics -->
163 { statistics(collections, Collections),
164 Collections > 0,
165 !,
166 statistics(collected, Collected),
167 statistics(gctime, GcTime)
168 },
169 [ gc{type:stack, unit:byte,
170 count:Collections, time:GcTime, gained:Collected } ].
171gc_statistics --> [].
172
173agc_statistics -->
174 { catch(statistics(agc, Agc), _, fail),
175 Agc > 0,
176 !,
177 statistics(agc_gained, Gained),
178 statistics(agc_time, Time)
179 },
180 [ gc{type:atom, unit:atom,
181 count:Agc, time:Time, gained:Gained} ].
182agc_statistics --> [].
183
184cgc_statistics -->
185 { catch(statistics(cgc, Cgc), _, fail),
186 Cgc > 0,
187 !,
188 statistics(cgc_gained, Gained),
189 statistics(cgc_time, Time)
190 },
191 [ gc{type:clause, unit:clause,
192 count:Cgc, time:Time, gained:Gained} ].
193cgc_statistics --> [].
194
195shift_statistics -->
196 { statistics(local_shifts, LS),
197 statistics(global_shifts, GS),
198 statistics(trail_shifts, TS),
199 ( LS > 0
200 ; GS > 0
201 ; TS > 0
202 ),
203 !,
204 statistics(shift_time, Time)
205 },
206 [ shift{local:LS, global:GS, trail:TS, time:Time} ].
207shift_statistics --> [].
208
209thread_counts -->
210 { current_prolog_flag(threads, true),
211 statistics(threads, Active),
212 statistics(threads_created, Created),
213 Created > 1,
214 !,
215 statistics(thread_cputime, CpuTime),
216 Finished is Created - Active
217 },
218 [ thread{count:Active, finished:Finished, time:CpuTime} ].
219thread_counts --> [].
220
221engine_counts -->
222 { current_prolog_flag(threads, true),
223 statistics(engines, Active),
224 statistics(engines_created, Created),
225 Created > 0,
226 !,
227 Finished is Created - Active
228 },
229 [ engine{count:Active, finished:Finished} ].
230engine_counts --> [].
231
232
240
241thread_statistics(Thread, Stats) :-
242 thread_property(Thread, status(Status)),
243 human_thread_id(Thread, Id),
244 ( catch(thread_stats(Thread, Stacks, Time), _, fail)
245 -> Stats = thread{id:Id,
246 status:Status,
247 time:Time,
248 stacks:Stacks}
249 ; Stats = thread{id:Thread,
250 status:Status}
251 ).
252
253human_thread_id(Thread, Id) :-
254 atom(Thread),
255 !,
256 Id = Thread.
257human_thread_id(Thread, Id) :-
258 thread_property(Thread, id(Id)).
259
260thread_stats(Thread, Stacks,
261 time{cpu:CpuTime,
262 inferences:Inferences,
263 epoch:Epoch
264 }) :-
265 thread_statistics(Thread, cputime, CpuTime),
266 thread_statistics(Thread, inferences, Inferences),
267 thread_statistics(Thread, epoch, Epoch),
268 thread_stack_statistics(Thread, Stacks).
269
270
284
285time(Goal) :-
286 time_state(State0),
287 ( call_cleanup(catch(Goal, E, (report(State0,10), throw(E))),
288 Det = true),
289 time_true(State0),
290 ( Det == true
291 -> !
292 ; true
293 )
294 ; report(State0, 11),
295 fail
296 ).
297
298report(t(OldWall, OldTime, OldInferences), Sub) :-
299 time_state(t(NewWall, NewTime, NewInferences)),
300 UsedTime is NewTime - OldTime,
301 UsedInf is NewInferences - OldInferences - Sub,
302 Wall is NewWall - OldWall,
303 ( UsedTime =:= 0
304 -> Lips = 'Infinite'
305 ; Lips is integer(UsedInf / UsedTime)
306 ),
307 print_message(information, time(UsedInf, UsedTime, Wall, Lips)).
308
309time_state(t(Wall, Time, Inferences)) :-
310 get_time(Wall),
311 statistics(cputime, Time),
312 statistics(inferences, Inferences).
313
314time_true(State0) :-
315 report(State0, 12). 316time_true(State) :-
317 get_time(Wall),
318 statistics(cputime, Time),
319 statistics(inferences, Inferences0),
320 plus(Inferences0, -3, Inferences),
321 nb_setarg(1, State, Wall),
322 nb_setarg(2, State, Time),
323 nb_setarg(3, State, Inferences),
324 fail.
325
326
327 330
338
339:- multifile
340 prolog:show_profile_hook/1. 341
354
355profile(Goal) :-
356 profile(Goal, []).
357
358profile(Goal0, Options) :-
359 option(time(Which), Options, cpu),
360 time_name(Which, How),
361 expand_goal(Goal0, Goal),
362 call_cleanup('$profile'(Goal, How),
363 prolog_statistics:show_profile(Options)).
364
365time_name(cpu, cputime) :- !.
366time_name(wall, walltime) :- !.
367time_name(cputime, cputime) :- !.
368time_name(walltime, walltime) :- !.
369time_name(Time, _) :-
370 must_be(oneof([cpu,wall]), Time).
371
381
382show_profile(N) :-
383 integer(N),
384 !,
385 show_profile([top(N)]).
386show_profile(Options) :-
387 profiler(Old, false),
388 show_profile_(Options),
389 profiler(_, Old).
390
391show_profile_(Options) :-
392 prolog:show_profile_hook(Options),
393 !.
394show_profile_(Options) :-
395 prof_statistics(Stat),
396 prof_statistics(time, Stat, Time),
397 sort_on(Options, SortKey),
398 findall(KeyedNode, prof_node(SortKey, KeyedNode), Nodes),
399 sort(1, >=, Nodes, Sorted),
400 format('~`=t~69|~n'),
401 format('Total time: ~3f seconds~n', [Time]),
402 format('~`=t~69|~n'),
403 format('~w~t~w =~45|~t~w~60|~t~w~69|~n',
404 [ 'Predicate', 'Box Entries', 'Calls+Redos', 'Time'
405 ]),
406 format('~`=t~69|~n'),
407 option(top(N), Options, 25),
408 show_plain(Sorted, N, Stat, SortKey).
409
410sort_on(Options, ticks_self) :-
411 option(cumulative(false), Options, false),
412 !.
413sort_on(_, ticks).
414
415show_plain([], _, _, _).
416show_plain(_, 0, _, _) :- !.
417show_plain([_-H|T], N, Stat, Key) :-
418 show_plain(H, Stat, Key),
419 N2 is N - 1,
420 show_plain(T, N2, Stat, Key).
421
422show_plain(Node, Stat, Key) :-
423 value(label, Node, Pred),
424 value(call, Node, Call),
425 value(redo, Node, Redo),
426 value(time(Key, percentage, Stat), Node, Percent),
427 IntPercent is round(Percent*10),
428 Entry is Call + Redo,
429 format('~w~t~D =~45|~t~D+~55|~D ~t~1d%~69|~n',
430 [Pred, Entry, Call, Redo, IntPercent]).
431
432
433 436
442
443prof_statistics(prof(Samples, Ticks, Account, Time, Nodes)) :-
444 '$prof_statistics'(Samples, Ticks, Account, Time, Nodes).
445
446prof_statistics(samples, Term, Samples) :-
447 arg(1, Term, Samples).
448prof_statistics(ticks, Term, Ticks) :-
449 arg(2, Term, Ticks).
450prof_statistics(accounting, Term, Ticks) :-
451 arg(3, Term, Ticks).
452prof_statistics(time, Term, Ticks) :-
453 arg(4, Term, Ticks).
454prof_statistics(nodes, Term, Ticks) :-
455 arg(5, Term, Ticks).
456
457
472
473prof_node(KeyOn, Node) :-
474 setup_call_cleanup(
475 ( current_prolog_flag(access_level, Old),
476 set_prolog_flag(access_level, system)
477 ),
478 get_prof_node(KeyOn, Node),
479 set_prolog_flag(access_level, Old)).
480
481get_prof_node(KeyOn, Key-Node) :-
482 Node = node(M:H,
483 TicksSelf, TicksSiblings,
484 Call, Redo,
485 Parents, Siblings),
486 current_predicate(_, M:H),
487 \+ predicate_property(M:H, imported_from(_)),
488 '$prof_procedure_data'(M:H,
489 TicksSelf, TicksSiblings,
490 Call, Redo,
491 Parents, Siblings),
492 value(KeyOn, Node, Key).
493
494key(predicate, 1).
495key(ticks_self, 2).
496key(ticks_siblings, 3).
497key(call, 4).
498key(redo, 5).
499key(callers, 6).
500key(callees, 7).
501
502value(name, Data, Name) :-
503 !,
504 arg(1, Data, Pred),
505 predicate_functor_name(Pred, Name).
506value(label, Data, Label) :-
507 !,
508 arg(1, Data, Pred),
509 predicate_label(Pred, Label).
510value(ticks, Data, Ticks) :-
511 !,
512 arg(2, Data, Self),
513 arg(3, Data, Siblings),
514 Ticks is Self + Siblings.
515value(time(Key, percentage, Stat), Data, Percent) :-
516 !,
517 value(Key, Data, Ticks),
518 prof_statistics(ticks, Stat, Total),
519 prof_statistics(accounting, Stat, Account),
520 ( Total-Account > 0
521 -> Percent is 100 * (Ticks/(Total-Account))
522 ; Percent is 0.0
523 ).
524value(Name, Data, Value) :-
525 key(Name, Arg),
526 arg(Arg, Data, Value).
527
531
532predicate_label(M:H, Label) :-
533 !,
534 functor(H, Name, Arity),
535 ( hidden_module(M, H)
536 -> atomic_list_concat([Name, /, Arity], Label)
537 ; atomic_list_concat([M, :, Name, /, Arity], Label)
538 ).
539predicate_label(H, Label) :-
540 !,
541 functor(H, Name, Arity),
542 atomic_list_concat([Name, /, Arity], Label).
543
544hidden_module(system, _).
545hidden_module(user, _).
546hidden_module(M, H) :-
547 predicate_property(system:H, imported_from(M)).
548
553
554predicate_functor_name(_:H, Name) :-
555 !,
556 predicate_functor_name(H, Name).
557predicate_functor_name(H, Name) :-
558 functor(H, Name, _Arity).
559
560
561 564
565:- multifile
566 prolog:message/3. 567
570
571prolog:message(time(UsedInf, UsedTime, Wall, Lips)) -->
572 [ '~D inferences, ~3f CPU in ~3f seconds (~w% CPU, ~w Lips)'-
573 [UsedInf, UsedTime, Wall, Perc, Lips] ],
574 { Wall > 0
575 -> Perc is round(100*UsedTime/Wall)
576 ; Perc = ?
577 }.
578prolog:message(statistics(List)) -->
579 msg_statistics(List).
580
581msg_statistics([]) --> [].
582msg_statistics([H|T]) -->
583 { is_dict(H, Tag) },
584 msg_statistics(Tag, H),
585 ( { T == [] }
586 -> []
587 ; [nl], msg_statistics(T)
588 ).
589
590msg_statistics(core, S) -->
591 { get_dict(time, S, Time),
592 get_dict(data, S, Data),
593 get_dict(stacks, S, Stacks)
594 },
595 time_stats(Time), [nl],
596 data_stats(Data), [nl,nl],
597 stacks_stats(Stacks).
598msg_statistics(gc, S) -->
599 { ( get_dict(type, S, stack)
600 -> Label = ''
601 ; get_dict(type, S, Type),
602 string_concat(Type, " ", Label)
603 ),
604 get_dict(count, S, Count),
605 get_dict(gained, S, Gained),
606 get_dict(unit, S, Unit),
607 get_dict(time, S, Time)
608 },
609 [ '~D ~wgarbage collections gained ~D ~ws in ~3f seconds.'-
610 [ Count, Label, Gained, Unit, Time]
611 ].
612msg_statistics(shift, S) -->
613 { get_dict(local, S, Local),
614 get_dict(global, S, Global),
615 get_dict(trail, S, Trail),
616 get_dict(time, S, Time)
617 },
618 [ 'Stack shifts: ~D local, ~D global, ~D trail in ~3f seconds'-
619 [ Local, Global, Trail, Time ]
620 ].
621msg_statistics(thread, S) -->
622 { get_dict(count, S, Count),
623 get_dict(finished, S, Finished),
624 get_dict(time, S, Time)
625 },
626 [ '~D threads, ~D finished threads used ~3f seconds'-
627 [Count, Finished, Time]
628 ].
629msg_statistics(engine, S) -->
630 { get_dict(count, S, Count),
631 get_dict(finished, S, Finished)
632 },
633 [ '~D engines, ~D finished engines'-
634 [Count, Finished]
635 ].
636
637time_stats(T) -->
638 { get_dict(epoch, T, Epoch),
639 format_time(string(EpochS), '%+', Epoch),
640 get_dict(cpu, T, CPU),
641 get_dict(inferences, T, Inferences)
642 },
643 [ 'Started at ~s'-[EpochS], nl,
644 '~3f seconds cpu time for ~D inferences'-
645 [ CPU, Inferences ]
646 ].
647data_stats(C) -->
648 { get_dict(atoms, C, Atoms),
649 get_dict(functors, C, Functors),
650 get_dict(predicates, C, Predicates),
651 get_dict(modules, C, Modules),
652 get_dict(vm_codes, C, VMCodes)
653 },
654 [ '~D atoms, ~D functors, ~D predicates, ~D modules, ~D VM-codes'-
655 [ Atoms, Functors, Predicates, Modules, VMCodes]
656 ].
657stacks_stats(S) -->
658 { get_dict(local, S, Local),
659 get_dict(global, S, Global),
660 get_dict(trail, S, Trail),
661 get_dict(total, S, Total)
662 },
663 [ '~|~tLimit~25+~tAllocated~12+~tIn use~12+'-[], nl ],
664 stack_stats('Local', Local), [nl],
665 stack_stats('Global', Global), [nl],
666 stack_stats('Trail', Trail), [nl],
667 stack_stats('Total', Total), [nl].
668
669stack_stats('Total', S) -->
670 { dict_human_bytes(limit, S, Limit),
671 dict_human_bytes(allocated, S, Allocated),
672 dict_human_bytes(usage, S, Usage)
673 },
674 !,
675 [ '~|~tTotal:~13+~t~s~12+ ~t~s~12+ ~t~s~12+'-
676 [Limit, Allocated, Usage]
677 ].
678stack_stats(Stack, S) -->
679 { dict_human_bytes(allocated, S, Allocated),
680 dict_human_bytes(usage, S, Usage)
681 },
682 [ '~|~w ~tstack:~13+~t~w~12+ ~t~s~12+ ~t~s~12+'-
683 [Stack, -, Allocated, Usage]
684 ].
685
686dict_human_bytes(Key, Dict, String) :-
687 get_dict(Key, Dict, Bytes),
688 human_bytes(Bytes, String).
689
690human_bytes(Bytes, String) :-
691 Bytes < 20_000,
692 !,
693 format(string(String), '~D b', [Bytes]).
694human_bytes(Bytes, String) :-
695 Bytes < 20_000_000,
696 !,
697 Kb is (Bytes+512) // 1024,
698 format(string(String), '~D Kb', [Kb]).
699human_bytes(Bytes, String) :-
700 Bytes < 20_000_000_000,
701 !,
702 Mb is (Bytes+512*1024) // (1024*1024),
703 format(string(String), '~D Mb', [Mb]).
704human_bytes(Bytes, String) :-
705 Gb is (Bytes+512*1024*1024) // (1024*1024*1024),
706 format(string(String), '~D Gb', [Gb]).
707
708
709:- multifile sandbox:safe_primitive/1. 710
711sandbox:safe_primitive(prolog_statistics:statistics(_)).
712sandbox:safe_primitive(prolog_statistics:statistics).
713sandbox:safe_meta_predicate(prolog_statistics:profile/1).
714sandbox:safe_meta_predicate(prolog_statistics:profile/2)