34
35:- module(prolog_profile,
36 [ profile/1, 37 profile/2, 38 show_profile/1, 39 profile_data/1, 40 profile_procedure_data/2 41 ]). 42:- autoload(library(error),[must_be/2]). 43:- autoload(library(lists), [member/2]). 44:- autoload(library(option), [option/3]). 45:- autoload(library(pairs), [map_list_to_pairs/3, pairs_values/2]). 46:- autoload(library(prolog_code), [predicate_sort_key/2, predicate_label/2]). 47
48:- meta_predicate
49 profile(0),
50 profile(0, +),
51 profile_procedure_data(:, -). 52
53:- create_prolog_flag(profile_ports, true,
54 [ keep(true),
55 type(oneof([true,false,classic]))
56 ]). 57:- create_prolog_flag(profile_sample_rate, 200.0,
58 [ keep(true),
59 type(float)
60 ]). 61
62:- set_prolog_flag(generate_debug_info, false). 63
70
71:- multifile
72 prolog:show_profile_hook/1. 73
103
104profile(Goal) :-
105 profile(Goal, []).
106
107profile(Goal0, Options) :-
108 current_prolog_flag(profile_ports, DefPorts),
109 current_prolog_flag(profile_sample_rate, DefRate),
110 option(time(Which), Options, cpu),
111 time_name(Which, How),
112 option(ports(Ports), Options, DefPorts),
113 must_be(oneof([true,false,classic]),Ports),
114 option(sample_rate(Rate), Options, DefRate),
115 must_be(between(1.0,1000), Rate),
116 expand_goal(Goal0, Goal),
117 call_cleanup('$profile'(Goal, How, Ports, Rate),
118 prolog_statistics:show_profile(Options)).
119
120time_name(cpu, cputime) :- !.
121time_name(wall, walltime) :- !.
122time_name(cputime, cputime) :- !.
123time_name(walltime, walltime) :- !.
124time_name(Time, _) :-
125 must_be(oneof([cpu,wall]), Time).
126
136
137show_profile(N) :-
138 integer(N),
139 !,
140 show_profile([top(N)]).
141show_profile(Options) :-
142 profiler(Old, false),
143 show_profile_(Options),
144 profiler(_, Old).
145
146show_profile_(Options) :-
147 prolog:show_profile_hook(Options),
148 !.
149show_profile_(Options) :-
150 prof_statistics(Stat),
151 sort_on(Options, SortKey),
152 findall(Node, profile_procedure_data(_:_, Node), Nodes),
153 sort_prof_nodes(SortKey, Nodes, Sorted),
154 format('~`=t~69|~n'),
155 format('Total time: ~3f seconds~n', [Stat.time]),
156 format('~`=t~69|~n'),
157 format('~w~t~w =~45|~t~w~60|~t~w~69|~n',
158 [ 'Predicate', 'Box Entries', 'Calls+Redos', 'Time'
159 ]),
160 format('~`=t~69|~n'),
161 option(top(N), Options, 25),
162 show_plain(Sorted, N, Stat, SortKey).
163
164sort_on(Options, ticks_self) :-
165 option(cumulative(false), Options, false),
166 !.
167sort_on(_, ticks).
168
169sort_prof_nodes(ticks, Nodes, Sorted) :-
170 !,
171 map_list_to_pairs(key_ticks, Nodes, Keyed),
172 sort(1, >=, Keyed, KeySorted),
173 pairs_values(KeySorted, Sorted).
174sort_prof_nodes(Key, Nodes, Sorted) :-
175 sort(Key, >=, Nodes, Sorted).
176
177key_ticks(Node, Ticks) :-
178 Ticks is Node.ticks_self + Node.ticks_siblings.
179
180show_plain([], _, _, _).
181show_plain(_, 0, _, _) :- !.
182show_plain([H|T], N, Stat, Key) :-
183 show_plain(H, Stat, Key),
184 N2 is N - 1,
185 show_plain(T, N2, Stat, Key).
186
187show_plain(Node, Stat, Key) :-
188 value(label, Node, Pred),
189 value(call, Node, Call),
190 value(redo, Node, Redo),
191 value(time(Key, percentage, Stat), Node, Percent),
192 IntPercent is round(Percent*10),
193 Entry is Call + Redo,
194 format('~w~t~D =~45|~t~D+~55|~D ~t~1d%~69|~n',
195 [Pred, Entry, Call, Redo, IntPercent]).
196
197
198 201
240
241profile_data(Data) :-
242 setup_call_cleanup(
243 profiler(Old, false),
244 profile_data_(Data),
245 profiler(_, Old)).
246
247profile_data_(profile{summary:Summary, nodes:Nodes}) :-
248 prof_statistics(Summary),
249 findall(Node, profile_procedure_data(_:_, Node), Nodes).
250
256
257prof_statistics(summary{samples:Samples, ticks:Ticks,
258 accounting:Account, time:Time,
259 nodes:Nodes,
260 sample_period: Period,
261 ports: Ports
262 }) :-
263 '$prof_statistics'(Samples, Ticks, Account, Time, Nodes, Period, Ports).
264
270
271profile_procedure_data(Pred, Node) :-
272 Node = node{predicate:Pred,
273 ticks_self:TicksSelf, ticks_siblings:TicksSiblings,
274 call:Call, redo:Redo, exit:Exit,
275 callers:Parents, callees:Siblings},
276 ( specified(Pred)
277 -> true
278 ; profiled_predicates(Preds),
279 member(Pred, Preds)
280 ),
281 '$prof_procedure_data'(Pred,
282 TicksSelf, TicksSiblings,
283 Call, Redo, Exit,
284 Parents, Siblings).
285
286specified(Module:Head) :-
287 atom(Module),
288 callable(Head).
289
290profiled_predicates(Preds) :-
291 setof(Pred, prof_impl(Pred), Preds).
292
293prof_impl(Pred) :-
294 prof_node_id(Node),
295 node_id_pred(Node, Pred).
296
297prof_node_id(N) :-
298 prof_node_id_below(N, -).
299
300prof_node_id_below(N, Root) :-
301 '$prof_sibling_of'(N0, Root),
302 ( N = N0
303 ; prof_node_id_below(N, N0)
304 ).
305
306node_id_pred(Node, Pred) :-
307 '$prof_node'(Node, Pred, _Calls, _Redos, _Exits, _Recur,
308 _Ticks, _SiblingTicks).
309
313
314value(name, Data, Name) :-
315 !,
316 predicate_sort_key(Data.predicate, Name).
317value(label, Data, Label) :-
318 !,
319 predicate_label(Data.predicate, Label).
320value(ticks, Data, Ticks) :-
321 !,
322 Ticks is Data.ticks_self + Data.ticks_siblings.
323value(time(Key, percentage, Stat), Data, Percent) :-
324 !,
325 value(Key, Data, Ticks),
326 Total = Stat.ticks,
327 Account = Stat.accounting,
328 ( Total-Account > 0
329 -> Percent is 100 * (Ticks/(Total-Account))
330 ; Percent is 0.0
331 ).
332value(Name, Data, Value) :-
333 Value = Data.Name