View source with raw comments or as raw
    1/*  Part of XPCE --- The SWI-Prolog GUI toolkit
    2
    3    Author:        Jan Wielemaker and Anjo Anjewierden
    4    E-mail:        wielemak@science.uva.nl
    5    WWW:           http://www.swi-prolog.org/packages/xpce/
    6    Copyright (c)  1985-2007, University of 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(pce_portray_object,
   36        [ portray_object/1
   37        , portray_object/2
   38        ]).   39
   40
   41:- use_module(library(pce)).   42:- require([ maplist/3,
   43             memberchk/2
   44           ]).

Create Human readable XPCE object descriptions

Note: you may wish to incorporate portray_object/2 with the standard portray mechanism of your Prolog. In that case:

portray(Object) :-
        object(Object), !,
        portray_object(Object).

Sometimes the use of object references can be a new nuisance, in particular while writing and debugging PCE programs. Suppose you have done:

    new(@s, spatial(xref=x+w, yref=x+h/2, xref=x, yref=y+h))

then

    object(@s, S)
    S = spatial(@1234, @1235, @1236, @1237, @default, @default)

is not of much use. portray_object/2 makes life easier:

    portray_object(@s, S)
    S = spatial(xref=x+w, yref=x+h/2, xref=x, yref=y+h)

More or less expanding the arguments until they become readable. portray_object/3 uses rules which specify how each object will be portrayed. You can make private extensions to these rules if you like. */

 portray_class(Description, Term)
Term is a template which may contain object references which need to be portrayed recursively (indicated with the "p/" prefix):
portray_class(constraint(A, B, C), _, constraint(A, B, p/C)).

Which should not touch the first two arguments (A and B), but portrays C recursively.

   97vararg_class(Class) :-
   98    get(@pce, convert, Class, class, TheClass),
   99    get(TheClass, term_names, @nil).
  100
  101portray_class(+(A, B), +(p/A, p/B)).
  102portray_class(-(A, B), -(p/A, p/B)).
  103portray_class(*(A, B), *(p/A, p/B)).
  104portray_class(/(A, B), /(p/A, p/B)).
  105portray_class(=(A, B), =(p/A, p/B)).
  106portray_class(==(A, B), ==(p/A, p/B)).
  107portray_class(\==(A, B), \==(p/A, p/B)).
  108portray_class(if(A,B,C), if(p/A, p/B, p/C)).
  109portray_class(while(A,B), while(p/A, p/B)).
  110portray_class(when(A,B,C), when(p/A, p/B, p/C)).
  111portray_class(attribute(A, B), attribute(A, p/B)).
  112portray_class(constraint(A, B, C), constraint(A, B, p/C)).
  113portray_class(handler(A, B, C), handler(A, p/B, p/C)).
  114portray_class(identity(A, A), identity(A)).
  115portray_class(identity(A, B), identity(A, B)).
  116portray_class(line(A, B, C, D), line(A, B, C, D)).
  117portray_class(link(A, A, _), link(A)).
  118portray_class(link(A, B, C), link(A, B, p/C)).
  119portray_class(number(A), A).
  120portray_class(node(A), node(p/A)).
  121portray_class(text(A,B,C), text(p/A, B, C)).
  122portray_class(button(A,B), button(A, p/B)).
  123portray_class(real(A), A).
  124portray_class(type(Name, _, _, _), Name).
  125portray_class(spatial(A, B, C, D, @default, @default), spatial(p/A, p/B, p/C, p/D)).
  126portray_class(spatial(A, B, C, D, @nil, @nil), spatial(p/A, p/B, p/C, p/D)).
  127portray_class(spatial(A, B, C, D, E, F), spatial(p/A, p/B, p/C, p/D, p/E, p/F)).
  128portray_class(string(A), A).
  129portray_class(click_gesture(A, B, C, D, E, F),
  130              click_gesture(A, p/B, C, p/D, p/E, p/F)).
  131portray_class(handle(A,B,C,D), handle(p/A, p/B, C, D)).
  132portray_class(quote_function(X), quote_function(p/X)).
  133portray_class(Term, NewTerm) :-
  134    functor(Term, Functor, _),
  135    vararg_class(Functor),
  136    !,
  137    Term =.. [Functor|Arguments],
  138    maplist(tag_p, Arguments, NewArguments),
  139    NewTerm =.. [Functor|NewArguments].
  140portray_class(A, A).
  141
  142tag_p(X, p/X).
 global_object(+Ref)
Declare commonly known objects
  148global_object(@nil).
  149global_object(@default).
  150global_object(@arg1).
  151global_object(@arg2).
  152global_object(@arg3).
  153global_object(@arg4).
  154global_object(@arg5).
  155global_object(@arg6).
  156global_object(@arg7).
  157global_object(@arg8).
  158global_object(@arg9).
  159global_object(@arg10).
  160global_object(@receiver).
  161global_object(@event).
  162global_object(@pce).
  163global_object(@prolog).
  164global_object(@display).
  165global_object(@classes).
  166global_object(@cursor_names).
  167global_object(@event_tree).
  168global_object(@white_image).
  169global_object(@grey12_image).
  170global_object(@grey25_image).
  171global_object(@grey50_image).
  172global_object(@grey75_image).
  173global_object(@black_image).
  174global_object(@on).
  175global_object(@off).
 portray_object(@Object)
Prints the result of portray_object/2 on the display.
  181portray_object(Object) :-
  182    portray_object(Object, Term),
  183    print(Term), nl,
  184    !.
 portray_object(@Object, -Term)
Expands the object description of Object in a human readable form and returs this in Term. portray_object/2 uses the rules found under portray_class/2.
  193portray_object(Obj, Term) :-
  194    portray_object(Obj, Term, []).
  195
  196portray_object(@Object, @Object, _) :-
  197    global_object(@Object),
  198    !.
  199portray_object(Obj, '<recursive>'(Obj), Done) :-
  200    memberchk(Obj, Done),
  201    !.
  202portray_object(@Object, Term, Done) :-
  203    object(@Object, Description),
  204    portray_class(Description, Result),
  205    portray_description(Result, Term, [@Object|Done]),
  206    !.
  207portray_object(Term, Term, _).
  208
  209portray_description(Result, Term, Done) :-
  210    Result =.. Arguments,
  211    maplist(portray_argument(Done), Arguments, List),
  212    !,
  213    Term =.. List.
  214portray_description(Term, Term, _).
  215
  216portray_argument(Done, p/Object, Term) :-
  217    !,
  218    portray_object(Object, Term, Done).
  219portray_argument(_, Term, Term)