View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        jan@swi-prolog.org
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2023, SWI-Prolog Solutions b.v.
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(prolog_profile,
   36          [ profile/1,                  % :Goal
   37            profile/2,                  % :Goal, +Options
   38            show_profile/1,             % +Options
   39            profile_data/1,             % -Dict
   40            profile_procedure_data/2    % :PI, -Data
   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:- set_prolog_flag(generate_debug_info, false).   54
   55/** <module> Execution profiler
   56
   57This module provides a simple frontend on  the execution profiler with a
   58hook  to  the  GUI  visualiser   for    profiling   results  defined  in
   59library(swi/pce_profile).
   60*/
   61
   62:- multifile
   63    prolog:show_profile_hook/1.   64
   65%!  profile(:Goal).
   66%!  profile(:Goal, +Options).
   67%
   68%   Run once(Goal) under the execution profiler.   If  the (xpce) GUI is
   69%   enabled this predicate is  hooked   by  library(swi/pce_profile) and
   70%   results are presented in a gui that enables navigating the call tree
   71%   and jump to predicate implementations.  Without   the  GUI, a simple
   72%   textual report is generated. Defined options are:
   73%
   74%     * time(Which)
   75%     Profile `cpu` or `wall` time.  The default is CPU time.
   76%     * sample_rate(Rate)
   77%     Samples per second, any numeric value between 1 and 1000
   78%     * ports(Bool)
   79%     Specifies ports counted - `true` (all ports), `false` (call
   80%     port only) or `classic` (all with some errors).
   81%     Accomodates space/accuracy tradeoff building call tree.
   82%     * top(N)
   83%     When generating a textual report, show the top N predicates.
   84%     * cumulative(Bool)
   85%     If `true` (default `false`), show cumulative output in
   86%     a textual report.
   87%
   88%   @tbd The textual input reflects only part of the information.
   89%   @see show_coverage/2 from library(test_cover).
   90
   91profile(Goal) :-
   92    profile(Goal, []).
   93
   94profile(Goal0, Options) :-
   95    option(time(Which), Options, cpu),
   96    time_name(Which, How),
   97    option(ports(Ports), Options, classic),
   98    must_be(oneof([true,false,classic]),Ports),
   99    option(sample_rate(Rate), Options, 200),
  100    must_be(between(1.0,1000), Rate),
  101    expand_goal(Goal0, Goal),
  102    call_cleanup('$profile'(Goal, How, Ports, Rate),
  103                 prolog_statistics:show_profile(Options)).
  104
  105time_name(cpu,      cputime)  :- !.
  106time_name(wall,     walltime) :- !.
  107time_name(cputime,  cputime)  :- !.
  108time_name(walltime, walltime) :- !.
  109time_name(Time, _) :-
  110    must_be(oneof([cpu,wall]), Time).
  111
  112%!  show_profile(+Options)
  113%
  114%   Display last collected profiling data.  Options are
  115%
  116%     * top(N)
  117%     When generating a textual report, show the top N predicates.
  118%     * cumulative(Bool)
  119%     If =true= (default =false=), show cumulative output in
  120%     a textual report.
  121
  122show_profile(N) :-
  123    integer(N),
  124    !,
  125    show_profile([top(N)]).
  126show_profile(Options) :-
  127    profiler(Old, false),
  128    show_profile_(Options),
  129    profiler(_, Old).
  130
  131show_profile_(Options) :-
  132    prolog:show_profile_hook(Options),
  133    !.
  134show_profile_(Options) :-
  135    prof_statistics(Stat),
  136    sort_on(Options, SortKey),
  137    findall(Node, profile_procedure_data(_:_, Node), Nodes),
  138    sort_prof_nodes(SortKey, Nodes, Sorted),
  139    format('~`=t~69|~n'),
  140    format('Total time: ~3f seconds~n', [Stat.time]),
  141    format('~`=t~69|~n'),
  142    format('~w~t~w =~45|~t~w~60|~t~w~69|~n',
  143           [ 'Predicate', 'Box Entries', 'Calls+Redos', 'Time'
  144           ]),
  145    format('~`=t~69|~n'),
  146    option(top(N), Options, 25),
  147    show_plain(Sorted, N, Stat, SortKey).
  148
  149sort_on(Options, ticks_self) :-
  150    option(cumulative(false), Options, false),
  151    !.
  152sort_on(_, ticks).
  153
  154sort_prof_nodes(ticks, Nodes, Sorted) :-
  155    !,
  156    map_list_to_pairs(key_ticks, Nodes, Keyed),
  157    sort(1, >=, Keyed, KeySorted),
  158    pairs_values(KeySorted, Sorted).
  159sort_prof_nodes(Key, Nodes, Sorted) :-
  160    sort(Key, >=, Nodes, Sorted).
  161
  162key_ticks(Node, Ticks) :-
  163    Ticks is Node.ticks_self + Node.ticks_siblings.
  164
  165show_plain([], _, _, _).
  166show_plain(_, 0, _, _) :- !.
  167show_plain([H|T], N, Stat, Key) :-
  168    show_plain(H, Stat, Key),
  169    N2 is N - 1,
  170    show_plain(T, N2, Stat, Key).
  171
  172show_plain(Node, Stat, Key) :-
  173    value(label,                       Node, Pred),
  174    value(call,                        Node, Call),
  175    value(redo,                        Node, Redo),
  176    value(time(Key, percentage, Stat), Node, Percent),
  177    IntPercent is round(Percent*10),
  178    Entry is Call + Redo,
  179    format('~w~t~D =~45|~t~D+~55|~D ~t~1d%~69|~n',
  180           [Pred, Entry, Call, Redo, IntPercent]).
  181
  182
  183                 /*******************************
  184                 *         DATA GATHERING       *
  185                 *******************************/
  186
  187%!  profile_data(-Data) is det.
  188%
  189%   Gather all relevant data from profiler. This predicate may be called
  190%   while profiling is active  in  which   case  it  is  suspended while
  191%   collecting the data. Data is a dict providing the following fields:
  192%
  193%     - summary:Dict
  194%       Overall statistics providing
  195%       - samples:Count:
  196%         Times the statistical profiler was called
  197%       - ticks:Count
  198%         Virtual ticks during profiling
  199%       - accounting:Count
  200%         Tick spent on accounting
  201%       - time:Seconds
  202%         Total time sampled
  203%       - nodes:Count
  204%         Nodes in the call graph.
  205%       - sample_period: MicroSeconds
  206%         Same interval timer period in micro seconds
  207%       - ports: Ports
  208%         One of `true`, `false` or `classic`
  209%     - nodes
  210%       List of nodes.  Each node provides:
  211%       - predicate:PredicateIndicator
  212%       - ticks_self:Count
  213%       - ticks_siblings:Count
  214%       - call:Count
  215%       - redo:Count
  216%       - exit:Count
  217%       - callers:list_of(Relative)
  218%       - callees:list_of(Relative)
  219%
  220%    _Relative_ is a term of the shape below that represents a caller or
  221%    callee. Future versions are likely to use a dict instead.
  222%
  223%        node(PredicateIndicator, CycleID, Ticks, TicksSiblings,
  224%             Calls, Redos, Exits)
  225
  226profile_data(Data) :-
  227    setup_call_cleanup(
  228        profiler(Old, false),
  229        profile_data_(Data),
  230        profiler(_, Old)).
  231
  232profile_data_(profile{summary:Summary, nodes:Nodes}) :-
  233    prof_statistics(Summary),
  234    findall(Node, profile_procedure_data(_:_, Node), Nodes).
  235
  236%!  prof_statistics(-Node) is det.
  237%
  238%   Get overall statistics
  239%
  240%   @param Node     term of the format prof(Ticks, Account, Time, Nodes)
  241
  242prof_statistics(summary{samples:Samples, ticks:Ticks,
  243                        accounting:Account, time:Time,
  244                        nodes:Nodes,
  245                        sample_period: Period,
  246                        ports: Ports
  247                       }) :-
  248    '$prof_statistics'(Samples, Ticks, Account, Time, Nodes, Period, Ports).
  249
  250%!  profile_procedure_data(?Pred, -Data:dict) is nondet.
  251%
  252%   Collect data for Pred. If Pred is   unbound  data for each predicate
  253%   that has profile data available is   returned.  Data is described in
  254%   profile_data/1 as an element of the `nodes` key.
  255
  256profile_procedure_data(Pred, Node) :-
  257    Node = node{predicate:Pred,
  258                ticks_self:TicksSelf, ticks_siblings:TicksSiblings,
  259                call:Call, redo:Redo, exit:Exit,
  260                callers:Parents, callees:Siblings},
  261    (   specified(Pred)
  262    ->  true
  263    ;   profiled_predicates(Preds),
  264        member(Pred, Preds)
  265    ),
  266    '$prof_procedure_data'(Pred,
  267                           TicksSelf, TicksSiblings,
  268                           Call, Redo, Exit,
  269                           Parents, Siblings).
  270
  271specified(Module:Head) :-
  272    atom(Module),
  273    callable(Head).
  274
  275profiled_predicates(Preds) :-
  276    setof(Pred, prof_impl(Pred), Preds).
  277
  278prof_impl(Pred) :-
  279    prof_node_id(Node),
  280    node_id_pred(Node, Pred).
  281
  282prof_node_id(N) :-
  283    prof_node_id_below(N, -).
  284
  285prof_node_id_below(N, Root) :-
  286    '$prof_sibling_of'(N0, Root),
  287    (   N = N0
  288    ;   prof_node_id_below(N, N0)
  289    ).
  290
  291node_id_pred(Node, Pred) :-
  292    '$prof_node'(Node, Pred, _Calls, _Redos, _Exits, _Recur,
  293                 _Ticks, _SiblingTicks).
  294
  295%!  value(+Key, +NodeData, -Value)
  296%
  297%   Obtain possible computed attributes from NodeData.
  298
  299value(name, Data, Name) :-
  300    !,
  301    predicate_sort_key(Data.predicate, Name).
  302value(label, Data, Label) :-
  303    !,
  304    predicate_label(Data.predicate, Label).
  305value(ticks, Data, Ticks) :-
  306    !,
  307    Ticks is Data.ticks_self + Data.ticks_siblings.
  308value(time(Key, percentage, Stat), Data, Percent) :-
  309    !,
  310    value(Key, Data, Ticks),
  311    Total = Stat.ticks,
  312    Account = Stat.accounting,
  313    (   Total-Account > 0
  314    ->  Percent is 100 * (Ticks/(Total-Account))
  315    ;   Percent is 0.0
  316    ).
  317value(Name, Data, Value) :-
  318    Value = Data.Name