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 NetTicks is Stat.ticks-Stat.accounting,
152 NetTime is (NetTicks/Stat.ticks)*Stat.time,
153 Ports = Stat.ports,
154 findall(Node, profile_procedure_data(_:_, Node), Nodes),
155 ( option(cumulative(false), Options, false)
156 -> SortKey = ticks_self
157 ; SortKey = ticks
158 ),
159 sort_prof_nodes(SortKey, Nodes, Sorted),
160 format_divider,
161 format('Number of nodes: ~w~t[ports(~w)]~55|~tTotal time: ~3f seconds~101|~n',
162 [Stat.nodes, Ports, NetTime]),
163 format('Predicate~tCalls +~41| Redos~t~49|~t \c
164 Exits +~58| Fails~tTime:Self +~87| Time:Children~n', []),
165 format_divider,
166 option(top(N), Options, 25),
167 show_plain(Sorted, N, (NetTicks,NetTime,Ports)).
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 value(ticks,Node,Ticks).
179
180show_plain([], _, _) :- format_divider.
181show_plain([H|T], N, Stat) :-
182 show_plain(H, Stat),
183 N2 is N - 1,
184 ( N2 > 0
185 -> show_plain(T, N2, Stat)
186 ; format_divider
187 ).
188
189show_plain(Node, (NetTicks,NetTime,Ports)) :-
190 value(label, Node, Pred),
191 value(call, Node, Call),
192 ( Ports == false
193 -> Redo = 0, Exit = 0, Fail = 0
194 ; value(redo, Node, Redo),
195 value(exit, Node, Exit),
196 Fail is Call+Redo-Exit
197 ),
198 time_data(Node,NetTicks,NetTime,SelfPC,SelfTime,ChildrenPC,ChildrenTime),
199 format('~w ~t~D +~41| ~D ~t~49|~t~D +~58| ~D ~t~2fs.(~78|~t~1f%) +~87|~t~2fs.(~95|~t~1f%)~102|~n',
200 [Pred, Call, Redo, Exit, Fail, SelfTime, SelfPC, ChildrenTime, ChildrenPC]).
201
202format_divider :- format('~`=t~102|~n').
203
204time_data(Data,NetTicks,NetTime,SelfPC,SelfTime,ChildrenPC,ChildrenTime) :-
205 value(ticks_self,Data,Ticks),
206 SelfPC is 100*Ticks/NetTicks,
207 SelfTime is SelfPC*NetTime/100,
208 value(ticks_siblings,Data,ChildrenTicks),
209 ChildrenPC is 100*ChildrenTicks/NetTicks,
210 ChildrenTime is ChildrenPC*NetTime/100.
211
212
213 216
255
256profile_data(Data) :-
257 setup_call_cleanup(
258 profiler(Old, false),
259 profile_data_(Data),
260 profiler(_, Old)).
261
262profile_data_(profile{summary:Summary, nodes:Nodes}) :-
263 prof_statistics(Summary),
264 findall(Node, profile_procedure_data(_:_, Node), Nodes).
265
271
272prof_statistics(summary{samples:Samples, ticks:Ticks,
273 accounting:Account, time:Time,
274 nodes:Nodes,
275 sample_period: Period,
276 ports: Ports
277 }) :-
278 '$prof_statistics'(Samples, Ticks, Account, Time, Nodes, Period, Ports).
279
285
286profile_procedure_data(Pred, Node) :-
287 Node = node{predicate:Pred,
288 ticks_self:TicksSelf, ticks_siblings:TicksSiblings,
289 call:Call, redo:Redo, exit:Exit,
290 callers:Parents, callees:Siblings},
291 ( specified(Pred)
292 -> true
293 ; profiled_predicates(Preds),
294 member(Pred, Preds)
295 ),
296 '$prof_procedure_data'(Pred,
297 TicksSelf, TicksSiblings,
298 Call, Redo, Exit,
299 Parents, Siblings).
300
301specified(Module:Head) :-
302 atom(Module),
303 callable(Head).
304
305profiled_predicates(Preds) :-
306 setof(Pred, prof_impl(Pred), Preds).
307
308prof_impl(Pred) :-
309 prof_node_id(Node),
310 node_id_pred(Node, Pred).
311
312prof_node_id(N) :-
313 prof_node_id_below(N, -).
314
315prof_node_id_below(N, Root) :-
316 '$prof_sibling_of'(N0, Root),
317 ( N = N0
318 ; prof_node_id_below(N, N0)
319 ).
320
321node_id_pred(Node, Pred) :-
322 '$prof_node'(Node, Pred, _Calls, _Redos, _Exits, _Recur,
323 _Ticks, _SiblingTicks).
324
328
329value(name, Data, Name) :-
330 !,
331 predicate_sort_key(Data.predicate, Name).
332value(label, Data, Label) :-
333 !,
334 predicate_label(Data.predicate, Label).
335value(ticks, Data, Ticks) :-
336 !,
337 Ticks is Data.ticks_self + Data.ticks_siblings.
338value(time(Key, percentage, TotalTicks), Data, Percent) :-
339 !,
340 value(Key, Data, Ticks),
341 (TotalTicks > 0
342 -> Percent is 100 * (Ticks/TotalTicks)
343 ; Percent is 0.0
344 ).
345value(Name, Data, Value) :-
346 Value = Data.Name