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//NTArity, Explanation) :-
  137    atom(Name),
  138    integer(NTArity),
  139    NTArity >= 0,
  140    !,
  141    Arity is NTArity + 2,
  142    explain(Name/Arity, Explanation).
  143explain(Name/Arity, Explanation) :-
  144    atom(Name),
  145    integer(Arity),
  146    Arity >= 0,
  147    !,
  148    functor(Head, Name, Arity),
  149    known_predicate(Module:Head),
  150    (   Module == system
  151    ->  true
  152    ;   \+ predicate_property(Module:Head, imported_from(_))
  153    ),
  154    explain_predicate(Module:Head, Explanation).
  155explain(Module:Name/Arity, Explanation) :-
  156    atom(Module), atom(Name), integer(Arity),
  157    !,
  158    functor(Head, Name, Arity),
  159    explain_predicate(Module:Head, Explanation).
  160explain(Module:Head, Explanation) :-
  161    callable(Head),
  162    !,
  163    explain_predicate(Module:Head, Explanation).
  164explain(Dict, Explanation) :-
  165    is_dict(Dict, Tag),
  166    !,
  167    Explanation = [isa(Dict, 'a dict with tag ~q'-[Tag]) ].
  168explain(Term, Explanation) :-
  169    compound(Term),
  170    compound_name_arity(Term, _Name, Arity),
  171    numbervars(Term, 0, _, [singletons(true)]),
  172    Explanation = [isa(Term, 'is a compound term with arity ~D'-[Arity])].
  173explain(Term, Explanation) :-
  174    explain_functor(Term, Explanation).
  175
  176%!  known_predicate(:Head)
  177%
  178%   Succeeds if we know anything about this predicate.  Undefined
  179%   predicates are considered `known' for this purpose, so we can
  180%   provide referenced messages on them.
  181
  182known_predicate(M:Head) :-
  183    var(M),
  184    current_predicate(_, M2:Head),
  185    (   predicate_property(M2:Head, imported_from(M))
  186    ->  true
  187    ;   M = M2
  188    ).
  189known_predicate(Pred) :-
  190    predicate_property(Pred, undefined).
  191known_predicate(_:Head) :-
  192    functor(Head, Name, Arity),
  193    '$in_library'(Name, Arity, _Path).
  194
  195op_type(X, prefix) :-
  196    atom_chars(X, [f, _]).
  197op_type(X, infix) :-
  198    atom_chars(X, [_, f, _]).
  199op_type(X, postfix) :-
  200    atom_chars(X, [_, f]).
  201
  202printable(C) :-
  203    integer(C),
  204    code_type(C, graph).
  205
  206
  207                /********************************
  208                *             ATOMS             *
  209                *********************************/
  210
  211explain_atom(A, Explanation) :-
  212    referenced(A, Explanation).
  213explain_atom(A, Explanation) :-
  214    current_predicate(A, Module:Head),
  215    (   Module == system
  216    ->  true
  217    ;   \+ predicate_property(Module:Head, imported_from(_))
  218    ),
  219    explain_predicate(Module:Head, Explanation).
  220explain_atom(A, Explanation) :-
  221    predicate_property(Module:Head, undefined),
  222    functor(Head, A, _),
  223    explain_predicate(Module:Head, Explanation).
  224
  225
  226                /********************************
  227                *            FUNCTOR             *
  228                *********************************/
  229
  230explain_functor(Head, Explanation) :-
  231    referenced(Head, Explanation).
  232explain_functor(Head, Explanation) :-
  233    current_predicate(_, Module:Head),
  234    \+ predicate_property(Module:Head, imported_from(_)),
  235    explain_predicate(Module:Head, Explanation).
  236explain_functor(Head, Explanation) :-
  237    predicate_property(M:Head, undefined),
  238    (   functor(Head, N, A),
  239        Explanation = [ pi(M:N/A), 'is an undefined predicate' ]
  240    ;   referenced(M:Head, Explanation)
  241    ).
  242
  243
  244                /********************************
  245                *           PREDICATE           *
  246                *********************************/
  247
  248lproperty(built_in,     [' built-in']).
  249lproperty(dynamic,      [' dynamic']).
  250lproperty(multifile,    [' multifile']).
  251lproperty(transparent,  [' meta']).
  252
  253tproperty(Pred, [' imported from module ', module(Module)]) :-
  254    predicate_property(Pred, imported(Module)).
  255tproperty(Pred, [' defined in ', url(File:Line)]) :-
  256    predicate_property(Pred, file(File)),
  257    predicate_property(Pred, line_count(Line)).
  258tproperty(Pred, [' that can be autoloaded']) :-
  259    predicate_property(Pred, autoload).
  260
  261%!  explain_predicate(:Head, -Explanation) is det.
  262
  263explain_predicate(Pred, Explanation) :-
  264    Pred = Module:Head,
  265    functor(Head, Name, Arity),
  266    (   predicate_property(Pred, non_terminal)
  267    ->  What = 'non-terminal'
  268    ;   What = 'predicate'
  269    ),
  270    (   predicate_property(Pred, undefined)
  271    ->  Explanation = [ pi(Module:Name/Arity),
  272                        ansi([bold,fg(default)], ' is an undefined ~w', [What])
  273                      ]
  274    ;   (   var(Module)
  275        ->  U0 = [ pi(Name/Arity),
  276                   ansi([bold,fg(default)], ' is a', [])
  277                 ]
  278        ;   U0 = [ pi(Module:Name/Arity),
  279                   ansi([bold,fg(default)], ' is a', [])
  280                 ]
  281        ),
  282        findall(Utter, (lproperty(Prop, Utter),
  283                        predicate_property(Pred, Prop)),
  284                U1),
  285        U2 = [ansi([bold,fg(default)], ' ~w', [What]) ],
  286        findall(Utter, tproperty(Pred, Utter),
  287                U3),
  288        flatten([U0, U1, U2, U3], Explanation)
  289    ).
  290:- if(current_predicate(man_object_property/2)).  291explain_predicate(Pred, Explanation) :-
  292    Pred = _Module:Head,
  293    functor(Head, Name, Arity),
  294    man_object_property(Name/Arity, summary(Summary)),
  295    source_file(Pred, File),
  296    current_prolog_flag(home, Home),
  297    sub_atom(File, 0, _, _, Home),
  298    Explanation = [indent, 'Summary: "~w"'-[Summary] ].
  299:- endif.  300explain_predicate(Pred, Explanation) :-
  301    referenced(Pred, Explanation).
  302
  303                /********************************
  304                *          REFERENCES           *
  305                *********************************/
  306
  307referenced(Term, Explanation) :-
  308    current_predicate(_, Module:Head),
  309    (   predicate_property(Module:Head, built_in)
  310    ->  current_prolog_flag(access_level, system)
  311    ;   true
  312    ),
  313    \+ predicate_property(Module:Head, imported_from(_)),
  314    Module:Head \= help_index:predicate(_,_,_,_,_),
  315    nth_clause(Module:Head, N, Ref),
  316    '$xr_member'(Ref, Term),
  317    utter_referenced(Module:Head, N, Ref,
  318                     'Referenced', Explanation).
  319referenced(_:Head, Explanation) :-
  320    current_predicate(_, Module:Head),
  321    (   predicate_property(Module:Head, built_in)
  322    ->  current_prolog_flag(access_level, system)
  323    ;   true
  324    ),
  325    \+ predicate_property(Module:Head, imported_from(_)),
  326    nth_clause(Module:Head, N, Ref),
  327    '$xr_member'(Ref, Head),
  328    utter_referenced(Module:Head, N, Ref,
  329                     'Possibly referenced', Explanation).
  330
  331utter_referenced(_Module:class(_,_,_,_,_,_), _, _, _, _) :-
  332    current_prolog_flag(xpce, true),
  333    !,
  334    fail.
  335utter_referenced(_Module:lazy_send_method(_,_,_), _, _, _, _) :-
  336    current_prolog_flag(xpce, true),
  337    !,
  338    fail.
  339utter_referenced(_Module:lazy_get_method(_,_,_), _, _, _, _) :-
  340    current_prolog_flag(xpce, true),
  341    !,
  342    fail.
  343utter_referenced(From, _, _, _, _) :-
  344    hide_reference(From),
  345    !,
  346    fail.
  347utter_referenced(pce_xref:defined(_,_,_), _, _, _, _) :-
  348    !,
  349    fail.
  350utter_referenced(pce_xref:called(_,_,_), _, _, _, _) :-
  351    !,
  352    fail.
  353utter_referenced(pce_principal:send_implementation(_, _, _),
  354                 _, Ref, Text, Explanation) :-
  355    current_prolog_flag(xpce, true),
  356    !,
  357    xpce_method_id(Ref, Id),
  358    Explanation = [indent, '~w from ~w'-[Text, Id]].
  359utter_referenced(pce_principal:get_implementation(Id, _, _, _),
  360                 _, Ref, Text, Explanation) :-
  361    current_prolog_flag(xpce, true),
  362    !,
  363    xpce_method_id(Ref, Id),
  364    Explanation = [indent, '~w from ~w'-[Text, Id]].
  365utter_referenced(Head, N, Ref, Text, Explanation) :-
  366    clause_property(Ref, file(File)),
  367    clause_property(Ref, line_count(Line)),
  368    !,
  369    pi_head(PI, Head),
  370    Explanation = [ indent,
  371                    '~w from ~d-th clause of '-[Text, N],
  372                    pi(PI), ' at ', url(File:Line)
  373                  ].
  374utter_referenced(Head, N, _Ref, Text, Explanation) :-
  375    pi_head(PI, Head),
  376    Explanation = [ indent,
  377                    '~w from ~d-th clause of '-[Text, N],
  378                    pi(PI)
  379                  ].
  380
  381xpce_method_id(Ref, Id) :-
  382    clause(Head, _Body, Ref),
  383    strip_module(Head, _, H),
  384    arg(1, H, Id).
  385
  386hide_reference(pce_xref:exported(_,_)).
  387hide_reference(pce_xref:defined(_,_,_)).
  388hide_reference(pce_xref:called(_,_,_)).
  389hide_reference(prolog_xref:called(_,_,_,_,_)).
  390hide_reference(prolog_xref:pred_mode(_,_,_)).
  391hide_reference(prolog_xref:exported(_,_)).
  392hide_reference(prolog_xref:dynamic(_,_,_)).
  393hide_reference(prolog_xref:imported(_,_,_)).
  394hide_reference(prolog_xref:pred_comment(_,_,_,_)).
  395hide_reference(_:'$mode'(_,_)).
  396hide_reference(_:'$pldoc'(_,_,_,_)).
  397hide_reference(prolog_manual_index:man_index(_,_,_,_,_)).
  398
  399
  400                /********************************
  401                *           MESSAGES            *
  402                *********************************/
  403
  404:- multifile
  405    prolog:message//1.  406
  407prolog:message(explain(Explanation)) -->
  408    report(Explanation).
  409
  410report(Explanation) -->
  411    { string(Explanation),
  412      !,
  413      split_string(Explanation, "\n", "", Lines)
  414    },
  415    lines(Lines).
  416report(Explanation) -->
  417    { is_list(Explanation) },
  418    report_list(Explanation).
  419
  420lines([]) -->
  421    [].
  422lines([H]) -->
  423    !,
  424    [ '~s'-[H] ].
  425lines([H|T]) -->
  426    [ '~s'-[H], nl ],
  427    lines(T).
  428
  429report_list([]) -->
  430    [].
  431report_list([H|T]) -->
  432    report1(H),
  433    report_list(T).
  434
  435report1(indent) -->
  436    !,
  437    [ '~t~6|'-[] ].
  438report1(String) -->
  439    { atomic(String) },
  440    [ '~w'-[String] ].
  441report1(Fmt-Args) -->
  442    !,
  443    [ Fmt-Args ].
  444report1(url(Location)) -->
  445    [ url(Location) ].
  446report1(url(URL, Label)) -->
  447    [ url(URL, Label) ].
  448report1(pi(PI)) -->
  449    { pi_nt(PI, NT) },
  450    [ ansi(code, '~q', [NT]) ].
  451report1(ansi(Style, Fmt, Args)) -->
  452    [ ansi(Style, Fmt, Args) ].
  453report1(isa(Obj, Fmt-Args)) -->
  454    !,
  455    [ ansi(code, '~p', [Obj]),
  456      ansi([bold,fg(default)], ' is ', []),
  457      ansi([bold,fg(default)], Fmt, Args)
  458    ].
  459report1(isa(Obj, Descr)) -->
  460    [ ansi(code, '~p', [Obj]),
  461      ansi([bold,fg(default)], ' is ~w', [Descr])
  462    ].
  463
  464pi_nt(Module:Name/Arity, NT),
  465    atom(Module), atom(Name), integer(Arity),
  466    Arity >= 2,
  467    functor(Head, Name, Arity),
  468    predicate_property(Module:Head, non_terminal) =>
  469    Arity2 is Arity - 2,
  470    NT = Module:Name//Arity2.
  471pi_nt(PI, NT) =>
  472    NT = PI