View source with raw comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  1999-2016, University of Amsterdam
    7                              VU University Amsterdam
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(prolog_statistics,
   37          [ statistics/0,
   38            statistics/1,               % -Stats
   39            thread_statistics/2,        % ?Thread, -Stats
   40            time/1,                     % :Goal
   41            profile/1,                  % :Goal
   42            profile/2,                  % :Goal, +Options
   43            show_profile/1              % +Options
   44          ]).   45:- use_module(library(lists)).   46:- use_module(library(pairs)).   47:- use_module(library(option)).   48:- use_module(library(error)).   49:- set_prolog_flag(generate_debug_info, false).   50
   51:- meta_predicate
   52    time(0),
   53    profile(0),
   54    profile(0, +).

Get information about resource usage

This library provides predicates to obtain information about resource usage by your program. The predicates of this library are for human use at the toplevel: information is printed. All predicates obtain their information using public low-level primitives. These primitives can be use to obtain selective statistics during execution. */

 statistics is det
Print information about resource usage using print_message/2.
See also
- All statistics printed are obtained through statistics/2.
   71statistics :-
   72    phrase(collect_stats, Stats),
   73    print_message(information, statistics(Stats)).
 statistics(-Stats:dict) is det
Stats is a dict representing the same information as statistics/0. This convience function is primarily intended to pass statistical information to e.g., a web client. Time critical code that wishes to collect statistics typically only need a small subset and should use statistics/2 to obtain exactly the data they need.
   84statistics(Stats) :-
   85    phrase(collect_stats, [CoreStats|StatList]),
   86    dict_pairs(CoreStats, _, CorePairs),
   87    map_list_to_pairs(dict_key, StatList, ExtraPairs),
   88    append(CorePairs, ExtraPairs, Pairs),
   89    dict_pairs(Stats, statistics, Pairs).
   90
   91dict_key(Dict, Key) :-
   92    gc{type:atom} :< Dict,
   93    !,
   94    Key = agc.
   95dict_key(Dict, Key) :-
   96    gc{type:clause} :< Dict,
   97    !,
   98    Key = cgc.
   99dict_key(Dict, Key) :-
  100    is_dict(Dict, Key).
  101
  102collect_stats -->
  103    core_statistics,
  104    gc_statistics,
  105    agc_statistics,
  106    cgc_statistics,
  107    shift_statistics,
  108    thread_counts,
  109    engine_counts.
  110
  111core_statistics -->
  112    { statistics(process_cputime, Cputime),
  113      statistics(process_epoch, Epoch),
  114      statistics(inferences, Inferences),
  115      statistics(atoms, Atoms),
  116      statistics(functors, Functors),
  117      statistics(predicates, Predicates),
  118      statistics(modules, Modules),
  119      statistics(codes, Codes),
  120      thread_self(Me),
  121      thread_stack_statistics(Me, Stacks)
  122    },
  123    [ core{ time:time{cpu:Cputime, inferences:Inferences, epoch:Epoch},
  124            data:counts{atoms:Atoms, functors:Functors,
  125                        predicates:Predicates, modules:Modules,
  126                        vm_codes:Codes},
  127            stacks:Stacks
  128          }
  129    ].
  130
  131:- if(\+current_predicate(thread_statistics/3)).  132thread_statistics(_Thread, Key, Value) :-
  133    statistics(Key, Value).
  134:- endif.  135
  136thread_stack_statistics(Thread,
  137                  stacks{local:stack{name:local,
  138                                    limit:LocalLimit,
  139                                     allocated:Local,
  140                                     usage:LocalUsed},
  141                         global:stack{name:global,
  142                                      limit:GlobalLimit,
  143                                      allocated:Global,
  144                                      usage:GlobalUsed},
  145                         trail:stack{name:trail,
  146                                     limit:TrailLimit,
  147                                     allocated:Trail,
  148                                     usage:TrailUsed},
  149                         total:stack{name:stacks,
  150                                     limit:StackLimit,
  151                                     allocated:StackAllocated,
  152                                     usage:StackUsed}
  153                        }) :-
  154    thread_statistics(Thread, trail,       Trail),
  155    thread_statistics(Thread, trailused,   TrailUsed),
  156    thread_statistics(Thread, local,       Local),
  157    thread_statistics(Thread, localused,   LocalUsed),
  158    thread_statistics(Thread, global,      Global),
  159    thread_statistics(Thread, globalused,  GlobalUsed),
  160    thread_statistics(Thread, locallimit,  LocalLimit),
  161    thread_statistics(Thread, globallimit, GlobalLimit),
  162    thread_statistics(Thread, traillimit,  TrailLimit),
  163    StackUsed is LocalUsed+GlobalUsed+TrailUsed,
  164    StackAllocated is Local+Global+Trail,
  165    StackLimit is LocalLimit+GlobalLimit+TrailLimit.
  166
  167gc_statistics -->
  168    { statistics(collections, Collections),
  169      Collections > 0,
  170      !,
  171      statistics(collected, Collected),
  172      statistics(gctime, GcTime)
  173    },
  174    [ gc{type:stack, unit:byte,
  175         count:Collections, time:GcTime, gained:Collected } ].
  176gc_statistics --> [].
  177
  178agc_statistics -->
  179    { catch(statistics(agc, Agc), _, fail),
  180      Agc > 0,
  181      !,
  182      statistics(agc_gained, Gained),
  183      statistics(agc_time, Time)
  184    },
  185    [ gc{type:atom, unit:atom,
  186         count:Agc, time:Time, gained:Gained} ].
  187agc_statistics --> [].
  188
  189cgc_statistics -->
  190    { catch(statistics(cgc, Cgc), _, fail),
  191      Cgc > 0,
  192      !,
  193      statistics(cgc_gained, Gained),
  194      statistics(cgc_time, Time)
  195    },
  196    [ gc{type:clause, unit:clause,
  197         count:Cgc, time:Time, gained:Gained} ].
  198cgc_statistics --> [].
  199
  200shift_statistics -->
  201    { statistics(local_shifts, LS),
  202      statistics(global_shifts, GS),
  203      statistics(trail_shifts, TS),
  204      (   LS > 0
  205      ;   GS > 0
  206      ;   TS > 0
  207      ),
  208      !,
  209      statistics(shift_time, Time)
  210    },
  211    [ shift{local:LS, global:GS, trail:TS, time:Time} ].
  212shift_statistics --> [].
  213
  214thread_counts -->
  215    { current_prolog_flag(threads, true),
  216      statistics(threads, Active),
  217      statistics(threads_created, Created),
  218      Created > 1,
  219      !,
  220      statistics(thread_cputime, CpuTime),
  221      Finished is Created - Active
  222    },
  223    [ thread{count:Active, finished:Finished, time:CpuTime} ].
  224thread_counts --> [].
  225
  226engine_counts -->
  227    { current_prolog_flag(threads, true),
  228      statistics(engines, Active),
  229      statistics(engines_created, Created),
  230      Created > 0,
  231      !,
  232      Finished is Created - Active
  233    },
  234    [ engine{count:Active, finished:Finished} ].
  235engine_counts --> [].
 thread_statistics(?Thread, -Stats:dict) is nondet
Obtain statistical information about a single thread. Fails silently of the Thread is no longer alive.
Arguments:
Stats- is a dict containing status, time and stack-size information about Thread.
  246thread_statistics(Thread, Stats) :-
  247    thread_property(Thread, status(Status)),
  248    human_thread_id(Thread, Id),
  249    (   catch(thread_stats(Thread, Stacks, Time), _, fail)
  250    ->  Stats = thread{id:Id,
  251                       status:Status,
  252                       time:Time,
  253                       stacks:Stacks}
  254    ;   Stats = thread{id:Thread,
  255                       status:Status}
  256    ).
  257
  258human_thread_id(Thread, Id) :-
  259    atom(Thread),
  260    !,
  261    Id = Thread.
  262human_thread_id(Thread, Id) :-
  263    thread_property(Thread, id(Id)).
  264
  265thread_stats(Thread, Stacks,
  266             time{cpu:CpuTime,
  267                  inferences:Inferences,
  268                  epoch:Epoch
  269                 }) :-
  270    thread_statistics(Thread, cputime, CpuTime),
  271    thread_statistics(Thread, inferences, Inferences),
  272    thread_statistics(Thread, epoch, Epoch),
  273    thread_stack_statistics(Thread, Stacks).
 time(:Goal) is nondet
Execute Goal, reporting statistics to the user. If Goal succeeds non-deterministically, retrying reports the statistics for providing the next answer.

Statistics are retrieved using thread_statistics/3 on the calling thread. Note that not all systems support thread-specific CPU time. Notable, this is lacking on MacOS X.

See also
- statistics/2 for obtaining statistics in your program and understanding the reported values.
bug
- Inference statistics are often a few off.
  290time(Goal) :-
  291    time_state(State0),
  292    (   call_cleanup(catch(Goal, E, (report(State0,10), throw(E))),
  293                     Det = true),
  294        time_true(State0),
  295        (   Det == true
  296        ->  !
  297        ;   true
  298        )
  299    ;   report(State0, 11),
  300        fail
  301    ).
  302
  303report(t(OldWall, OldTime, OldInferences), Sub) :-
  304    time_state(t(NewWall, NewTime, NewInferences)),
  305    UsedTime is NewTime - OldTime,
  306    UsedInf  is NewInferences - OldInferences - Sub,
  307    Wall     is NewWall - OldWall,
  308    (   UsedTime =:= 0
  309    ->  Lips = 'Infinite'
  310    ;   Lips is integer(UsedInf / UsedTime)
  311    ),
  312    print_message(information, time(UsedInf, UsedTime, Wall, Lips)).
  313
  314time_state(t(Wall, Time, Inferences)) :-
  315    get_time(Wall),
  316    statistics(cputime, Time),
  317    statistics(inferences, Inferences).
  318
  319time_true(State0) :-
  320    report(State0, 12).             % leave choice-point
  321time_true(State) :-
  322    get_time(Wall),
  323    statistics(cputime, Time),
  324    statistics(inferences, Inferences0),
  325    plus(Inferences0, -3, Inferences),
  326    nb_setarg(1, State, Wall),
  327    nb_setarg(2, State, Time),
  328    nb_setarg(3, State, Inferences),
  329    fail.
  330
  331
  332                 /*******************************
  333                 *     EXECUTION PROFILING      *
  334                 *******************************/
  335
  336/* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  337This module provides a simple backward compatibility frontend on the new
  338(in version 5.1.10) execution profiler  with  a   hook  to  the  new GUI
  339visualiser for profiling results defined in library('swi/pce_profile').
  340
  341Later we will add a proper textual report-generator.
  342- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  343
  344:- multifile
  345    prolog:show_profile_hook/1.
 profile(:Goal)
 profile(:Goal, +Options)
Run Goal under the execution profiler. Defined options are:
time(Which)
Profile cpu or wall time. The default is CPU time.
top(N)
When generating a textual report, show the top N predicates.
cumulative(Bool)
If true (default false), show cumulative output in a textual report.
  360profile(Goal) :-
  361    profile(Goal, []).
  362
  363profile(Goal0, Options) :-
  364    option(time(Which), Options, cpu),
  365    time_name(Which, How),
  366    expand_goal(Goal0, Goal),
  367    call_cleanup('$profile'(Goal, How),
  368                 prolog_statistics:show_profile(Options)).
  369
  370time_name(cpu,      cputime)  :- !.
  371time_name(wall,     walltime) :- !.
  372time_name(cputime,  cputime)  :- !.
  373time_name(walltime, walltime) :- !.
  374time_name(Time, _) :-
  375    must_be(oneof([cpu,wall]), Time).
 show_profile(+Options)
Display last collected profiling data. Options are
top(N)
When generating a textual report, show the top N predicates.
cumulative(Bool)
If true (default false), show cumulative output in a textual report.
  387show_profile(N) :-
  388    integer(N),
  389    !,
  390    show_profile([top(N)]).
  391show_profile(Options) :-
  392    profiler(Old, false),
  393    show_profile_(Options),
  394    profiler(_, Old).
  395
  396show_profile_(Options) :-
  397    prolog:show_profile_hook(Options),
  398    !.
  399show_profile_(Options) :-
  400    prof_statistics(Stat),
  401    prof_statistics(time, Stat, Time),
  402    sort_on(Options, SortKey),
  403    findall(KeyedNode, prof_node(SortKey, KeyedNode), Nodes),
  404    sort(1, >=, Nodes, Sorted),
  405    format('~`=t~69|~n'),
  406    format('Total time: ~3f seconds~n', [Time]),
  407    format('~`=t~69|~n'),
  408    format('~w~t~w =~45|~t~w~60|~t~w~69|~n',
  409           [ 'Predicate', 'Box Entries', 'Calls+Redos', 'Time'
  410           ]),
  411    format('~`=t~69|~n'),
  412    option(top(N), Options, 25),
  413    show_plain(Sorted, N, Stat, SortKey).
  414
  415sort_on(Options, ticks_self) :-
  416    option(cumulative(false), Options, false),
  417    !.
  418sort_on(_, ticks).
  419
  420show_plain([], _, _, _).
  421show_plain(_, 0, _, _) :- !.
  422show_plain([_-H|T], N, Stat, Key) :-
  423    show_plain(H, Stat, Key),
  424    N2 is N - 1,
  425    show_plain(T, N2, Stat, Key).
  426
  427show_plain(Node, Stat, Key) :-
  428    value(label,                       Node, Pred),
  429    value(call,                        Node, Call),
  430    value(redo,                        Node, Redo),
  431    value(time(Key, percentage, Stat), Node, Percent),
  432    IntPercent is round(Percent*10),
  433    Entry is Call + Redo,
  434    format('~w~t~D =~45|~t~D+~55|~D ~t~1d%~69|~n',
  435           [Pred, Entry, Call, Redo, IntPercent]).
  436
  437
  438                 /*******************************
  439                 *         DATA GATHERING       *
  440                 *******************************/
 prof_statistics(-Node) is det
Get overall statistics
Arguments:
Node- term of the format prof(Ticks, Account, Time, Nodes)
  448prof_statistics(prof(Samples, Ticks, Account, Time, Nodes)) :-
  449    '$prof_statistics'(Samples, Ticks, Account, Time, Nodes).
  450
  451prof_statistics(samples, Term, Samples) :-
  452    arg(1, Term, Samples).
  453prof_statistics(ticks, Term, Ticks) :-
  454    arg(2, Term, Ticks).
  455prof_statistics(accounting, Term, Ticks) :-
  456    arg(3, Term, Ticks).
  457prof_statistics(time, Term, Ticks) :-
  458    arg(4, Term, Ticks).
  459prof_statistics(nodes, Term, Ticks) :-
  460    arg(5, Term, Ticks).
 prof_node(+Field, -Pairs) is nondet
Collect data for each of the interesting predicate.
Arguments:
Field- specifies the field to use as key in each pair.
Pair- is a term of the following format:
KeyValue-node(Pred,
              TimeSelf, TimeSiblings,
              Calls, Redo, Recursive,
              Parents)
  478prof_node(KeyOn, Node) :-
  479    setup_call_cleanup(
  480        ( current_prolog_flag(access_level, Old),
  481          set_prolog_flag(access_level, system)
  482        ),
  483        get_prof_node(KeyOn, Node),
  484        set_prolog_flag(access_level, Old)).
  485
  486get_prof_node(KeyOn, Key-Node) :-
  487    Node = node(M:H,
  488                TicksSelf, TicksSiblings,
  489                Call, Redo,
  490                Parents, Siblings),
  491    current_predicate(_, M:H),
  492    \+ predicate_property(M:H, imported_from(_)),
  493    '$prof_procedure_data'(M:H,
  494                           TicksSelf, TicksSiblings,
  495                           Call, Redo,
  496                           Parents, Siblings),
  497    value(KeyOn, Node, Key).
  498
  499key(predicate,      1).
  500key(ticks_self,     2).
  501key(ticks_siblings, 3).
  502key(call,           4).
  503key(redo,           5).
  504key(callers,        6).
  505key(callees,        7).
  506
  507value(name, Data, Name) :-
  508    !,
  509    arg(1, Data, Pred),
  510    predicate_functor_name(Pred, Name).
  511value(label, Data, Label) :-
  512    !,
  513    arg(1, Data, Pred),
  514    predicate_label(Pred, Label).
  515value(ticks, Data, Ticks) :-
  516    !,
  517    arg(2, Data, Self),
  518    arg(3, Data, Siblings),
  519    Ticks is Self + Siblings.
  520value(time(Key, percentage, Stat), Data, Percent) :-
  521    !,
  522    value(Key, Data, Ticks),
  523    prof_statistics(ticks, Stat, Total),
  524    prof_statistics(accounting, Stat, Account),
  525    (   Total-Account > 0
  526    ->  Percent is 100 * (Ticks/(Total-Account))
  527    ;   Percent is 0.0
  528    ).
  529value(Name, Data, Value) :-
  530    key(Name, Arg),
  531    arg(Arg, Data, Value).
 predicate_label(+Head, -Label)
Create a human-readable label for the given head
  537predicate_label(M:H, Label) :-
  538    !,
  539    functor(H, Name, Arity),
  540    (   hidden_module(M, H)
  541    ->  atomic_list_concat([Name, /, Arity], Label)
  542    ;   atomic_list_concat([M, :, Name, /, Arity], Label)
  543    ).
  544predicate_label(H, Label) :-
  545    !,
  546    functor(H, Name, Arity),
  547    atomic_list_concat([Name, /, Arity], Label).
  548
  549hidden_module(system, _).
  550hidden_module(user, _).
  551hidden_module(M, H) :-
  552    predicate_property(system:H, imported_from(M)).
 predicate_functor_name(+Head, -Name)
Return the (module-free) name of the predicate for sorting purposes.
  559predicate_functor_name(_:H, Name) :-
  560    !,
  561    predicate_functor_name(H, Name).
  562predicate_functor_name(H, Name) :-
  563    functor(H, Name, _Arity).
  564
  565
  566                 /*******************************
  567                 *            MESSAGES          *
  568                 *******************************/
  569
  570:- multifile
  571    prolog:message/3.  572
  573% NOTE: The code below uses get_dict/3 rather than the functional
  574% notation to make this code work with `swipl --traditional`
  575
  576prolog:message(time(UsedInf, UsedTime, Wall, Lips)) -->
  577    [ '~D inferences, ~3f CPU in ~3f seconds (~w% CPU, ~w Lips)'-
  578      [UsedInf, UsedTime, Wall, Perc, Lips] ],
  579    {   Wall > 0
  580    ->  Perc is round(100*UsedTime/Wall)
  581    ;   Perc = ?
  582    }.
  583prolog:message(statistics(List)) -->
  584    msg_statistics(List).
  585
  586msg_statistics([]) --> [].
  587msg_statistics([H|T]) -->
  588    { is_dict(H, Tag) },
  589    msg_statistics(Tag, H),
  590    (   { T == [] }
  591    ->  []
  592    ;   [nl], msg_statistics(T)
  593    ).
  594
  595msg_statistics(core, S) -->
  596    { get_dict(time, S, Time),
  597      get_dict(data, S, Data),
  598      get_dict(stacks, S, Stacks)
  599    },
  600    time_stats(Time), [nl],
  601    data_stats(Data), [nl,nl],
  602    stacks_stats(Stacks).
  603msg_statistics(gc, S) -->
  604    {   (   get_dict(type, S, stack)
  605        ->  Label = ''
  606        ;   get_dict(type, S, Type),
  607            string_concat(Type, " ", Label)
  608        ),
  609        get_dict(count, S, Count),
  610        get_dict(gained, S, Gained),
  611        get_dict(unit, S, Unit),
  612        get_dict(time, S, Time)
  613    },
  614    [ '~D ~wgarbage collections gained ~D ~ws in ~3f seconds.'-
  615      [ Count, Label, Gained, Unit, Time]
  616    ].
  617msg_statistics(shift, S) -->
  618    { get_dict(local, S, Local),
  619      get_dict(global, S, Global),
  620      get_dict(trail, S, Trail),
  621      get_dict(time, S, Time)
  622    },
  623    [ 'Stack shifts: ~D local, ~D global, ~D trail in ~3f seconds'-
  624      [ Local, Global, Trail, Time ]
  625    ].
  626msg_statistics(thread, S) -->
  627    { get_dict(count, S, Count),
  628      get_dict(finished, S, Finished),
  629      get_dict(time, S, Time)
  630    },
  631    [ '~D threads, ~D finished threads used ~3f seconds'-
  632      [Count, Finished, Time]
  633    ].
  634msg_statistics(engine, S) -->
  635    { get_dict(count, S, Count),
  636      get_dict(finished, S, Finished)
  637    },
  638    [ '~D engines, ~D finished engines'-
  639      [Count, Finished]
  640    ].
  641
  642time_stats(T) -->
  643    { get_dict(epoch, T, Epoch),
  644      format_time(string(EpochS), '%+', Epoch),
  645      get_dict(cpu, T, CPU),
  646      get_dict(inferences, T, Inferences)
  647    },
  648    [ 'Started at ~s'-[EpochS], nl,
  649      '~3f seconds cpu time for ~D inferences'-
  650      [ CPU, Inferences ]
  651    ].
  652data_stats(C) -->
  653    { get_dict(atoms, C, Atoms),
  654      get_dict(functors, C, Functors),
  655      get_dict(predicates, C, Predicates),
  656      get_dict(modules, C, Modules),
  657      get_dict(vm_codes, C, VMCodes)
  658    },
  659    [ '~D atoms, ~D functors, ~D predicates, ~D modules, ~D VM-codes'-
  660      [ Atoms, Functors, Predicates, Modules, VMCodes]
  661    ].
  662stacks_stats(S) -->
  663    { get_dict(local, S, Local),
  664      get_dict(global, S, Global),
  665      get_dict(trail, S, Trail)
  666    },
  667    [ '~|~tLimit~28+~tAllocated~13+~tIn use~13+'-[], nl ],
  668    stack_stats('Local ', Local),  [nl],
  669    stack_stats('Global', Global), [nl],
  670    stack_stats('Trail ', Trail),  [nl].
  671
  672stack_stats(Stack, S) -->
  673    { get_dict(limit, S, Limit),
  674      get_dict(allocated, S, Allocated),
  675      get_dict(usage, S, Usage)
  676    },
  677    [ '~|~w stack:~t~D~28+ ~t~D~13+ ~t~D~13+ Bytes'-
  678      [Stack, Limit, Allocated, Usage]
  679    ].
  680
  681:- multifile sandbox:safe_primitive/1.  682
  683sandbox:safe_primitive(prolog_statistics:statistics(_)).
  684sandbox:safe_primitive(prolog_statistics:statistics).
  685sandbox:safe_meta_predicate(prolog_statistics:profile/1).
  686sandbox:safe_meta_predicate(prolog_statistics:profile/2)