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-2025, 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:- 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
   64/** <module> Execution profiler
   65
   66This module provides a simple frontend on  the execution profiler with a
   67hook  to  the  GUI  visualiser   for    profiling   results  defined  in
   68library(swi/pce_profile).
   69*/
   70
   71:- multifile
   72    prolog:show_profile_hook/1.   73
   74%!  profile(:Goal).
   75%!  profile(:Goal, +Options).
   76%
   77%   Run once(Goal) under the execution profiler.   If  the (xpce) GUI is
   78%   enabled this predicate is  hooked   by  library(swi/pce_profile) and
   79%   results are presented in a gui that enables navigating the call tree
   80%   and jump to predicate implementations.  Without   the  GUI, a simple
   81%   textual report is generated. Defined options are:
   82%
   83%     - time(Which)
   84%       Profile `cpu` or `wall` time.  The default is CPU time.
   85%     - sample_rate(Rate)
   86%       Samples per second, any numeric value between 1 and 1000.
   87%       Default is defined by the Prolog flag `profile_sample_rate`,
   88%       which defaults to 200.
   89%     - ports(Bool)
   90%       Specifies ports counted - `true` (all ports), `false` (call
   91%       port only) or `classic` (all with some errors).
   92%       Accomodates space/accuracy tradeoff building call tree.
   93%       Default is defined by the Prolog flag `profile_ports`,
   94%       which defaults to `true`.
   95%     - top(N)
   96%       When generating a textual report, show the top N predicates.
   97%     - cumulative(Bool)
   98%       If `true` (default `false`), show cumulative output in
   99%       a textual report.
  100%
  101%   @tbd The textual input reflects only part of the information.
  102%   @see show_coverage/2 from library(test_cover).
  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
  127%!  show_profile(+Options)
  128%
  129%   Display last collected profiling data.  Options are
  130%
  131%     * top(N)
  132%     When generating a textual report, show the top N predicates.
  133%     * cumulative(Bool)
  134%     If =true= (default =false=), show cumulative output in
  135%     a textual report.
  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                 /*******************************
  214                 *         DATA GATHERING       *
  215                 *******************************/
  216
  217%!  profile_data(-Data) is det.
  218%
  219%   Gather all relevant data from profiler. This predicate may be called
  220%   while profiling is active  in  which   case  it  is  suspended while
  221%   collecting the data. Data is a dict providing the following fields:
  222%
  223%     - summary:Dict
  224%       Overall statistics providing
  225%       - samples:Count:
  226%         Times the statistical profiler was called
  227%       - ticks:Count
  228%         Virtual ticks during profiling
  229%       - accounting:Count
  230%         Tick spent on accounting
  231%       - time:Seconds
  232%         Total time sampled
  233%       - nodes:Count
  234%         Nodes in the call graph.
  235%       - sample_period: MicroSeconds
  236%         Same interval timer period in micro seconds
  237%       - ports: Ports
  238%         One of `true`, `false` or `classic`
  239%     - nodes
  240%       List of nodes.  Each node provides:
  241%       - predicate:PredicateIndicator
  242%       - ticks_self:Count
  243%       - ticks_siblings:Count
  244%       - call:Count
  245%       - redo:Count
  246%       - exit:Count
  247%       - callers:list_of(Relative)
  248%       - callees:list_of(Relative)
  249%
  250%    _Relative_ is a term of the shape below that represents a caller or
  251%    callee. Future versions are likely to use a dict instead.
  252%
  253%        node(PredicateIndicator, CycleID, Ticks, TicksSiblings,
  254%             Calls, Redos, Exits)
  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
  266%!  prof_statistics(-Node) is det.
  267%
  268%   Get overall statistics
  269%
  270%   @param Node     term of the format prof(Ticks, Account, Time, Nodes)
  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
  280%!  profile_procedure_data(?Pred, -Data:dict) is nondet.
  281%
  282%   Collect data for Pred. If Pred is   unbound  data for each predicate
  283%   that has profile data available is   returned.  Data is described in
  284%   profile_data/1 as an element of the `nodes` key.
  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
  325%!  value(+Key, +NodeData, -Value)
  326%
  327%   Obtain possible computed attributes from NodeData.
  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