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)  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:- autoload(library(apply),[maplist/2,maplist/3]).   41:- autoload(library(lists),[flatten/2]).   42
   43:- if(exists_source(library(pldoc/man_index))).   44:- autoload(library(pldoc/man_index), [man_object_property/2]).   45:- endif.

Describe Prolog Terms

The library(explain) describes prolog-terms. The most useful functionality is its cross-referencing function.

?- explain(subset(_,_)).
"subset(_, _)" is a compound term
        Referenced from 2-th clause of lists:subset/2
        Referenced from 46-th clause of prolog_xref:imported/3
        Referenced from 68-th clause of prolog_xref:imported/3
lists:subset/2 is a predicate defined in
        /staff/jan/lib/pl-5.6.17/library/lists.pl:307
        Referenced from 2-th clause of lists:subset/2
        Possibly referenced from 2-th clause of lists:subset/2

Note that the help-tool for XPCE provides a nice graphical cross-referencer. */

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