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)  2017-2025, VU University Amsterdam
    7			      CWI Amsterdam
    8                              SWI-Prolog Solutions b.v.
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module(prolog_jiti,
   38          [ jiti_list/0,
   39            jiti_list/1,                % +Spec
   40            jiti_suggest_modes/1,       % :Spec
   41            jiti_suggest_modes/0
   42          ]).   43:- autoload(library(apply), [maplist/2, foldl/4, convlist/3]).   44:- autoload(library(dcg/basics), [number//1]).   45:- autoload(library(ansi_term), [ansi_format/3, ansi_hyperlink/3]).   46:- autoload(library(prolog_code), [pi_head/2, most_general_goal/2]).   47:- autoload(library(listing), [portray_clause/1]).   48:- autoload(library(lists), [append/2]).   49:- autoload(library(ordsets), [ord_subtract/3]).   50
   51
   52:- meta_predicate
   53    jiti_list(:),
   54    jiti_suggest_modes(:).

Just In Time Indexing (JITI) utilities

This module provides utilities to examine just-in-time indexes created by the system and can help diagnosing space and performance issues.

To be done
- Use print_message/2 and dynamically figure out the column width. */
 jiti_list is det
 jiti_list(:Spec) is det
List the JITI (Just In Time Indexes) of selected predicates. The predicate jiti_list/0 list all just-in-time indexed predicates. The predicate jiti_list/1 takes one of the patterns below. All parts except for Name can be variables. The last pattern takes an arbitrary number of arguments.

The columns use the following notation:

   97jiti_list :-
   98    jiti_list(_:_).
   99
  100jiti_list(Spec) :-
  101    spec_head(Spec, Head),
  102    !,
  103    jiti_list(Head).
  104jiti_list(Head) :-
  105    tty_width(TTYW),
  106    findall(PI-Indexed,
  107            (   predicate_property(Head, indexed(Indexed)),
  108                \+ predicate_property(Head, imported_from(_)),
  109                pi_head(PI, Head)
  110            ), Pairs0),
  111    sort(Pairs0, Pairs),
  112    PredColW is TTYW-47,
  113    TableWidth is TTYW-1,
  114    ansi_format(bold, 'Predicate~*|~w ~t~10+~w ~t~w~14+ ~t~w~9+ ~t~w~6+ ~t~w~6+~n',
  115                [PredColW, '#Clauses', 'Index','Buckets','Speedup','Coll','Flags']),
  116    format('~`\u2015t~*|~n', [TableWidth]),
  117    maplist(print_indexes(PredColW), Pairs).
  118
  119print_indexes(PredColW, PI-List) :-
  120    foldl(print_index(PredColW, PI), List, 1, _).
  121
  122:- det(print_index/5).  123print_index(PredColW, PI0, Dict, N, N1) :-
  124    pi_head(PI0, Head),
  125    head_pi(Head, PI),                  % Create DCG PI
  126    N1 is N+1,
  127    _{arguments:Args, position:Pos,
  128      buckets:Buckets, speedup:Speedup, list:List, realised:R,
  129      collisions:Collisions0} :< Dict,
  130    predicate_property(Head, number_of_clauses(CCount)),
  131    phrase(iarg_spec(Pos, Args), ArgsS),
  132    phrase(iflags(List, R), Flags),
  133    istyle(R, Style),
  134    icoll(R, List, Collisions0, Collisions),
  135    CCountColZ is PredColW+8,
  136    (   N == 1
  137    ->  format_pi(PI),
  138        format(' ~t~D~*|  ', [CCount, CCountColZ])
  139    ;   format(' ~t~*|  ', [CCountColZ])
  140    ),
  141    ansi_format(Style, '~|~s ~t~D~14+ ~t~1f~9+ ~t~w~6+ ~s~n',
  142                [ArgsS,Buckets,Speedup,Collisions,Flags]).
  143
  144format_pi(PI) :-
  145    pi_head(PI, Head),
  146    predicate_property(Head, file(File)),
  147    predicate_property(Head, line_count(Line)),
  148    !,
  149    format(string(Label), '~q', [PI]),
  150    ansi_hyperlink(user_output, File:Line, Label).
  151format_pi(PI) :-
  152    format('~q', [PI]).
 iarg_spec(+Position, +Args)//
  156iarg_spec([], [N]) ==>
  157    number(N).
  158iarg_spec([], List) ==>
  159    plus_list(List).
  160iarg_spec(Deep, Args) ==>
  161    deep_list(Deep),
  162    iarg_spec([], Args).
  163
  164plus_list([H|T]) -->
  165    number(H),
  166    (   {T==[]}
  167    ->  []
  168    ;   "+",
  169        plus_list(T)
  170    ).
  171
  172deep_list([Last]) -->
  173    !,
  174    number(Last),
  175    ":".
  176deep_list([H|T]) -->
  177    number(H),
  178    "/",
  179    deep_list(T).
  180
  181
  182iflags(true, R)  ==> "L", irealised(R).
  183iflags(false, R) ==> "", irealised(R).
  184
  185irealised(false) ==> "V".
  186irealised(true)  ==> "".
  187
  188istyle(true, code).
  189istyle(false, comment).
  190
  191icoll(true,  false, Collisions0, Collisions) =>
  192    Collisions = Collisions0.
  193icoll(_, _, _, Collisions) =>
  194    Collisions = '-'.
  195
  196head_pi(Head, PI) :-
  197    predicate_property(Head, non_terminal),
  198    !,
  199    pi_head(PI0, Head),
  200    dcg_pi(PI0, PI).
  201head_pi(Head, PI) :-
  202    pi_head(PI, Head).
  203
  204dcg_pi(M:Name/Arity, DCG) =>
  205    Arity2 is Arity-2,
  206    DCG = M:Name//Arity2.
  207dcg_pi(Name/Arity, DCG) =>
  208    Arity2 is Arity-2,
  209    DCG = Name//Arity2.
  210
  211
  212                /*******************************
  213                *            MODES             *
  214                *******************************/
 jiti_suggest_modes is det
 jiti_suggest_modes(:Spec) is det
Propose modes for the predicates referenced by Spec. This utility may be executed after a clean load of your program and after running the program. It searches for static predicates that have been called and (thus) have been examined for candidate indexes. If candidate indexes have not been materialized this implies that the predicate was never called with a nonvar value for the corresponding argument. Adding a mode/1 declaration may be used to inform the system thereof. The system will never examine arguments for indexing that have been declared as mode -.

Note: This predicate merely detects that some predicate is never called with instantiated specific arguments during this run. The user should verify whether the suggested - arguments are correct and typically complete the mode by changing ? into + (or -) where applicable. Currently, in SWI-Prolog, mode/1 declarations have no effect on the semantics of the code. In particular, a predicate that declares some argument as - may be called with this argument instantiated. This may change in the future.

Arguments:
Spec- uses the same conventions as jiti_list/1.
  240jiti_suggest_modes :-
  241    jiti_suggest_modes(_:_).
  242
  243jiti_suggest_modes(Partial) :-
  244    spec_head(Partial, Head),
  245    !,
  246    jiti_suggest_modes(Head).
  247jiti_suggest_modes(Head) :-
  248    Head = M:_,
  249    freeze(M, module_property(M, class(user))),
  250    findall(Head-Indexed,
  251            (   predicate_property(Head, indexed(Indexed)),
  252                \+ predicate_property(Head, imported_from(_))
  253            ), Pairs),
  254    convlist(suggest_mode, Pairs, Modes),
  255    (   Modes == []
  256    ->  print_message(informational, jiti(no_modes(Head)))
  257    ;   maplist(portray_clause, Modes)
  258    ).
  259
  260suggest_mode((M:Head)-Indexes, (:- mode(M:GenHead))) :-
  261    convlist(not_realised_index_arg, Indexes, FArgs),
  262    convlist(realised_index_arg, Indexes, ArgsL),
  263    append(ArgsL, Realised),
  264    sort(FArgs, Sargs),
  265    sort(Realised, RArgs),
  266    ord_subtract(Sargs, RArgs, Args),
  267    Args \== [],
  268    !,
  269    most_general_goal(Head, GenHead),
  270    make_mode(Args, GenHead).
  271
  272not_realised_index_arg(Index, Arg) :-
  273    _{ arguments:[Arg], position:[], realised:false } :< Index.
  274
  275realised_index_arg(Index, Args) :-
  276    _{ arguments:Args, position:[], realised:true } :< Index.
  277
  278make_mode([], GenHead) =>
  279    functor(GenHead, _, Arity),
  280    set_any(1, Arity, GenHead).
  281make_mode([H|T], GenHead) =>
  282    arg(H, GenHead, -),
  283    make_mode(T, GenHead).
  284
  285set_any(I, Arity, GenHead), arg(I, GenHead, Var) =>
  286    (   var(Var)
  287    ->  Var = '?'
  288    ;   true
  289    ),
  290    I2 is I+1,
  291    set_any(I2, Arity, GenHead).
  292set_any(_, _, _) =>
  293    true.
  294
  295
  296                /*******************************
  297                *      SPECIFY PREDICATES      *
  298                *******************************/
  299
  300spec_head(Module:Name/Arity, Head), atom(Name), integer(Arity) =>
  301    Head = Module:Head0,
  302    functor(Head0, Name, Arity).
  303spec_head(Module:Name/Arity, Head), atom(Name), var(Arity) =>
  304    Head = Module:Head0,
  305    freeze(Head0, functor(Head0, Name, _)).
  306spec_head(Module:Name, Head), atom(Name) =>
  307    Head = Module:Head0,
  308    freeze(Head0, functor(Head0, Name, _)).
  309spec_head(_, _) =>
  310    fail.
  311
  312                /*******************************
  313                *            OUTPUT            *
  314                *******************************/
  315
  316tty_width(W) :-
  317    catch(tty_size(_, TtyW), _, fail),
  318    !,
  319    W is max(65, TtyW).
  320tty_width(80).
  321
  322                /*******************************
  323                *           MESSAGES           *
  324                *******************************/
  325
  326:- multifile prolog:message//1.  327
  328prolog:message(jiti(no_modes(M:Head))) -->
  329    { var(Head) },
  330    [ 'No mode suggestions for predicates in module ~p'-[M] ].
  331prolog:message(jiti(no_modes(Head))) -->
  332    { numbervars(Head, 0, _, [singletons(true)]) },
  333    [ 'No mode suggestions for ~p'-[Head] ]