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)  1985-2021, University of Amsterdam,
    7                              VU University 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_explain,
   38          [ explain/1,
   39            explain/2
   40          ]).   41:- autoload(library(apply),[maplist/2,maplist/3]).   42:- autoload(library(lists),[flatten/2]).   43:- autoload(library(prolog_code), [pi_head/2]).   44
   45:- if(exists_source(library(pldoc/man_index))).   46:- autoload(library(pldoc/man_index), [man_object_property/2]).   47:- endif.   48
   49/** <module> Describe Prolog Terms
   50
   51The   library(explain)   describes   prolog-terms.   The   most   useful
   52functionality is its cross-referencing function.
   53
   54```
   55?- explain(subset(_,_)).
   56"subset(_, _)" is a compound term
   57    from 2-th clause of lists:subset/2
   58    Referenced from 46-th clause of prolog_xref:imported/3
   59    Referenced from 68-th clause of prolog_xref:imported/3
   60lists:subset/2 is a predicate defined in
   61    /staff/jan/lib/pl-5.6.17/library/lists.pl:307
   62    Referenced from 2-th clause of lists:subset/2
   63    Possibly referenced from 2-th clause of lists:subset/2
   64```
   65
   66Note that PceEmacs can jump to definitions   and gxref/0 can be used for
   67an overview of dependencies.
   68*/
   69
   70%!  explain(@Term) is det
   71%
   72%   Give an explanation on Term. The  argument   may  be any Prolog data
   73%   object. If the argument is an atom,  a term of the form `Name/Arity`
   74%   or a term of the form   `Module:Name/Arity`, explain/1 describes the
   75%   predicate as well as possible references to it. See also gxref/0.
   76
   77explain(Item) :-
   78    explain(Item, Explanation),
   79    print_message(information, explain(Explanation)),
   80    fail.
   81explain(_).
   82
   83                /********************************
   84                *           BASIC TYPES         *
   85                *********************************/
   86
   87%!  explain(@Term, -Explanation) is nondet.
   88%
   89%   True when Explanation is an explanation of Term. The explaination is
   90%   a list of elements that  is printed using print_message(information,
   91%   explain(Explanation)).
   92
   93explain(Var, [isa(Var, 'unbound variable')]) :-
   94    var(Var),
   95    !.
   96explain(I, [isa(I, 'an integer')]) :-
   97    integer(I),
   98    !.
   99explain(F, [isa(F, 'a floating point number')]) :-
  100    float(F),
  101    !.
  102explain(Q, [isa(Q, 'a rational (Q) number')]) :-
  103    rational(Q),
  104    !.
  105explain(S, [isa(S, 'a string')]) :-
  106    string(S),
  107    !.
  108explain([], [isa([], 'a special constant denoting an empty list')]) :-
  109    !.
  110explain(A, [isa(A, 'an atom')]) :-
  111    atom(A).
  112explain(A, Explanation) :-
  113    atom(A),
  114    current_op(Pri, F, A),
  115    op_type(F, Type),
  116    Explanation = [ isa(A, 'a ~w (~w) operator of priority ~d'-[Type, F, Pri]) ].
  117explain(A, Explanation) :-
  118    atom(A),
  119    !,
  120    explain_atom(A, Explanation).
  121explain([H|T], Explanation) :-
  122    List = [H|T],
  123    is_list(T),
  124    !,
  125    length(List, L),
  126    (   Explanation = [ isa(List, 'a proper list with ~d elements'-[L]) ]
  127    ;   maplist(printable, List),
  128        Explanation = [ indent, 'Text is "~s"'-[List] ]
  129    ).
  130explain(List, Explanation) :-
  131    List = [_|_],
  132    !,
  133    length(List, L),
  134    !,
  135    Explanation = [isa(List, 'is a not-closed list with ~d elements'-[L])].
  136explain(Name/Arity, Explanation) :-
  137    atom(Name),
  138    integer(Arity),
  139    !,
  140    functor(Head, Name, Arity),
  141    known_predicate(Module:Head),
  142    (   Module == system
  143    ->  true
  144    ;   \+ predicate_property(Module:Head, imported_from(_))
  145    ),
  146    explain_predicate(Module:Head, Explanation).
  147explain(Module:Name/Arity, Explanation) :-
  148    atom(Module), atom(Name), integer(Arity),
  149    !,
  150    functor(Head, Name, Arity),
  151    explain_predicate(Module:Head, Explanation).
  152explain(Module:Head, Explanation) :-
  153    callable(Head),
  154    !,
  155    explain_predicate(Module:Head, Explanation).
  156explain(Dict, Explanation) :-
  157    is_dict(Dict, Tag),
  158    !,
  159    Explanation = [isa(Dict, 'a dict with tag ~q'-[Tag]) ].
  160explain(Term, Explanation) :-
  161    compound(Term),
  162    compound_name_arity(Term, _Name, Arity),
  163    numbervars(Term, 0, _, [singletons(true)]),
  164    Explanation = [isa(Term, 'is a compound term with arity ~D'-[Arity])].
  165explain(Term, Explanation) :-
  166    explain_functor(Term, Explanation).
  167
  168%!  known_predicate(:Head)
  169%
  170%   Succeeds if we know anything about this predicate.  Undefined
  171%   predicates are considered `known' for this purpose, so we can
  172%   provide referenced messages on them.
  173
  174known_predicate(M:Head) :-
  175    var(M),
  176    current_predicate(_, M2:Head),
  177    (   predicate_property(M2:Head, imported_from(M))
  178    ->  true
  179    ;   M = M2
  180    ),
  181    !.
  182known_predicate(Pred) :-
  183    predicate_property(Pred, undefined).
  184known_predicate(_:Head) :-
  185    functor(Head, Name, Arity),
  186    '$in_library'(Name, Arity, _Path).
  187
  188op_type(X, prefix) :-
  189    atom_chars(X, [f, _]).
  190op_type(X, infix) :-
  191    atom_chars(X, [_, f, _]).
  192op_type(X, postfix) :-
  193    atom_chars(X, [_, f]).
  194
  195printable(C) :-
  196    integer(C),
  197    code_type(C, graph).
  198
  199
  200                /********************************
  201                *             ATOMS             *
  202                *********************************/
  203
  204explain_atom(A, Explanation) :-
  205    referenced(A, Explanation).
  206explain_atom(A, Explanation) :-
  207    current_predicate(A, Module:Head),
  208    (   Module == system
  209    ->  true
  210    ;   \+ predicate_property(Module:Head, imported_from(_))
  211    ),
  212    explain_predicate(Module:Head, Explanation).
  213explain_atom(A, Explanation) :-
  214    predicate_property(Module:Head, undefined),
  215    functor(Head, A, _),
  216    explain_predicate(Module:Head, Explanation).
  217
  218
  219                /********************************
  220                *            FUNCTOR             *
  221                *********************************/
  222
  223explain_functor(Head, Explanation) :-
  224    referenced(Head, Explanation).
  225explain_functor(Head, Explanation) :-
  226    current_predicate(_, Module:Head),
  227    \+ predicate_property(Module:Head, imported_from(_)),
  228    explain_predicate(Module:Head, Explanation).
  229explain_functor(Head, Explanation) :-
  230    predicate_property(M:Head, undefined),
  231    (   functor(Head, N, A),
  232        Explanation = [ pi(M:N/A), 'is an undefined predicate' ]
  233    ;   referenced(M:Head, Explanation)
  234    ).
  235
  236
  237                /********************************
  238                *           PREDICATE           *
  239                *********************************/
  240
  241lproperty(built_in,     [' built-in']).
  242lproperty(dynamic,      [' dynamic']).
  243lproperty(multifile,    [' multifile']).
  244lproperty(transparent,  [' meta']).
  245
  246tproperty(Pred, [' imported from module ', module(Module)]) :-
  247    predicate_property(Pred, imported(Module)).
  248tproperty(Pred, [' defined in ', url(File:Line)]) :-
  249    predicate_property(Pred, file(File)),
  250    predicate_property(Pred, line_count(Line)).
  251tproperty(Pred, [' that can be autoloaded']) :-
  252    predicate_property(Pred, autoload).
  253
  254%!  explain_predicate(:Head, -Explanation) is det.
  255
  256explain_predicate(Pred, Explanation) :-
  257    Pred = Module:Head,
  258    functor(Head, Name, Arity),
  259    (   predicate_property(Pred, undefined)
  260    ->  Explanation = [ pi(Module:Name/Arity),
  261                        ansi([bold,fg(default)], ' is an undefined predicate', [])
  262                      ]
  263    ;   (   var(Module)
  264        ->  U0 = [ pi(Name/Arity),
  265                   ansi([bold,fg(default)], ' is a', [])
  266                 ]
  267        ;   U0 = [ pi(Module:Name/Arity),
  268                   ansi([bold,fg(default)], ' is a', [])
  269                 ]
  270        ),
  271        findall(Utter, (lproperty(Prop, Utter),
  272                        predicate_property(Pred, Prop)),
  273                U1),
  274        U2 = [ansi([bold,fg(default)], ' predicate', []) ],
  275        findall(Utter, tproperty(Pred, Utter),
  276                U3),
  277        flatten([U0, U1, U2, U3], Explanation)
  278    ).
  279:- if(current_predicate(man_object_property/2)).  280explain_predicate(Pred, Explanation) :-
  281    Pred = _Module:Head,
  282    functor(Head, Name, Arity),
  283    man_object_property(Name/Arity, summary(Summary)),
  284    source_file(Pred, File),
  285    current_prolog_flag(home, Home),
  286    sub_atom(File, 0, _, _, Home),
  287    Explanation = [indent, 'Summary: "~w"'-[Summary] ].
  288:- endif.  289explain_predicate(Pred, Explanation) :-
  290    referenced(Pred, Explanation).
  291
  292                /********************************
  293                *          REFERENCES           *
  294                *********************************/
  295
  296referenced(Term, Explanation) :-
  297    current_predicate(_, Module:Head),
  298    (   predicate_property(Module:Head, built_in)
  299    ->  current_prolog_flag(access_level, system)
  300    ;   true
  301    ),
  302    \+ predicate_property(Module:Head, imported_from(_)),
  303    Module:Head \= help_index:predicate(_,_,_,_,_),
  304    nth_clause(Module:Head, N, Ref),
  305    '$xr_member'(Ref, Term),
  306    utter_referenced(Module:Head, N, Ref,
  307                     'Referenced', Explanation).
  308referenced(_:Head, Explanation) :-
  309    current_predicate(_, Module:Head),
  310    (   predicate_property(Module:Head, built_in)
  311    ->  current_prolog_flag(access_level, system)
  312    ;   true
  313    ),
  314    \+ predicate_property(Module:Head, imported_from(_)),
  315    nth_clause(Module:Head, N, Ref),
  316    '$xr_member'(Ref, Head),
  317    utter_referenced(Module:Head, N, Ref,
  318                     'Possibly referenced', Explanation).
  319
  320utter_referenced(_Module:class(_,_,_,_,_,_), _, _, _, _) :-
  321    current_prolog_flag(xpce, true),
  322    !,
  323    fail.
  324utter_referenced(_Module:lazy_send_method(_,_,_), _, _, _, _) :-
  325    current_prolog_flag(xpce, true),
  326    !,
  327    fail.
  328utter_referenced(_Module:lazy_get_method(_,_,_), _, _, _, _) :-
  329    current_prolog_flag(xpce, true),
  330    !,
  331    fail.
  332utter_referenced(From, _, _, _, _) :-
  333    hide_reference(From),
  334    !,
  335    fail.
  336utter_referenced(pce_xref:defined(_,_,_), _, _, _, _) :-
  337    !,
  338    fail.
  339utter_referenced(pce_xref:called(_,_,_), _, _, _, _) :-
  340    !,
  341    fail.
  342utter_referenced(pce_principal:send_implementation(_, _, _),
  343                 _, Ref, Text, Explanation) :-
  344    current_prolog_flag(xpce, true),
  345    !,
  346    xpce_method_id(Ref, Id),
  347    Explanation = [indent, '~w from ~w'-[Text, Id]].
  348utter_referenced(pce_principal:get_implementation(Id, _, _, _),
  349                 _, Ref, Text, Explanation) :-
  350    current_prolog_flag(xpce, true),
  351    !,
  352    xpce_method_id(Ref, Id),
  353    Explanation = [indent, '~w from ~w'-[Text, Id]].
  354utter_referenced(Head, N, Ref, Text, Explanation) :-
  355    clause_property(Ref, file(File)),
  356    clause_property(Ref, line_count(Line)),
  357    !,
  358    pi_head(PI, Head),
  359    Explanation = [ indent,
  360                    '~w from ~d-th clause of '-[Text, N],
  361                    pi(PI), ' at ', url(File:Line)
  362                  ].
  363utter_referenced(Head, N, _Ref, Text, Explanation) :-
  364    pi_head(PI, Head),
  365    Explanation = [ indent,
  366                    '~w from ~d-th clause of '-[Text, N],
  367                    pi(PI)
  368                  ].
  369
  370xpce_method_id(Ref, Id) :-
  371    clause(Head, _Body, Ref),
  372    strip_module(Head, _, H),
  373    arg(1, H, Id).
  374
  375hide_reference(pce_xref:exported(_,_)).
  376hide_reference(pce_xref:defined(_,_,_)).
  377hide_reference(pce_xref:called(_,_,_)).
  378hide_reference(prolog_xref:called(_,_,_,_,_)).
  379hide_reference(prolog_xref:pred_mode(_,_,_)).
  380hide_reference(prolog_xref:exported(_,_)).
  381hide_reference(prolog_xref:dynamic(_,_,_)).
  382hide_reference(prolog_xref:imported(_,_,_)).
  383hide_reference(prolog_xref:pred_comment(_,_,_,_)).
  384hide_reference(_:'$mode'(_,_)).
  385hide_reference(_:'$pldoc'(_,_,_,_)).
  386hide_reference(prolog_manual_index:man_index(_,_,_,_,_)).
  387
  388
  389                /********************************
  390                *           MESSAGES            *
  391                *********************************/
  392
  393:- multifile
  394    prolog:message//1.  395
  396prolog:message(explain(Explanation)) -->
  397    report(Explanation).
  398
  399report(Explanation) -->
  400    { string(Explanation),
  401      !,
  402      split_string(Explanation, "\n", "", Lines)
  403    },
  404    lines(Lines).
  405report(Explanation) -->
  406    { is_list(Explanation) },
  407    report_list(Explanation).
  408
  409lines([]) -->
  410    [].
  411lines([H]) -->
  412    !,
  413    [ '~s'-[H] ].
  414lines([H|T]) -->
  415    [ '~s'-[H], nl ],
  416    lines(T).
  417
  418report_list([]) -->
  419    [].
  420report_list([H|T]) -->
  421    report1(H),
  422    report_list(T).
  423
  424report1(indent) -->
  425    !,
  426    [ '~t~6|'-[] ].
  427report1(String) -->
  428    { atomic(String) },
  429    [ '~w'-[String] ].
  430report1(Fmt-Args) -->
  431    !,
  432    [ Fmt-Args ].
  433report1(url(Location)) -->
  434    [ url(Location) ].
  435report1(url(URL, Label)) -->
  436    [ url(URL, Label) ].
  437report1(pi(PI)) -->
  438    [ ansi(code, '~q', [PI]) ].
  439report1(ansi(Style, Fmt, Args)) -->
  440    [ ansi(Style, Fmt, Args) ].
  441report1(isa(Obj, Fmt-Args)) -->
  442    !,
  443    [ ansi(code, '~p', [Obj]),
  444      ansi([bold,fg(default)], ' is ', []),
  445      ansi([bold,fg(default)], Fmt, Args)
  446    ].
  447report1(isa(Obj, Descr)) -->
  448    [ ansi(code, '~p', [Obj]),
  449      ansi([bold,fg(default)], ' is ~w', [Descr])
  450    ]