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)  1985-2018, 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_explain,
   37          [ explain/1,
   38            explain/2
   39          ]).   40:- if(exists_source(library(pldoc/man_index))).   41:- use_module(library(pldoc/man_index)).   42:- elif(exists_source(library(helpidx))).   43:- use_module(library(helpidx)).   44:- endif.   45:- use_module(library(lists)).   46:- use_module(library(apply)).   47
   48/** <module> Describe Prolog Terms
   49
   50The   library(explain)   describes   prolog-terms.   The   most   useful
   51functionality is its cross-referencing function.
   52
   53==
   54?- explain(subset(_,_)).
   55"subset(_, _)" is a compound term
   56        Referenced from 2-th clause of lists:subset/2
   57        Referenced from 46-th clause of prolog_xref:imported/3
   58        Referenced from 68-th clause of prolog_xref:imported/3
   59lists:subset/2 is a predicate defined in
   60        /staff/jan/lib/pl-5.6.17/library/lists.pl:307
   61        Referenced from 2-th clause of lists:subset/2
   62        Possibly referenced from 2-th clause of lists:subset/2
   63==
   64
   65Note  that  the  help-tool  for   XPCE    provides   a   nice  graphical
   66cross-referencer.
   67*/
   68
   69%!  explain(@Term) is det
   70%
   71%   Give an explanation on Term. The  argument   may  be any Prolog data
   72%   object. If the argument is an atom,  a term of the form `Name/Arity`
   73%   or a term of the form   `Module:Name/Arity`, explain/1 describes the
   74%   predicate as well as possible references to it. See also gxref/0.
   75
   76explain(Item) :-
   77    explain(Item, Explanation),
   78    writeln(Explanation),
   79    fail.
   80explain(_).
   81
   82                /********************************
   83                *           BASIC TYPES         *
   84                *********************************/
   85
   86%!  explain(@Term, -Explanation) is nondet.
   87%
   88%   True when Explanation is an explanation of Term.
   89
   90explain(Var, Explanation) :-
   91    var(Var),
   92    !,
   93    utter(Explanation, '"~w" is an unbound variable', [Var]).
   94explain(I, Explanation) :-
   95    integer(I),
   96    !,
   97    utter(Explanation, '"~w" is an integer', [I]).
   98explain(F, Explanation) :-
   99    float(F),
  100    !,
  101    utter(Explanation, '"~w" is a floating point number', [F]).
  102explain(S, Explanation) :-
  103    string(S),
  104    !,
  105    utter(Explanation, '"~w" is a string', S).
  106explain([], Explanation) :-
  107    !,
  108    utter(Explanation, '"[]" is a special constant denoting an empty list', []).
  109explain(A, Explanation) :-
  110    atom(A),
  111    utter(Explanation, '"~w" is an atom', [A]).
  112explain(A, Explanation) :-
  113    atom(A),
  114    current_op(Pri, F, A),
  115    op_type(F, Type),
  116    utter(Explanation, '"~w" is a ~w (~w) operator of priority ~d',
  117          [A, Type, F, Pri]).
  118explain(A, Explanation) :-
  119    atom(A),
  120    !,
  121    explain_atom(A, Explanation).
  122explain([H|T], Explanation) :-
  123    is_list(T),
  124    !,
  125    List = [H|T],
  126    length(List, L),
  127    (   utter(Explanation, '"~p" is a proper list with ~d elements',
  128              [List, L])
  129    ;   maplist(printable, List),
  130        utter(Explanation, '~t~8|Text is "~s"',  [List])
  131    ).
  132explain([H|T], Explanation) :-
  133    !,
  134    length([H|T], L),
  135    !,
  136    utter(Explanation, '"~p" is a not-closed list with ~d elements',
  137          [[H|T], L]).
  138explain(Name/Arity, Explanation) :-
  139    atom(Name),
  140    integer(Arity),
  141    !,
  142    functor(Head, Name, Arity),
  143    known_predicate(Module:Head),
  144    (   Module == system
  145    ->  true
  146    ;   \+ predicate_property(Module:Head, imported_from(_))
  147    ),
  148    explain_predicate(Module:Head, Explanation).
  149explain(Module:Name/Arity, Explanation) :-
  150    atom(Module), atom(Name), integer(Arity),
  151    !,
  152    functor(Head, Name, Arity),
  153    explain_predicate(Module:Head, Explanation).
  154explain(Module:Head, Explanation) :-
  155    callable(Head),
  156    !,
  157    explain_predicate(Module:Head, Explanation).
  158explain(Term, Explanation) :-
  159    numbervars(Term, 0, _, [singletons(true)]),
  160    utter(Explanation, '"~W" is a compound term',
  161          [Term, [quoted(true), numbervars(true)]]).
  162explain(Term, Explanation) :-
  163    explain_functor(Term, Explanation).
  164
  165%!  known_predicate(:Head)
  166%
  167%   Succeeds if we know anything about this predicate.  Undefined
  168%   predicates are considered `known' for this purpose, so we can
  169%   provide referenced messages on them.
  170
  171known_predicate(M:Head) :-
  172    var(M),
  173    current_predicate(_, M2:Head),
  174    (   predicate_property(M2:Head, imported_from(M))
  175    ->  true
  176    ;   M = M2
  177    ),
  178    !.
  179known_predicate(Pred) :-
  180    predicate_property(Pred, undefined).
  181known_predicate(_:Head) :-
  182    functor(Head, Name, Arity),
  183    '$in_library'(Name, Arity, _Path).
  184
  185op_type(X, prefix) :-
  186    atom_chars(X, [f, _]).
  187op_type(X, infix) :-
  188    atom_chars(X, [_, f, _]).
  189op_type(X, postfix) :-
  190    atom_chars(X, [_, f]).
  191
  192printable(C) :-
  193    integer(C),
  194    between(32, 126, C).
  195
  196                /********************************
  197                *             ATOMS             *
  198                *********************************/
  199
  200explain_atom(A, Explanation) :-
  201    referenced(A, Explanation).
  202explain_atom(A, Explanation) :-
  203    current_predicate(A, Module:Head),
  204    (   Module == system
  205    ->  true
  206    ;   \+ predicate_property(Module:Head, imported_from(_))
  207    ),
  208    explain_predicate(Module:Head, Explanation).
  209explain_atom(A, Explanation) :-
  210    predicate_property(Module:Head, undefined),
  211    functor(Head, A, _),
  212    explain_predicate(Module:Head, Explanation).
  213
  214
  215                /********************************
  216                *            FUNCTOR             *
  217                *********************************/
  218
  219explain_functor(Head, Explanation) :-
  220    referenced(Head, Explanation).
  221explain_functor(Head, Explanation) :-
  222    current_predicate(_, Module:Head),
  223    \+ predicate_property(Module:Head, imported_from(_)),
  224    explain_predicate(Module:Head, Explanation).
  225explain_functor(Head, Explanation) :-
  226    predicate_property(M:Head, undefined),
  227    (   functor(Head, N, A),
  228        utter(Explanation,
  229              '~w:~w/~d is an undefined predicate', [M,N,A])
  230    ;   referenced(M:Head, Explanation)
  231    ).
  232
  233
  234                /********************************
  235                *           PREDICATE           *
  236                *********************************/
  237
  238lproperty(built_in,     ' built-in', []).
  239lproperty(dynamic,      ' dynamic', []).
  240lproperty(multifile,    ' multifile', []).
  241lproperty(transparent,  ' meta', []).
  242
  243tproperty(imported_from(Module), ' imported from module ~w', [Module]).
  244tproperty(file(File),           ' defined in~n~t~8|~w', [File]).
  245tproperty(line_count(Number),   ':~d', [Number]).
  246tproperty(autoload,             ' that can be autoloaded', []).
  247
  248combine_utterances(Pairs, Explanation) :-
  249    maplist(first, Pairs, Fmts),
  250    atomic_list_concat(Fmts, Format),
  251    maplist(second, Pairs, ArgList),
  252    flatten(ArgList, Args),
  253    utter(Explanation, Format, Args).
  254
  255first(A-_B, A).
  256second(_A-B, B).
  257
  258%!  explain_predicate(:Head, -Explanation) is det.
  259
  260explain_predicate(Pred, Explanation) :-
  261    Pred = Module:Head,
  262    functor(Head, Name, Arity),
  263
  264    (   predicate_property(Pred, undefined)
  265    ->  utter(Explanation,
  266              '~w:~w/~d is an undefined predicate', [Module,Name,Arity])
  267    ;   (   var(Module)
  268        ->  U0 = '~w/~d is a' - [Name, Arity]
  269        ;   U0 = '~w:~w/~d is a' - [Module, Name, Arity]
  270        ),
  271        findall(Fmt-Arg, (lproperty(Prop, Fmt, Arg),
  272                          predicate_property(Pred, Prop)),
  273                U1),
  274        U2 = ' predicate' - [],
  275        findall(Fmt-Arg, (tproperty(Prop, Fmt, Arg),
  276                          predicate_property(Pred, Prop)),
  277                U3),
  278        flatten([U0, U1, U2, U3], Utters),
  279        combine_utterances(Utters, Explanation)
  280    ).
  281:- if(current_predicate(man_object_property/2)).  282explain_predicate(Pred, Explanation) :-
  283    Pred = _Module:Head,
  284    functor(Head, Name, Arity),
  285    man_object_property(Name/Arity, summary(Summary)),
  286    source_file(Pred, File),
  287    current_prolog_flag(home, Home),
  288    sub_atom(File, 0, _, _, Home),
  289    utter(Explanation, '~t~8|Summary: ``~w''''', [Summary]).
  290:- elif(current_predicate(predicate/5)).  291explain_predicate(Pred, Explanation) :-
  292    predicate_property(Pred, built_in),
  293    Pred = _Module:Head,
  294    functor(Head, Name, Arity),
  295    predicate(Name, Arity, Summary, _, _),
  296    utter(Explanation, '~t~8|Summary: ``~w''''', [Summary]).
  297:- endif.  298explain_predicate(Pred, Explanation) :-
  299    referenced(Pred, Explanation).
  300
  301                /********************************
  302                *          REFERENCES           *
  303                *********************************/
  304
  305referenced(Term, Explanation) :-
  306    current_predicate(_, Module:Head),
  307    (   predicate_property(Module:Head, built_in)
  308    ->  current_prolog_flag(access_level, system)
  309    ;   true
  310    ),
  311    \+ predicate_property(Module:Head, imported_from(_)),
  312    Module:Head \= help_index:predicate(_,_,_,_,_),
  313    nth_clause(Module:Head, N, Ref),
  314    '$xr_member'(Ref, Term),
  315    utter_referenced(Module:Head, N, Ref,
  316                     'Referenced', Explanation).
  317referenced(_:Head, Explanation) :-
  318    current_predicate(_, Module:Head),
  319    (   predicate_property(Module:Head, built_in)
  320    ->  current_prolog_flag(access_level, system)
  321    ;   true
  322    ),
  323    \+ predicate_property(Module:Head, imported_from(_)),
  324    nth_clause(Module:Head, N, Ref),
  325    '$xr_member'(Ref, Head),
  326    utter_referenced(Module:Head, N, Ref,
  327                     'Possibly referenced', Explanation).
  328
  329utter_referenced(_Module:class(_,_,_,_,_,_), _, _, _, _) :-
  330    current_prolog_flag(xpce, true),
  331    !,
  332    fail.
  333utter_referenced(_Module:lazy_send_method(_,_,_), _, _, _, _) :-
  334    current_prolog_flag(xpce, true),
  335    !,
  336    fail.
  337utter_referenced(_Module:lazy_get_method(_,_,_), _, _, _, _) :-
  338    current_prolog_flag(xpce, true),
  339    !,
  340    fail.
  341utter_referenced(pce_xref:exported(_,_), _, _, _, _) :-
  342    !,
  343    fail.
  344utter_referenced(pce_xref:defined(_,_,_), _, _, _, _) :-
  345    !,
  346    fail.
  347utter_referenced(pce_xref:called(_,_,_), _, _, _, _) :-
  348    !,
  349    fail.
  350utter_referenced(pce_principal:send_implementation(_, _, _),
  351                 _, Ref, Text, Explanation) :-
  352    current_prolog_flag(xpce, true),
  353    !,
  354    xpce_method_id(Ref, Id),
  355    utter(Explanation, '~t~8|~w from ~w', [Text, Id]).
  356utter_referenced(pce_principal:get_implementation(Id, _, _, _),
  357                 _, Ref, Text, Explanation) :-
  358    current_prolog_flag(xpce, true),
  359    !,
  360    xpce_method_id(Ref, Id),
  361    utter(Explanation, '~t~8|~w from ~w', [Text, Id]).
  362utter_referenced(Module:Head, N, _Ref, Text, Explanation) :-
  363    functor(Head, Name, Arity),
  364    utter(Explanation,
  365          '~t~8|~w from ~d-th clause of ~w:~w/~d',
  366          [Text, N, Module, Name, Arity]).
  367
  368xpce_method_id(Ref, Id) :-
  369    clause(Head, _Body, Ref),
  370    strip_module(Head, _, H),
  371    arg(1, H, Id).
  372
  373
  374
  375                /********************************
  376                *             UTTER            *
  377                *********************************/
  378
  379utter(Explanation, Fmt, Args) :-
  380    format(string(Explanation), Fmt, Args)