View source with formatted 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/3]).   45:- autoload(library(ansi_term), [ansi_format/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(:).   55
   56/** <module> Just In Time Indexing (JITI) utilities
   57
   58This module provides utilities to   examine just-in-time indexes created
   59by the system and can help diagnosing space and performance issues.
   60
   61@tbd	Use print_message/2 and dynamically figure out the column width.
   62*/
   63
   64
   65%!  jiti_list is det.
   66%!  jiti_list(:Spec) is det.
   67%
   68%   List the JITI (Just In  Time   Indexes)  of selected predicates. The
   69%   predicate jiti_list/0 list all just-in-time  indexed predicates. The
   70%   predicate jiti_list/1 takes one of  the   patterns  below. All parts
   71%   except for Name  can  be  variables.   The  last  pattern  takes  an
   72%   arbitrary number of arguments.
   73%
   74%     - Module:Head
   75%     - Module:Name/Arity
   76%     - Module:Name
   77%
   78%   The columns use the following notation:
   79%
   80%     - The _Indexed_ column describes the argument(s) indexed:
   81%       - A plain integer refers to a 1-based argument number
   82%       - ``A+B`` is a multi-argument index on the arguments `A` and `B`.
   83%       - ``P:L`` is a deep-index `L` on sub-argument `P`.  For example,
   84%         ``1/2:2+3`` is an index of the 2nd and 3rd argument of the
   85%         2nd argument of a compound on the first argument of the predicate.
   86%         This implies `x` and `y` in the head p(f(_,g(_,x,y)))
   87%     - The `Buckets` specifies the number of buckets of the hash table
   88%     - The `Speedup` specifies the selectivity of the index
   89%     - The `Flags` describes additional properties, currently:
   90%       - ``L`` denotes that the index contains multiple compound
   91%         terms with the same name/arity that may be used to create
   92%         deep indexes.  The deep indexes themselves are created
   93%         as just-in-time indexes.
   94%       - ``V`` denotes the index is _virtual_, i.e., it has not yet
   95%         been materialized.
   96
   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(Head-Indexed,
  107            (   predicate_property(Head, indexed(Indexed)),
  108                \+ predicate_property(Head, imported_from(_))
  109            ), Pairs),
  110    PredColW is TTYW-41,
  111    TableWidth is TTYW-1,
  112    ansi_format(bold, 'Predicate~*|~w ~t~10+~w ~t~w~14+ ~t~w~9+ ~t~w~7+~n',
  113                [PredColW, '#Clauses', 'Index','Buckets','Speedup','Flags']),
  114    format('~`\u2015t~*|~n', [TableWidth]),
  115    maplist(print_indexes(PredColW), Pairs).
  116
  117print_indexes(PredColW, Head-List) :-
  118    foldl(print_index(PredColW, Head), List, 1, _).
  119
  120:- det(print_index/5).  121print_index(PredColW, QHead, Dict, N, N1) :-
  122    QHead = (M:Head),
  123    N1 is N+1,
  124    _{arguments:Args, position:Pos,
  125      buckets:Buckets, speedup:Speedup, list:List, realised:R} :< Dict,
  126    predicate_property(M:Head, number_of_clauses(CCount)),
  127    head_pi(QHead, PI),
  128    phrase(iarg_spec(Pos, Args), ArgsS),
  129    phrase(iflags(List, R), Flags),
  130    istyle(R, Style),
  131    CCountColZ is PredColW+8,
  132    (   N == 1
  133    ->  ansi_format(bold, '~q', [PI]),
  134        format(' ~t~D~*|  ', [CCount, CCountColZ])
  135    ;   format(' ~t~*|  ', [CCountColZ])
  136    ),
  137    ansi_format(Style, '~|~s ~t~D~14+ ~t~1f~9+  ~s~n',
  138                [ArgsS,Buckets,Speedup,Flags]).
  139
  140iarg_spec([], [N]) ==>
  141    number(N).
  142iarg_spec([], List) ==>
  143    plus_list(List).
  144iarg_spec(Deep, Args) ==>
  145    deep_list(Deep),
  146    iarg_spec([], Args).
  147
  148plus_list([H|T]) -->
  149    number(H),
  150    (   {T==[]}
  151    ->  []
  152    ;   "+",
  153        plus_list(T)
  154    ).
  155
  156deep_list([Last]) -->
  157    !,
  158    number(Last),
  159    ":".
  160deep_list([H|T]) -->
  161    number(H),
  162    "/",
  163    deep_list(T).
  164
  165
  166iflags(true, R)  ==> "L", irealised(R).
  167iflags(false, R) ==> "", irealised(R).
  168
  169irealised(false) ==> "V".
  170irealised(true)  ==> "".
  171
  172istyle(true, code).
  173istyle(false, comment).
  174
  175head_pi(Head, PI) :-
  176    predicate_property(Head, non_terminal),
  177    !,
  178    pi_head(PI0, Head),
  179    dcg_pi(PI0, PI).
  180head_pi(Head, PI) :-
  181    pi_head(PI, Head).
  182
  183dcg_pi(M:Name/Arity, DCG) =>
  184    Arity2 is Arity-2,
  185    DCG = M:Name//Arity2.
  186dcg_pi(Name/Arity, DCG) =>
  187    Arity2 is Arity-2,
  188    DCG = Name//Arity2.
  189
  190
  191                /*******************************
  192                *            MODES             *
  193                *******************************/
  194
  195%!  jiti_suggest_modes is det.
  196%!  jiti_suggest_modes(:Spec) is det.
  197%
  198%   Propose modes for the predicates referenced   by  Spec. This utility
  199%   may be executed _after_ a  clean  load   of  your  program and after
  200%   running the program. It searches  for   static  predicates that have
  201%   been called and (thus) have been  examined for candidate indexes. If
  202%   candidate indexes have not been materialized   this implies that the
  203%   predicate was never called with a nonvar value for the corresponding
  204%   argument. Adding a mode/1 declaration  may   be  used  to inform the
  205%   system thereof. The system will never examine arguments for indexing
  206%   that have been declared as mode `-`.
  207%
  208%   __Note:__ This predicate merely detects that some predicate is never
  209%   called with instantiated specific arguments __during this run__. The
  210%   user should verify whether the suggested   `-` arguments are correct
  211%   and typically complete the mode by changing   `?`  into `+` (or `-`)
  212%   where applicable. Currently, in SWI-Prolog, mode/1 declarations have
  213%   no effect on the semantics of the   code. In particular, a predicate
  214%   that declares some argument as `-` may  be called with this argument
  215%   instantiated. This may change in the future.
  216%
  217%   @arg Spec uses the same conventions as jiti_list/1.
  218
  219jiti_suggest_modes :-
  220    jiti_suggest_modes(_:_).
  221
  222jiti_suggest_modes(Partial) :-
  223    spec_head(Partial, Head),
  224    !,
  225    jiti_suggest_modes(Head).
  226jiti_suggest_modes(Head) :-
  227    Head = M:_,
  228    freeze(M, module_property(M, class(user))),
  229    findall(Head-Indexed,
  230            (   predicate_property(Head, indexed(Indexed)),
  231                \+ predicate_property(Head, imported_from(_))
  232            ), Pairs),
  233    convlist(suggest_mode, Pairs, Modes),
  234    (   Modes == []
  235    ->  print_message(informational, jiti(no_modes(Head)))
  236    ;   maplist(portray_clause, Modes)
  237    ).
  238
  239suggest_mode((M:Head)-Indexes, (:- mode(M:GenHead))) :-
  240    convlist(not_realised_index_arg, Indexes, FArgs),
  241    convlist(realised_index_arg, Indexes, ArgsL),
  242    append(ArgsL, Realised),
  243    sort(FArgs, Sargs),
  244    sort(Realised, RArgs),
  245    ord_subtract(Sargs, RArgs, Args),
  246    Args \== [],
  247    !,
  248    most_general_goal(Head, GenHead),
  249    make_mode(Args, GenHead).
  250
  251not_realised_index_arg(Index, Arg) :-
  252    _{ arguments:[Arg], position:[], realised:false } :< Index.
  253
  254realised_index_arg(Index, Args) :-
  255    _{ arguments:Args, position:[], realised:true } :< Index.
  256
  257make_mode([], GenHead) =>
  258    functor(GenHead, _, Arity),
  259    set_any(1, Arity, GenHead).
  260make_mode([H|T], GenHead) =>
  261    arg(H, GenHead, -),
  262    make_mode(T, GenHead).
  263
  264set_any(I, Arity, GenHead), arg(I, GenHead, Var) =>
  265    (   var(Var)
  266    ->  Var = '?'
  267    ;   true
  268    ),
  269    I2 is I+1,
  270    set_any(I2, Arity, GenHead).
  271set_any(_, _, _) =>
  272    true.
  273
  274
  275                /*******************************
  276                *      SPECIFY PREDICATES      *
  277                *******************************/
  278
  279spec_head(Module:Name/Arity, Head), atom(Name), integer(Arity) =>
  280    Head = Module:Head0,
  281    functor(Head0, Name, Arity).
  282spec_head(Module:Name/Arity, Head), atom(Name), var(Arity) =>
  283    Head = Module:Head0,
  284    freeze(Head0, functor(Head0, Name, _)).
  285spec_head(Module:Name, Head), atom(Name) =>
  286    Head = Module:Head0,
  287    freeze(Head0, functor(Head0, Name, _)).
  288spec_head(_, _) =>
  289    fail.
  290
  291                /*******************************
  292                *            OUTPUT            *
  293                *******************************/
  294
  295tty_width(W) :-
  296    catch(tty_size(_, TtyW), _, fail),
  297    !,
  298    W is max(65, TtyW).
  299tty_width(80).
  300
  301                /*******************************
  302                *           MESSAGES           *
  303                *******************************/
  304
  305:- multifile prolog:message//1.  306
  307prolog:message(jiti(no_modes(M:Head))) -->
  308    { var(Head) },
  309    [ 'No mode suggestions for predicates in module ~p'-[M] ].
  310prolog:message(jiti(no_modes(Head))) -->
  311    { numbervars(Head, 0, _, [singletons(true)]) },
  312    [ 'No mode suggestions for ~p'-[Head] ]