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-2010, University of Amsterdam, VU University Amsterdam
    7    All rights reserved.
    8
    9    Redistribution and use in source and binary forms, with or without
   10    modification, are permitted provided that the following conditions
   11    are met:
   12
   13    1. Redistributions of source code must retain the above copyright
   14       notice, this list of conditions and the following disclaimer.
   15
   16    2. Redistributions in binary form must reproduce the above copyright
   17       notice, this list of conditions and the following disclaimer in
   18       the documentation and/or other materials provided with the
   19       distribution.
   20
   21    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   22    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   23    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   24    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   25    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   26    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   27    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   28    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   29    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   30    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   31    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   32    POSSIBILITY OF SUCH DAMAGE.
   33*/
   34
   35:- module(prolog_explain,
   36          [ explain/1,
   37            explain/2
   38          ]).   39:- use_module(library(helpidx)).   40:- use_module(library(lists)).   41:- use_module(library(apply)).

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
Write all information known about Term to the current output.
   68explain(Item) :-
   69    explain(Item, Explanation),
   70    writeln(Explanation),
   71    fail.
   72explain(_).
   73
   74                /********************************
   75                *           BASIC TYPES         *
   76                *********************************/
 explain(@Term, -Explanation) is nondet
Explanation describes information about Term.
   82explain(Var, Explanation) :-
   83    var(Var),
   84    !,
   85    utter(Explanation, '"~w" is an unbound variable', [Var]).
   86explain(I, Explanation) :-
   87    integer(I),
   88    !,
   89    utter(Explanation, '"~w" is an integer', [I]).
   90explain(F, Explanation) :-
   91    float(F),
   92    !,
   93    utter(Explanation, '"~w" is a floating point number', [F]).
   94explain(S, Explanation) :-
   95    string(S),
   96    !,
   97    utter(Explanation, '"~w" is a string', S).
   98explain([], Explanation) :-
   99    !,
  100    utter(Explanation, '"[]" is a special constant denoting an empty list', []).
  101explain(A, Explanation) :-
  102    atom(A),
  103    utter(Explanation, '"~w" is an atom', [A]).
  104explain(A, Explanation) :-
  105    atom(A),
  106    current_op(Pri, F, A),
  107    op_type(F, Type),
  108    utter(Explanation, '"~w" is a ~w (~w) operator of priority ~d',
  109          [A, Type, F, Pri]).
  110explain(A, Explanation) :-
  111    atom(A),
  112    !,
  113    explain_atom(A, Explanation).
  114explain([H|T], Explanation) :-
  115    is_list(T),
  116    !,
  117    List = [H|T],
  118    length(List, L),
  119    (   utter(Explanation, '"~p" is a proper list with ~d elements',
  120              [List, L])
  121    ;   maplist(printable, List),
  122        utter(Explanation, '~t~8|Text is "~s"',  [List])
  123    ).
  124explain([H|T], Explanation) :-
  125    !,
  126    length([H|T], L),
  127    !,
  128    utter(Explanation, '"~p" is a not-closed list with ~d elements',
  129          [[H|T], L]).
  130explain(Name/Arity, Explanation) :-
  131    atom(Name),
  132    integer(Arity),
  133    !,
  134    functor(Head, Name, Arity),
  135    known_predicate(Module:Head),
  136    (   Module == system
  137    ->  true
  138    ;   \+ predicate_property(Module:Head, imported_from(_))
  139    ),
  140    explain_predicate(Module:Head, Explanation).
  141explain(Module:Name/Arity, Explanation) :-
  142    atom(Module), atom(Name), integer(Arity),
  143    !,
  144    functor(Head, Name, Arity),
  145    explain_predicate(Module:Head, Explanation).
  146explain(Module:Head, Explanation) :-
  147    callable(Head),
  148    !,
  149    explain_predicate(Module:Head, Explanation).
  150explain(Term, Explanation) :-
  151    numbervars(Term, 0, _, [singletons(true)]),
  152    utter(Explanation, '"~W" is a compound term',
  153          [Term, [quoted(true), numbervars(true)]]).
  154explain(Term, Explanation) :-
  155    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.
  163known_predicate(Pred) :-
  164    current_predicate(_, Pred),
  165    !.
  166known_predicate(Pred) :-
  167    predicate_property(Pred, undefined).
  168known_predicate(_:Head) :-
  169    functor(Head, Name, Arity),
  170    '$in_library'(Name, Arity, _Path).
  171
  172op_type(X, prefix) :-
  173    atom_chars(X, [f, _]).
  174op_type(X, infix) :-
  175    atom_chars(X, [_, f, _]).
  176op_type(X, postfix) :-
  177    atom_chars(X, [_, f]).
  178
  179printable(C) :-
  180    integer(C),
  181    between(32, 126, C).
  182
  183                /********************************
  184                *             ATOMS             *
  185                *********************************/
  186
  187explain_atom(A, Explanation) :-
  188    referenced(A, Explanation).
  189explain_atom(A, Explanation) :-
  190    current_predicate(A, Module:Head),
  191    (   Module == system
  192    ->  true
  193    ;   \+ predicate_property(Module:Head, imported_from(_))
  194    ),
  195    explain_predicate(Module:Head, Explanation).
  196explain_atom(A, Explanation) :-
  197    predicate_property(Module:Head, undefined),
  198    functor(Head, A, _),
  199    explain_predicate(Module:Head, Explanation).
  200
  201
  202                /********************************
  203                *            FUNCTOR             *
  204                *********************************/
  205
  206explain_functor(Head, Explanation) :-
  207    referenced(Head, Explanation).
  208explain_functor(Head, Explanation) :-
  209    current_predicate(_, Module:Head),
  210    \+ predicate_property(Module:Head, imported_from(_)),
  211    explain_predicate(Module:Head, Explanation).
  212explain_functor(Head, Explanation) :-
  213    predicate_property(M:Head, undefined),
  214    (   functor(Head, N, A),
  215        utter(Explanation,
  216              '~w:~w/~d is an undefined predicate', [M,N,A])
  217    ;   referenced(M:Head, Explanation)
  218    ).
  219
  220
  221                /********************************
  222                *           PREDICATE           *
  223                *********************************/
  224
  225lproperty(built_in,     ' built-in', []).
  226lproperty(dynamic,      ' dynamic', []).
  227lproperty(multifile,    ' multifile', []).
  228lproperty(transparent,  ' meta', []).
  229
  230tproperty(imported_from(Module), ' imported from module ~w', [Module]).
  231tproperty(file(File),           ' defined in~n~t~8|~w', [File]).
  232tproperty(line_count(Number),   ':~d', [Number]).
  233tproperty(autoload,             ' that can be autoloaded', []).
  234
  235combine_utterances(Pairs, Explanation) :-
  236    maplist(first, Pairs, Fmts),
  237    atomic_list_concat(Fmts, Format),
  238    maplist(second, Pairs, ArgList),
  239    flatten(ArgList, Args),
  240    utter(Explanation, Format, Args).
  241
  242first(A-_B, A).
  243second(_A-B, B).
 explain_predicate(:Head, -Explanation) is det
  247explain_predicate(Pred, Explanation) :-
  248    Pred = Module:Head,
  249    functor(Head, Name, Arity),
  250
  251    (   predicate_property(Pred, undefined)
  252    ->  utter(Explanation,
  253              '~w:~w/~d is an undefined predicate', [Module,Name,Arity])
  254    ;   (   var(Module)
  255        ->  U0 = '~w/~d is a' - [Name, Arity]
  256        ;   U0 = '~w:~w/~d is a' - [Module, Name, Arity]
  257        ),
  258        findall(Fmt-Arg, (lproperty(Prop, Fmt, Arg),
  259                          predicate_property(Pred, Prop)),
  260                U1),
  261        U2 = ' predicate' - [],
  262        findall(Fmt-Arg, (tproperty(Prop, Fmt, Arg),
  263                          predicate_property(Pred, Prop)),
  264                U3),
  265        flatten([U0, U1, U2, U3], Utters),
  266        combine_utterances(Utters, Explanation)
  267    ).
  268explain_predicate(Pred, Explanation) :-
  269    predicate_property(Pred, built_in),
  270    Pred = _Module:Head,
  271    functor(Head, Name, Arity),
  272    predicate(Name, Arity, Summary, _, _),
  273    utter(Explanation, '~t~8|Summary: ``~w''''', [Summary]).
  274explain_predicate(Pred, Explanation) :-
  275    referenced(Pred, Explanation).
  276
  277                /********************************
  278                *          REFERENCES           *
  279                *********************************/
  280
  281referenced(Term, Explanation) :-
  282    current_predicate(_, Module:Head),
  283    (   predicate_property(Module:Head, built_in)
  284    ->  current_prolog_flag(access_level, system)
  285    ;   true
  286    ),
  287    \+ predicate_property(Module:Head, imported_from(_)),
  288    Module:Head \= help_index:predicate(_,_,_,_,_),
  289    nth_clause(Module:Head, N, Ref),
  290    '$xr_member'(Ref, Term),
  291    utter_referenced(Module:Head, N, Ref,
  292                     'Referenced', Explanation).
  293referenced(_:Head, Explanation) :-
  294    current_predicate(_, Module:Head),
  295    (   predicate_property(Module:Head, built_in)
  296    ->  current_prolog_flag(access_level, system)
  297    ;   true
  298    ),
  299    \+ predicate_property(Module:Head, imported_from(_)),
  300    nth_clause(Module:Head, N, Ref),
  301    '$xr_member'(Ref, Head),
  302    utter_referenced(Module:Head, N, Ref,
  303                     'Possibly referenced', Explanation).
  304
  305utter_referenced(_Module:class(_,_,_,_,_,_), _, _, _, _) :-
  306    current_prolog_flag(xpce, true),
  307    !,
  308    fail.
  309utter_referenced(_Module:lazy_send_method(_,_,_), _, _, _, _) :-
  310    current_prolog_flag(xpce, true),
  311    !,
  312    fail.
  313utter_referenced(_Module:lazy_get_method(_,_,_), _, _, _, _) :-
  314    current_prolog_flag(xpce, true),
  315    !,
  316    fail.
  317utter_referenced(pce_xref:exported(_,_), _, _, _, _) :-
  318    !,
  319    fail.
  320utter_referenced(pce_xref:defined(_,_,_), _, _, _, _) :-
  321    !,
  322    fail.
  323utter_referenced(pce_xref:called(_,_,_), _, _, _, _) :-
  324    !,
  325    fail.
  326utter_referenced(pce_principal:send_implementation(_, _, _),
  327                 _, Ref, Text, Explanation) :-
  328    current_prolog_flag(xpce, true),
  329    !,
  330    xpce_method_id(Ref, Id),
  331    utter(Explanation, '~t~8|~w from ~w', [Text, Id]).
  332utter_referenced(pce_principal:get_implementation(Id, _, _, _),
  333                 _, Ref, Text, Explanation) :-
  334    current_prolog_flag(xpce, true),
  335    !,
  336    xpce_method_id(Ref, Id),
  337    utter(Explanation, '~t~8|~w from ~w', [Text, Id]).
  338utter_referenced(Module:Head, N, _Ref, Text, Explanation) :-
  339    functor(Head, Name, Arity),
  340    utter(Explanation,
  341          '~t~8|~w from ~d-th clause of ~w:~w/~d',
  342          [Text, N, Module, Name, Arity]).
  343
  344xpce_method_id(Ref, Id) :-
  345    clause(Head, _Body, Ref),
  346    strip_module(Head, _, H),
  347    arg(1, H, Id).
  348
  349
  350
  351                /********************************
  352                *             UTTER            *
  353                *********************************/
  354
  355utter(Explanation, Fmt, Args) :-
  356    format(string(Explanation), Fmt, Args)