Programmers FAQ for XPCE

This is the Frequently Asked Questions list for XPCE. This list contains question about programming problems in XPCE.

PCE is an object-oriented library for the development of user interfaces, meant to be connected to symbolic languages.

The authors of XPCE are Anjo Anjewierden and Jan Wielemaker at the Department of Social Science Informatics, University of Amsterdam (SWI).

This is not the only FAQ list for XPCE. Another one is maintained by Jan Wielemaker and describes general things such as `What is XPCE?' and `How do I get XPCE for ...?'.

Maintainer's note: the questions at the beginning of each section are likely to be addressed to beginners (nomina sunt consequentia rerum :-).



Documentation

Which path through the documentation should a beginner follow?

Jan Wielemaker suggests the following path:

  1. XPCE Course Notes (about 50 pages)
  2. XPCE User Guide (about 100 pages)
  3. Examples (PceDraw, various other library routines depending on what type of application you want to make).
  4. Online manual for finding definitions.

(Up to Table of Contents)


Where can I ask questions about XPCE?

The best thing is to consult this FAQ, first, and to eventually send a message to the XPCE mailing list (xpce@swi.psy.uva.nl). XPCE is not Prolog, so it is better not to post on comp.lang.prolog.

(Up to Table of Contents)


Is it possible to have a single-user PC version of XPCE ?

> I'm a student of Computer Science at Universita' Degli Studi
> di Milano; I'd like to use xpce library for Windows
> How can I get it?

As yet, we don't have any student arrangements. There are three ways to run XPCE/SWI-Prolog. First is to make your university obtain for a licence. Second is to install Linux, for which there is a free version (anonymous ftp from our site) and third is to apply for a licence yourself, but I understand this is rather expensive for personal use. It is not unlikely there will be a student version of Quintus/XPCE in the future.

(Up to Table of Contents)


Is there an XPCE version which interfaces with Clisp?

> my supervisor has been insisting
> that there should be a version of xpce which would interface
> with clisp (he already uses it with SWI prolog), and I have
> either find one or prove that it doesn't exist...
> I know from your documentation that there are Lucid and
> Lispwork versions, has clisp ever been attempted and what would it
> take to develop an interface between them if we were to
> attempt it? (unlikely)

You're right that it doesn't exists. I know some people have expressed interrest in this, but sofar no people with sufficient Clisp knowledge or just not enough time to make the connection. I think that if clisp provides a documented foreign-language interface, it shouldn't be too hard, as most of the interface is written in Lisp and there are already two lisp bindings with Lisps with quite different features.

You could try the mailing list xpce@swi.psy.uva.nl (maybe someone has something or, with some support from your site wants to implement it). If you come across something, please inform me.

(Up to Table of Contents)


Is it possible to get the PostScript files of the documentation?

> We have purchesed XPCE for use with Quintus Prolog
> from AII Ltd in the UK. We have the manuals - but
> is it possible to have Postscript files for these
> from you? It would save us photocopying them...

All documentation is available using anonymous ftp to swi.psy.uva.nl, directory pub/xpce/doc.

(Up to Table of Contents)


Where can I get revisions, bug reports etc.? Is there a user group?

Revisions are generally announced on thexpce mailing list, to which you may subscribe by sending mail to xpce-request@swi.psy.uva.nl. The list itself is accesible as xpce@swi.psy.uva.nl. The mailing list may be used for communicating with other users although this is as yet no common practice.

Bug reports are not published at the moment. The ChangeLog available using anonymous ftp to swi.psy.uva.nl, directory pub/xpce/doc. It indicates fixes to the development version.

A programmer's FAQ (this FAQ) is available through WWW at:

http://www.stud.unit.no/~passani/FAQ.html

and is maintained by Luca Passani (University of Pisa, Italy).

(Up to Table of Contents)


What is the difference between XPCE and ProWindows 3.0?

XPCE is the academic product. ProWindows-3 is a commercial version of it. This implies it is generally the previous release with bugs fixed. So, XPCE offers more functionality and more bugs :-)

(Up to Table of Contents)


Would it be possible to take XPCE for SICStus and adapt it to Quintus?

Yes, but you'll have to write the interface yourself. This is not a lot of code, but requires good knowledge of C, XPCE and the foreign interface of Quintus. It requires Quintus 3.14 or later (due to bugs there).

(Up to Table of Contents)


What are the licencing conditions for XPCE for an academic institution?

A licence including the whole lot (sources, interfaces and SWI-Prolog) costs 500 ECU (about $600). This is `as-is' basis; you'll have to compile and install the system yourself. You can only use this system for `non-comercial' purposes, which implies you cannot sell products that include it. Documentation is only on-line and in PostScript format.

(Up to Table of Contents)


Is XPCE upward compatible with ProWindows 2.1?

No. It provides the same terminoligy, style and predicates though. Adapting source-code is generally not too hard, but it depends on the quality of your original code (of course). The AIIL version contains some ported libraries.

For short, the history is this:

| -ProWindows-3 (XPCE-4.7.2 | with fixes, AIIL) PCE-1.0 -- PCE 2.0 --- PCE 3.0 --- XPCE-4.0 --- XPCE-4.8.0 (Academic) (AA) (AA) (AA&JW) (JW) (JW) | |--------ProWindows-1 -- ProWindows-2 (Quintus) (Quintus) Where (AA) is Anjo Anjewierden (UvA) and JW is Jan Wielemaker (me, UvA). PCE-3 adds simple programming facilities; XPCE-4 moved to X11, integrated graphics and dialog windows and provided full OO programming facilities to the application programmer, an extensive Prolog library and fully integrated online manual system.

In general PW3 is *much* faster, poses hardly any limits on what you can achieve and allows you to write much shorter programs. It is far too much to explain in a few lines. You can ftp the documentation from this site (ftp.swi.psy.uva.nl:/pub/xpce/doc/...).

(Up to Table of Contents)


Can XPCE really work on such an heterogeneous system of different platforms?

> in search for a tool to build graphical user interfaces for
> our applications that will run on a variety of platforms we found XPCE
> (actually in the disguise of ProWindows offered by Quintus - the
> project I'm working in does application development using Prolog). Now
> other people got interested in the tool and the question is, which
> platforms are actually supported rigth now, will be soon or could be
> later... In my project we are looking at different UNIX platforms and
> OS/2, other groups want to support OS/2, DOS/Windows and MAC. As far
> as I know (from Quintus) our UNIX platforms are OK, and OS/2 PM will
> be available later this year. Also, DOS/Windows is supported. I don't
> know about MAC...
.

PowerMacs claim to run MS-Windows apps, so this should in theory work. There are no concrete plans for a native MAC version. If plans are really big it can be discussed. The XPCE machine interfaces to a (XPCE) defined `virtual windowing interface'. Implementations thereof currently exist for MS-Windows and X11. This bit is about 200 KB for X11 and 160 KB for MS-Windows and takes about a month for an experienced C programmer with relevant experience to implement. XPCE itself is strict ANSI C and should be easily ported. So it all depends on how much copies you want to have :-)

(Up to Table of Contents)


Do XPCE applications conform to the GUI standards defined for the various platforms (OSF/Motif style guide, CUA, and so on)?

No. XPCE defines it's own GUI standards, currently closely confirming OpenLook and a bit less closely Motif. You can run XPCE using any of its supporting styles on any platform it runs on. Applications are independent of the look-and-feel preferred by the user, as long as they use the high-level UI specification (it is also possible to do nitty-gritty low-level manipulations, but these may give strange results if the user switches UI preferences).

Future versions are supposed to conform much closer to established GUI standards. Motif will be the first supported in much more detail.

(Up to Table of Contents)


I'd like to know about XPCE further developments.

Here is Jan Wielemaker's ToDo list.

(Up to Table of Contents)


Runtime and related issues

How do I make stand-alone executables?

The methods described here apply to XPCE/SWI-Prolog. Many comments will also apply to other host-languages, but the details may be different.

Writing a shell-script.

If the program is small (i.e. loads quickly), just write a small shell-script that loads and starts the program. Using SWI-Prolog, this becomes:

#!/bin/sh xpce -g '[/usr/local/src/myprog],startmyprog' See SWI-Prolog command-line options for details. This is often a good choice, but requires your adience to have access to the XPCE development environment. It will automatically pick the most recent version of the system.

Create a compiled program.

You may compile your program into a self-starting script for XPCE/SWI-Prolog using the command:

% xpce -o myprog -c prologfile ... See SWI-Prolog command-line options for details. There are some limitations on what can be handled by the `-c' compiler option. Check the SWI-Prolog manual for details.

Create a saved-state.

Using save/1 or save_program/1 and friends, you can create a saved state of the process that can be started directly from the shell. SWI-Prolog saved states start quickly, but are completely non-portable accross different machine architectures.

The xpce executable is a saved-state!

If you decide to make a saved-state, make sure the connection to the X11 display is not opened before making the state. Opening the connection will distribute the XPCE process state over both the XPCE executable itself and the X11 server process, making it impossible to create a snapshot of it.

There is only a little hack to test that the display opened:

?- get(@display, slot, ws_ref, X). Which will yield `0' if the display is not opened and non-zero otherwise. To find out *when* the display is opened, use:

?- debugpce(display). which will cause xpce to print:

Opening display @display at the moment the display is opened.

Normally, you should just load the program before creating the saved state. Notably, you should not create any graphical objects using Prolog directives as this will request the associated resources and thus requires XPCE to open the connection to the X-server (that maintains the X11 resource database). Use the :- pce_global/2 directive for such cases, which will delay the creation of the object till the object is referred too.

(Up to Table of Contents)


Runtime licenses

Right now, there is no runtime generator for XPCE/SWI-Prolog. This -in principle- forces users of your program to buy an XPCE licence in order to run your program.

In the future we will create a runtime version of the library that will be fully compatible as far as running a developed application is concerned, but will lack essential features to use it as a development environment. We will grant licence-holders the right to distribute this runtime library free of royalties.

In the meanwhile, contact us if you have concrete plans and we will try to get to an acceptable solution. In most cases this will involve creating some sort of saved-state of the program.

(Up to Table of Contents)


General Programming issues

I'd like to know the best way for implementing a graph editor which must be consistent with the Prolog internal representation

> In my application (a graph editor, as far as you are concerned), I
> need to keep an exact correspondence between the graph and a set of
> Prolog facts. I have implemented it by associating a different Prolog
> predicate which asserts and/or retracts facts to each action aimed at
> manipulating the graph.
>
> Even though response to user events is still good, I suspect that
> it is a bad programming habit.
> Furthermore, if I keep implementing complex responses to user
> events this way, I'm afraid problems might eventually show up.
>
> A better approach might be to concentrate on the graphical part
> without bothering about the Prolog database. At the right moment, the
> application would take a walk through the user-produced graph and
> interactively assert the right facts by exploitation of the
> connections.

This is a complex issue. Surely the simplest implementation is where you see the relevant clauses of the Prolog database as a file (archive) you use to read (clauses --> graphical editor) and write (graphical editor --> new clauses). However, there are various cases in which this is not good enough. Suppose you have a set of clauses and you want to have multiple simultaneously operating editors that exploit diffent views on the same data. Using the read/write approach, this implies the user cannot use bot editors simultaneously to manipulate the database, but needs a lock/unlock schema. At lock, the contents of the other editors is invalidated and at unlock all editors need to be updated. This is unpleasant for the user and conflicts with the idea of neat direct manipulation. A better aproach is to define a database and a minimal set of predicates to manipulate this database. All user actions that affect the database are mapped into manipulations on this minimal set. Each editor watches the manipulations and updates its graphical representation accordingly. You can use various changes caching mechanisms here for speedup if necessary. This has been discussed in a paper for the UIST 89 by me and Anjo Anjewierden, which you can obtain here or from:

ftp://swi.psy.uva.nl/pub/xpce/doc/uims.uist89.ps.gz
Anjo and me ar currently working on a reusable implementation of a successor of this schema for the Esprit project KACTUS. This library is likely to become part of future XPCE releases. This library basically provides a global structure for applications (and is thus much less flexible as XPCE in this sense).

Maintainer's Note: This question has actually a continuation about a related technical problem you might find interesting.

(Up to Table of Contents)


How do I attach hidden information to a device object? I'd like to keep related information in a self-contained package.

> Since I've taken the approach to "assert" the user produced-graph
> into the prolog database only when it's complete, I now face the
> problem to attach "hidden information" to a device node.
>
> When the user creates a new node, (s)he is prompted with a dialog
> which determines some of the features of the icon.
>
> The dialog gets further information which, although not immediately
> reflected in the graphical representation, I'd like to retrieve later
> on, if the icon still exists without explicitly saving them in a
> different location (this would pose a consistency problem).
>
> Do you think attaching the "invisible" info to the device is a good
> idea?

*If* you decide (as you did) for the idea that a graphical representation of some part of the Prolog database is created, the (graphical) representation is modified and the result is used to replace the old Prolog database, I guess it makes sense to ensure the loaded/edited/saved information is an (as good a possible) self-contained pack of data.

So, suppose you have a graph and the nodes have attributes (which is what I deduce from your description). It could be that the nodes are entities themselves (i.e. can exists without the graph) and the graph (possibly multiple graphs) represent some structure(s) of the database. In this case, I would design a Prolog database where nodes are self contained packages with some identifier and the graphs are self contained packages using the node identifiers. The graph editor(s) just manipulate the graph. If you want to have a dialog for manipulating the data of a node, the dialog will load the existing info and store it back once the user is finished editing the node attributes

On the other hand, if a node with its attribute makes no sense outside the graph, a single self-contained database representing the combination might be a better solution. In that case it might be logical to store the node attribute values with the graphical representation.

> What's the best way to achieve this?

There are essentially three natural ways to store such information with graphicals:

  1. Using object-level attributes This is done with the methods `object <->attribute'. Object-level attributes are dynamic but relatively expensive it you needs *lots* of them (The attributes are in a linked list and each attribute needs to store both the name of the attribute and the value).
  2. Using subclasses Just make variable declarations for the extra data you need to store. Basically the same as above, but you can exploit XPCE's typing for consistency and it is cheaper in terms of memory. On the other hand, you may need to define a lot of classes.
  3. Using a sheet You can attach sheet object to the graphical (using a subclass or object-level attribute). This nicely packages the info together.
Of course, you can make combinations of the above solutions. In all cases, the additional data will automatically be GC'ed if the graphical is destroyed.

(Up to Table of Contents)


I know I cannot invoke a Prolog predicate from within a message by passing it Prolog data structure in the usual Prolog syntax, but what is the alternative?

> Pag. 33 of the Programming Manual. You warn against confusing PCE
> data structure with Prolog data structure. You point out that XPCE
> will try to view the argument to the Prolog predicate as a PCE
> object, thus preventing the passage of all of those Prolog
> argument which lack a simple XPCE onject counterpart.
> The manuals fail to give the right solution, though.

> new(D, dialog('bug')), > send(D, append, button(verbose, > message(@prolog, assert, > verbose(on)))), > send(D,open). > I suspect that the right way to do this is: > send(D, append, button(verbose, > message(@prolog, verbose, on))), > but I can't get a confirmation since verbose is note defined.

Your suspicion is accurate, but you have to define a Prolog predicate verbose/1, of course. Verbose is supposed to be something of your application. For example:

:- dynamic verbose/1. dformat(Fmt, Args) :- verbose(on), !, format(Fmt, Args). dformat(_,_). ... dformat('Now trying to fly~n', []), ... in this context, the example dialog would be a natural way to control `verboseness', but doesn't work, so you have to use your example and define verbose(Val) :- retractall(verbose(_)), assert(verbose(Val)).

(Up to Table of Contents)


How can I assert a text_item selection as a Prolog integer?

> Below 'Npwg' is text_item extracted using <- selection.
> I want to assert it as an iteger to perform some arithmatic operations.
> Could you tell me how to make the type conversion?
>
>             str_write(Dname, Npwg):-
>                         assert(pp_npwg(Dname, Npwg)),

If the text_item is to produce an integer, the best is to register this with the text_item:

... new(TI, text_item(npwg)), send(TI, type, int), ... In this case, the returned value will be an integer. If the typed value cannot be converted an error is raised by the text_item and <-selection will fail.

Once you have an atom, you can either use the Prolog primitives name/2 and/or number_chars/2 or explicitely invoke XPCE's type testing:

?- get(type(int), check, '45', X). X = 45

(Up to Table of Contents)


How can I assert an XPCE string as an atom (and not as an XPCE reference)?

> I'm trying to regain a string value from the text attached
> to a device and, then, to assert it in the
> database as a Prolog fact.

> db_new_task(Device) :- > get(Device, member, text, Text), > get(Text, string, Name), > asserta(task(Device, Name)). > The problem is that I keep asserting an XPCE reference instead of a
> Prolog atom (I also tried other ways).

This will transform the original name object (read-only shared text object) into a read-write string object. So, what is returned is an XPCE string object. There are two ways of converting:

?- get(String, value, Atom). ?- get(type(name), check, String, Atom). The first works for all subclasses of char_array, the second for anything that may be translated into something textual.

(Up to Table of Contents)


How can I invoke a Prolog predicates from a message and give it a Prolog list as a parameter?

Maintainer's note: The problem is not simple to solve and many cases must be considered.
This is why I made a special pourpose subsection to the problem. A general advice is to use XPCE chain, chain_table, sheets etc... as much as possible, in that they may have many useful feature which makes them much more versatile than Prolog lists.
Furthermore, conversions from chain to Prolog lists and viceversa are possible.

How can I turn a chain into a Prolog list?

> In the documentation you say there are predicates to turn a chain
> into a Prolog list

Try the Browsers/Prolog Predicates list from the online manual. The predicate is called chain_list(+Chain, -List).

(Up to Table of Contents)


How can I build a chain out of a Prolog list?

> How do I go from a chain to a Prolog list?

?- L = [a,b,c], T =.. [chain|L], new(Ch, T). If your Prolog has no limit or compound-term arity or the one below if the arity is limited. ?- L = [a,b,c], new(Ch, chain), forall(member(E, L), send(Ch, append, E)).

(Up to Table of Contents)


I'd like to do something like message(@prolog, prolog_predicate, [a, b, c]), which obviously fails. Is it possible?

Maintainer's note: This question is tightly connected to the next. I recomend you read both

> I'd like to do something like :
>

message(@prolog, prolog_predicate, [a, b, c])

> which obviously fails. I was thinking about going through a
> chain but that's bad since I need two conversions.
> Is there a simpler way?

There isn't anything else (but...). It is also difficult to imagine anything else. One solution would be to allow for passing Prolog datastructures:

..., send(Button, message(@prolog, call, prolog(assert(foo, bar)))), ..., Now, unfortunately if you pass a Prolog reference to the term assert(foo, bar) you are faced with the fact that the lifetime of the Prolog term is not unlikely to end before the lifetime of the button.

So, the only way would be to translate this into:

..., record('$pce_term', assert(foo, bar), Ref), send(Button, message(@prolog, call, prolog(Ref))), ..., and let the interface make the reverse translation. This feature would allow for passing arbitrary Prolog data over the XPCE interface, although one should realise that what is passed is actually a *copy* of the original, and this all bindings will be lost, so you still can't do ?- send(@prolog, call, prolog(get0(C))). It will call ok, but as the call will be executed on a copy of the term, the variable C will remain unbound.

The XPCE <-> CommonLisp interface implements a schema like this which is used commonly to associate a lambda function with a GUI object.

Maintainer's note:Jan Wielemaker called for feedback above these, but he himself has already produced an implementation of this proposal.
If you have a better suggestion it would be welcome anyway.

(Up to Table of Contents)


Maintainer's note: This question is tightly connected to the previous one. Reading the answer to the previous one first is likely to facilitate your understanding of the problem and relative solution

I just can't give up Prolog list. Furthermore I have to deal with lists of lists. What's worse they are possible arguments to Prolog predicate invocation from a message! Is there any way to do this?

> Here is the problem, the list they deal with are not simple lists,
> but lists of lists :'-(
>
> I can try to modify the following into something recursive,

> ?- L = [a,b,c], > new(Ch, chain), > forall(member(E, L), send(Ch, append, E)). > the question is, do you think it's possible? or is there some problem
> I'm not aware of? or maybe you still have
> one of those famous aces up your sleeve (something
> like: recursivize ->method : method :-) ?

Of course you can make chains of chains.

> Unluckily lists are very general and untouchable in this case, in
> that they are also used for reasoning on them (i.e. redoing everything
> from scratch with chains is not feasible).

In general, you'd better write a predicate

prolog_to_pce(?Prolog, ?Pce)

If you want to pass info over the Pce interface. This will, as I explained, always deal only with *copies*. The simplest and probably fastest way to implement that (using Prolog as storage) is: :- pce_begin_class(prolog_ref(ref), object, "Reference to Prolog structure"). variable(ref, int, get, "database reference"). initialise(PR, Ref:int) :-> "Create from database record":: send(PR, send_super, initialise), send(PR, slot, ref, Ref). unlink(PR) :-> "Erase related prolog record":: get(PR, ref, Ref), erase(Ref), send(PR, send_super, unlink). :- pce_end_class. prolog_to_pce(Prolog, Pce) :- object(Pce), !, get(Pce, ref, Ref), recorded(_, Prolog, Ref). prolog_to_pce(Prolog, Pce) :- recorda('$prolog_to_pce', Prolog, Ref), new(Pce, prolog_ref(Ref)).

(Up to Table of Contents)


Language issues

How do I trace an XPCE program?

The XPCE tracer may be activated using the predicates tracepce/[0,1], breakpce/1 and spypce/1. The XPCE tracer is similar to the standard 4-port Prolog tracer, except that the tracer has no `redo' port as XPCE goals cannot be resatisfied.

You find the definition of Prolog predicates in Browsers/Prolog Predicates of the XPCE manual or in the user-guide.

(Up to Table of Contents)


I'd like to do something like send(@test, append, [@t1, @t2]) instead of repeating send many times

There are two predicates available from the "pce_util" library which do exactly this: send_list/2 and send_list/3
Users of SWI-prolog can activate this predicate without explicitly importing them. Users of SICStus Prolog should declare these predicates by using the require/1 directive.

The above two predicates invoke send-behaviour as send[2-12]. Each of the arguments is either as accepted by send[2-12] or a list of such arguments.

(Up to Table of Contents)


How do I make a simple editor for editing a file?

> Even though setting up a dialog which shows the content of a file is
> straigtforward, setting up a simple editor for editing a file does not
> seem to be as easy. From the documentation I was able to understand
> that you have to define an object of class view first, which
> subsequently delegates to an object of class editor, but I couldn't
> find the examples in the demos (I tried to browse the EMACS example).
> Can you give me a hint ?

?- new(V, view), send(V, load, myfile), send(V, open). Not too bad, is it? :-). An editor is a graphical object for editing files; a view is a window displaying an editor. If you make a view, it will make an editor for you and delegate all messages to the editor, so you don't have to be concerned with the difference in 99% of the cases.

(Up to Table of Contents)


I have a few questions about identities.

> I have defined two classes with many attibutes and I want to force
> most of the attributes of two particular instances to
> match. The idea is to put an identity constraints on all
> of the attributes this way:

> set_identities(Old, New) :- > new(_, constraint(Old, New, identity(supertype))), > new(_, constraint(Old, New, identity(legalsuffix))), > new(_, constraint(Old, New, identity(legalsuffix_inher))), > new(_, constraint(Old, New, identity(initvers))), > new(_, constraint(Old, New, identity(initvers_inher))), > new(_, constraint(Old, New, identity(initprimary))), > new(_, constraint(Old, New, identity(initprimary_inher))). > Do you think it's a good idea or would you use an alternative?
> Is there any problem (dangling references, for ex:) if the user
> deletes one of the products?

It will (should :-) do what you expect it to do. There won't be any dangling references as constraints are know to the object management system and automatically deleted.

Problem with this approach is that *any* send-message arriving on the device will cause the constraints to be evaluated. Depending on the complexity of the application, this might noticible slow down the application.

I would be tempted to split the product object into the graphical object and a second object (subclass of class object) holding the data. If you then use a hyper object to relate the graphical and storage object, you can just create a second hyper to the second graphical representation and the job is done. Consider this example.

> In the case in which you assert an
> identity on two attributes which already possess different values,
> which one prevails?
On initialisation, the constraint is executed in the `forwards' direction: the second object is made consistent with the first.

(Up to Table of Contents)


Class Variables

XPCE only offers `instance variables'. There are three ways to represent common data at the class level:

Note, the explicit creation of my_class is necessary. When omitted, :- pce_begin_class will create a normal class (instance of class class).

(Up to Table of Contents)


Can I use an XPCE object reference as the key for a chain_table?

> Can you tell me where can I find an example of chain_table use?

Not in one of the demos for the time being. They basicaly make a key to a set instead of a single value.

> Is there, as far as you know, some problem if I use an XPCE object
> reference as a key?

No, that is perfectly valid. Note however that identity means the *same* *reference*. So,

..., send(Table, append, string(foo), something), get(Table, member, string(foo), X), ..., won't work, but the following will: ..., new(S, string(foo)), send(Table, append, S, something), get(Table, member, S, X), ...,

(Up to Table of Contents)


How does the following obtainer work?

get(Links, find, ?(Graphical, handles, @default, @arg1?from), Match),

>I can't completely figure out how this obtainer works. :- pce_begin_class(connect_multiple_gesture, connect_gesture, "Make one of multiple connections"). variable(links, chain*, get, "Links to choose from"). add_link(G, Link:link) :->.......OK verify(G, Ev:event) :-> "Select appropriate link":: get(G, links, Links), Links \== @nil, get(Ev, receiver, Graphical), HERE! get(Links, find, ?(Graphical, handles, @default, @arg1?from), Match), send(G, link, Match), send(G, send_super, verify, Ev). > I interpret:
> find the first link in the list for which the obtainer evaluates to
> TRUE and unify that with Match.

Close. Obtainers either return an object or the exception code `failure' (get(Obj, selector, X) returns object or fails). So, find the first link from the chain for which the obtainer returns a non-failure value.

During execution of the obtainer, @arg1 is bound to the currently tried link object. @arg1?from thus refers to the name of the handle on the `from' side of the connection (link). So, te obtainer returns a chain of handle objects iff Graphical has one or more handles with the requested name. See graphical <-handles: the get operation faiulks if no matching handles can be found (instead of returning an empty chain.

> How was I supposed to consult the documentation on line in
>order to find the information by myself?

You should be able to find your info from chain<-find and graphical <-handles.

(Up to Table of Contents)


I cannot understand how "send(Draw?dialog?feedback_member, selection, Str)" works

> I can't understand how this obtainer works:

PceDraw, file draw.pl line 200 feedback(Draw, Str:string) :-> "Print feedback message in dialog":: send(Draw?dialog?feedback_member, selection, Str). ^^^^^^^^^^^^^^^ > I know that it concerns the feedback label, but how does it work?

It is trapped by the <-catch_all method of class device (inherited thourgh window to dialog). If XPCE cannot resolve a method, it will try to invoke the method `catch_all' as a last resort (prepending the selector to the argument list).
This particular usage is actually `backward compatibility only' New code better using

?(Draw, member, feedback) which does the same, but is easier to understand.

(Up to Table of Contents)


How can I assign the selection string of a text_item to a Prolog variable

Prolog has only logical variables, so you'll have to wait for the user to complete the dialog window. This is achieved with the <-confirm ->return methods of class frame (delegated from the windows): get_name(Name) :- new(D, dialog('Assign Prolog Variable')), send(D, append, new(N, text_item(name, ''))), send(D, append, button(ok, message(D, return, N?selection))), send(D, append, button(quit, message(D, return, @nil))), get(D, confirm, Answer), send(D, destroy), Answer \== @nil, Name = Answer.

(Up to Table of Contents)


How do I read the content of file

> I have some text printed to a unix-file, and I don't know how I
> shall read it back into a variable. To write the text to an unix-file
> I used these commands:

tell(outfile), /* The files name is outfile */ writef("This is a test file I want to read back"), nl, writef("I really want to get this information!!!"), nl, told, ..... /* Here should I add some code for reading the file into a variable */ ..... > The text which I should read from the file, is going to be displayed
> in a XPCE-browser, and that's why I must be able to read it back.
> The text written to the outfile will not in the future just be
> nonsence-text, but output from a privous defined function I`ve
> made.

There are many ways to do this. One is to read the characters one-by-one using get0(X) and parse them back into lines. The other is to use XPCE's file<-readline method, which returns the lines as strings. This would simplify your problem to:

new(F, file(infile)), send(F, open, read), repeat, ( get(F, read_line, Line) -> send(Browser, append, Line), fail ; !, send(F, close) ).

(Up to Table of Contents)


Why "get(I, mode, draw_proto)"?

> In the menu.pl file (PceDraw) one of the methods of
> draw_icon class is:

can_delete(I) :-> "Can I delete this icon?":: get(I, mode, draw_proto). > Shouldn't the last parameters of a get always be a variable
> (i.e. always have a capital first letter)?

Not necessarily. This is a useful shorthand. It is the same as

get(I, mode, Mode), Mode == draw_icon in this case. If this wasn't possible I'd get a lot of questions from Prolog programmers :-) The general case is a bit more complicated: ?- get(area(20,20,30,40), size, size(X, Y)). to give an example.

(Up to Table of Contents)


How do I keep string from destroying the potentially useful value of @receiver?

> I defined this gesture.

:- pce_global(@open, new(click_gesture(left, '', single, and(message(?(?(@receiver?frame, member, dialog), member, feedback), selection, Here-> string('You want to model a %s', Here-> @receiver?name)), message(@receiver, inverted, @off)), message(@receiver, inverted, @on), message(@receiver, inverted,@off)))). > The problem is that in the dialog label I get "You want to model a
> nil", no matter which label I clicked on. If I just send the name of
> the label without trying to compose it with a string (just
> @receiver?name) , everything works fine.
>
> Looks like the string function destroys the value of @receiver.
> Is that correct? How can I avoid the problem?

The problem is the moment of evaluation. In your case the @receiver?name will be evaluated at the moment the string is created, which is when the pce_global trap is executed (i.e. the first reference to the object @open (b.t.w. a bit too general name for a global reference). The trick is to write function that returns a string:

create(string, 'You want to model a %s', @receiver?name) is a function object, than -when executed- creates what you want. By the way, the ->report mechanism is likely to do what you want much simple and more general. See visual ->report for documentation. Your handler will probably be (this is also an example about how to attach a recognizer to a label to simulate a button): :- pce_global(@open, new(click_gesture(left, '', single, and(message(@receiver, report, status, 'You want to model a %s', @receiver?name), message(@receiver, flash))))).

(Up to Table of Contents)


I need to build a graph by querying facts in the Prolog database. How can I do that?

> When loading a graph from a prolog data base, I wanted to
> check whether a particular node is already in the window,
> before displaying a particular node. For this purpose
> perhaps I have to assert (and fetch) an xpce object to
> a prolog data base.

??? Just assert the reference if you want. So:

.... send(Window, display, new(Node, text(hello))), assert(node(hello, Node)), ... You can also keep the references in a Prolog list (which is much better style): display_arcs(Window, Arcs) :- display_arcs(Arcs, Window, []). display_arcs([], _, _). display_arcs([arc(From, To)|Rest], Window, D0) :- ensure_displayed(Window, From, FromRef, D0, D1), ensure_displayed(Window, To, ToRef, D1, D2), new(_, connection(FromRef, ToRef)), display_arcs(Rest, Window, D2). ensure_displayed(_, Node, Ref, D, D) :- memberchk(Node=Ref, D), !. ensure_displayed(Window, Node, Ref, D, [Node=Ref|D]) :- send(Window, display, new(Ref, text(Node))), send(Ref, handle, handle(w/2, h/2, link)). I gues you can addapt this.

> Is there any other simple way of loading a graph from
> an associated prolog data base?

Altogether it should not be much more than one page.

(Up to Table of Contents)


I have a graph made of icons and connections. How can I "assert" it into the Prolog database as Prolog facts?

> I would like my application
> to take a walk through the user-produced graph and
> interactively assert the right facts by exploitation of the
> connections.
> I'd like to get opinions about the approach I should follow. If
> you think that the second one is better, the problems are:
>
>   1) Where do I start inspecting the graph (I don't have a reference)

Well, you *do* need a reference to something. I guess you know where to find the picture window displaying the graph. Now, how you collect the graph depends on what database representation you have for it. The simplest way is to simply enumerate the arcs (represented as connections) and convert them:

... send(Picture?graphicals, for_all, if(message(@arg1, instance_of, connection), message(@prolog, store_connection, @arg1))), ... store_connection(Connection) :- get(Connection, from, From), get(Connection, to, To), <map the nodes to a sensible Prolog representation>, <determine the type of the connectionif applicable>, <assert the fact(s) for this arc> >    2) How do I make sure I don't get in a loop.

The above example surely terminates. If you have a start-node, you can build the graph by asking the node for its <-connections and recursively continue. Keep a list of visited connection objects to avoid a loop.

Maintainer's Note: This question is actually the continuation of another very general, yet IMHO very interesting one. The next concerns a particular case which might occur in a situation like this.

(Up to Table of Contents)


How do I get to know the kind of connection in a graph with different kinds of arcs?

> My application builds graph with different kinds of connection.
> I'd like to assert it as a set of prolog facts, but how can I tell
> the different kinds of connection?

Simplest way is to test the link used to instantiate the connection:

send(Picture?graphicals, for_all, if(and(message(@arg1, instance_of, connection), @arg1?link == @my_nice_link), <do something to assert that arc>)

(Up to Table of Contents)


Can I use object/2 for testing the existence of an object?

>| ?- object(@a,L). > > no !!?? No, you can't. This may be called a bug, although I don't consider it a serious one. object/1 is a valid test for object-existence. object/2 is first of all meant to simplify debugging by providing a description of an object. Using object/2 in sourcecode should be limited to instances that have all (most) status information in their initialisation arguments: get(Graphical, size, size(W, H))

(Up to Table of Contents)


Is there any way of asking a popup what object, if any, it is attached to (as in ProWindows-2's get_ref(Popup,object,Host)?

> Is there any way of asking a popup what object, if any,
> it is attached to (as in PW2's get_ref(Popup,object,Host)).
> From a quick check of the manual I can't find anything.

You can get this info, but not by asking the popup. This info is passed as context to the message executed from the popup. Note that (unlike PW2), the same popup object may be connected to any number of objects. See the documentation of `popup- > execute' for details on the context arguments passed to the message. (I'll put a pointer in the main description to this ...).

(Up to Table of Contents)


Changing family and style of existing text is a bit tricky. Do "shortcut methods" exist?

> I wonder if there is some shortcut that I have not yet detected.
>
> What I want to do is to change family, style, or for some existing
> text. What I now feel forced to do is along these lines:
>
> e.g. change just the style to NewStyle:
> ..
> get from Text the old font OldFont
> extract from it Family
> extract from it Point
> NewFont = font(Family, NewStyle, Point)
> send to Text the new font NewFont
> ..
>
> I expected to do just like this:
> ..
> get from Text the old font OldFont
> send to OldFont font NewFont
> ..
>
> but I could not find the methods necessary.
>
> Comments?

You got bad luck. No, there isn't anything better (I agree there should be though). Of course you can define a method yourself ...

(Up to Table of Contents)


How do I keep track of all instances of a class?

XPCE basically doesn't know what objects are in the database, except for objects that have a global reference and objects that can be followed by following slot-relations from objects found (this is exactly what checkpce/0 is doing).

If you need to keep track of instances for a class, you have three alternatives:

  1. Send ->record_instances: @on to the class. The hash-table `class <-instances' will represent a list of all instances.
  2. (re)define the methods ->initialise and ->unlink. The first is called whenever an instance is created, the second whenever an instances is removed (explicitely or by the garbage collector).
  3. associate a `class ->created_message' and `class ->freed_message' to the class. These messages are executed when an object is created/destroyed.

(Up to Table of Contents)


How can I get a separator line in a complex dialog box?

> Fast question. Is there any way to have a line which works as
> a separator in a complex dialog box? I'm thinking about something
> simple like the <HR> tag in HTML.

You can just do:

send(Dialog, append, line(0, 0, 200, 0))

or so. The only thing you cannot accomplish is to make the line ending (let's say) 10 pixels before the right-side of the dialog. To the right is easy: just make it ridiculously long.

(Up to Table of Contents)


How can I make a dialog button the default button, i.e. the button which is activated correspondingly to a carriage return?

send(Dialog, default_button, <ButtonOrNameOfButton>),

(Up to Table of Contents)


How do I wait for the user to perform some action, for example to fill out a dialog window and press OK or CANCEL?

It's not that hard. Try the following:

... new(D, dialog('Test Dialog')), send(D, append, text_item(name)), send(D, append, button('OK', message(D, return, ok))), get(D, confirm, Ok), send(D, destroy), ... See frame->return and frame <-confirm for details. Actually, you could also have implemented this using (not tested): new(D, dialog('Test Dialog')), send(D, append, text_item('Vorname')), send(D, append, button('OK', message(D, destroy))), send(D, open), repeat, send(@display, dispatch), \+ object(D), !. Various of these isues are explained properly (hopefully) in the CourseNotes I've written for a couple of commercial courses I've given. These coursenotes are on anonymous ftp ftp://swi.psy.uva.nl/pub/xpce/doc/coursenotes/coursenotes.ps.gz

(Up to Table of Contents)


I have problems with editors

. > I declared a text_buffer as an object variable. > variable(trigger_code, > text_buffer, both, "code of the trigger"). > I want to associate it with an editor in order to keep its content
> persistent to the life of the dialog containing the editor.
> I have problems with initialization (maybe due to the fact that the
> text_buffer is still undefined). Any hint?

How do you mean `undefined'? If you just want to store the plain ASCII text, use a string object for the storage. Use <->contents to save/load the string into an editor (<->contents is delegated to/from text_buffer).

TextBuffers are a far too specific class for storing just plain text (although they *could* be used for that).

> send(TD, append, new(ED, editor(@default, 30, 6))), > send(ED, text_buffer, Task?trigger_code), > > % get(Task, trigger_code, TCode), > % (TCode \== @ nil -> send(ED, text_buffer, TCode?contents) ; true), The argument of Editor->text_buffer is a text_buffer object, so it should not be TCode?contents, but plainly TCode.

> How do I attach a message to an editor?
> I'm looking for something similar to the return-carriage in text_item.
> I tried editor <->modified_message: code*

Rebind the return key and do whatever you like. Basically:

send(Editor, key_binding, 'RET', message(...)). also remember to include this message if you are interested in maintaining the default carriage return behaviour. message(Editor, newline_and_indent)

(Up to Table of Contents)


How can I put three editors in a row?

> Here is my problem, I need to make a dialog containing three small
> editors in a row.

The combination of ->append and a subsequent ->right doesn't work as ->append already relates the new object to the last one displayed. ->append by default puts objects below each other, which the exception of multiple buttons, which are places left-to-right. If you want other objects left-to-right, using ->append: object, right.

->right should give a warning instead of succeeding silently.

The following works fine in this case:

new(D, dialog('code attribute editor')), send(D, append, new(Pre, editor(@default,20,12))), send(D, append, new(Main, editor(@default,20,12)), right), send(D, append, new(Post, editor(@default,20,12)), right), send(D, append, new(L2,line(0, 0, 600, 0)), below), send(L2, pen, 4), send(D, append, button(quit, message(D, destroy)), below), send(D, open).

(Up to Table of Contents)


How can I activate a menu_item conditionally to a Prolog clause?

> how can I make menu_item 'metaphoric' active only if the prolog
> clause session/1 is bound as 'session(um)'?
>
>   send(MIL, append, menu_item(metaphoric,
>       message(@prolog, metaphorical, @arg1, P, Root, Dh))),

use the condition argument of menu_item:

... menu_item(metaphorical, message(@prolog, metaphorical, @arg1, P, Root, Dh), condition := message(@prolog, session, um)), ...

(Up to Table of Contents)


How do I implement a drag_and_drop gesture?

> I need to implement a drag_and_drop gesture like the one used in
> the 'Dialog Editor'. Can I reuse the plain method without any
> problems?

Basically, yes! In order to drag-and-drop and object, just connect a drag-and-drop gesture to it. To receive an object, define the methods ->drop and if you like, ->preview_drop (for feedback while dragging).

->drop is defined with at least one argument. If it is defined with two and the latter accepts a point, the current location of the cursor relative to the drop-zone is reported (see ->terminate method of the gesture class). The type-check of the first argument may be used to only accept objects of specified type (but of course, you can also just fail in ->drop if you don't like the object).

:- pce_autoload(drag_and_drop_gesture, library(pce_drag_and_drop)). dd :- new(P1, drop_picture), new(P2, drop_picture), send(P1, display, new(B, box(50,50))), send(B, recogniser, new(drag_and_drop_gesture)), send(new(D, dialog), below, P1), send(D, append, new(label)), send(P1, open), send(P2, open) :- pce_begin_class(drop_picture, picture). preview_drop(P, Gr:graphical*) :-> "Give feedback":: ( Gr == @nil -> send(P, report, status, '') ; ( get(Gr, window, P) -> send(Gr, report, status, 'Moving object in window') ; send(Gr, report, status, 'Moving object to other window') ) ). drop(P, Gr:graphical, Pos:point) :-> "Import the graphical if dropped on me":: send(P, display, Gr, Pos). :- pce_end_class. Notice that if you actually need to duplicate the object you are dragging, this could be performed by specializing the ->drop method.

(Up to Table of Contents)


How can I implement a multiple listbrowser ?

> I would like to have multiple selection in a listbrowser.

Multiple_selection implies SHIFT-left-click which means `toggle the selected value of the clicked element and send the select_message'. Simple left-click sets the selection to the clicked object. For example:

go :- new(D, dialog(test)), new(TI, text_item(send_mail_to, '', message(@prolog, true))), new(B, browser(browser)), send(B, multiple_selection, @on), send(B, select_message, message(@prolog, list_to_text_item, TI, B?selection)), send(B, below, D ), send(D, append, TI ), send_list(B, append, [jan, luca, donald]), send(D, open). list_to_text_item(TI, List) :- new(S, string), send(List, for_all, and(message(S, append, ' '), message(S, append, @arg1?key))), send(S, strip), send(TI, selection, S).

(Up to Table of Contents)


Can I have an editor without a scroll_bar?

Editors are not designed with this in mind. You can `hack' this by setting the width of the editor's scrollbar to 0:

?- new(E, editor), send(E?scroll_bar, width, 0). which will effectively delete the scrollbar.

(Up to Table of Contents)


Prowindows-like circular handles in XPCE

> Circular handles (shortest link meeting a virtual circle
> defined wrt a graphical) were specifiable in Prowindows2,
> but I can't find mention of them in PCE. Is there any
> way to implement them short of refining connection and
> graphical->connect ?

No. The best way to implement them would be to refine class connection. The skeleton for this would be something like this:

:- pce_begin_class(my_connection, connection). compute(C) :-> "Recompute `circular' connection":: ( get(C, request_compute, @nil) -> true ; send(C, slot, request_compute, @nil), get(C, from, From), get(C, to, To), ( get(From, is_displayed, @on), get(To, is_displayed, @on) -> <recompute end-points and send ->points to C>, send(C, displayed, @on) ; send(C, displayed, @off) ) ). :- pce_end_class.

Note that the engine requires handles to exist. I would create a handle at the center of the graphicals to be connected.

It may be easier to create a handle in the center, ensure the graphical is opaque (using -> fill_pattern for example) and the connection is hidden behind the connected graphicals. See graphical -> hide. This will work regardless of the shape of the graphical!

(Up to Table of Contents)


How do I scroll two windows with one scrollbar?

> How can I scroll two different picture-windows (in one frame) with one
> scrollbar? I have one window containing a timeline and one window containing
> a schedule and I don't want the timeline to disappear when scrolling the
> schedule vertically....

The trick is to intercept the communication from the scrollbars to the picture window. As the documentation tells me the window receives - > scroll_vertical and - > scroll_horizontal messages to handle the two scrollbars.

I've chosen for a little demo that intercepts both messages and forwards them to other windows related using a hyper object. The advantage of hypers in this context is twofold: they implement a broadcasting mechanism and the XPCE kernel will properly destroy the hyper-relation if either of the windows is destroyed, avoiding dangling references.

Both windows may be, but need not be in the same frame for the code below to work.

Note that a window is the same as a picture without scrollbars.

:- pce_begin_class(multiple_scroll_picture, picture). scroll_vertical(P, How:name, Unit:name, Amount:int) :-> send(P, send_super, scroll_vertical, How, Unit, Amount), get(P, visible, Area), get(Area, position, TopLeft), send(P, send_hyper, scroll_client, scroll_to, TopLeft). scroll_horizontal(P, How:name, Unit:name, Amount:int) :-> send(P, send_super, scroll_horizontal, How, Unit, Amount), get(P, visible, Area), get(Area, position, TopLeft), send(P, send_hyper, scroll_client, scroll_to, TopLeft). scroll_client(P, P2:window) :-> "Associate a window that follows scroll operations":: new(_, hyper(P, P2, scroll_client, scroll_server)). :- pce_end_class. test :- send(new(S, multiple_scroll_picture), open), forall(between(0, 100, V), send(S, display, text(V), point(0, V*20))), send(new(W, window), open), forall(between(0, 100, V), send(W, display, text(V), point(0, V*20))), send(S, scroll_client, W).

(Up to Table of Contents)


How can I make the dict_item's of a browser have a different style ?

> In my program I have a browser. My problem is how to make dict_item's
> in the browser with different style (I would like to have some text
> underline, and some text bold and other plain). If you can answere this
> question I will be very thankful (please give a program-example).

See the sources for the demo-starter tool. The sourcefile is ..../xpce/prolog/lib/pce_demo.pl.

The browser is prepared for bold font using:

send(B, style, title, style(font := font(helvetica, bold, 14))), A bold item is appended using: send(B, append, dict_item('======Contributions====================', style := title))

(Up to Table of Contents)


How can I layout four windows in a square?

> how can I layout 4 windows a,b,c,d in the following way...
>
>
> aaa bbb
> ccc ddd
>
> this looks so simple, but I couldn't work it out (after 4 hours!).
> (and of course, the manual's example is limited to 3 windows).

As far as I know the best explanation is in the sourcenotes document:

ftp://swi.psy.uva.nl/pub/xpce/doc/coursenotes/coursenotes.ps.gz
For this example, the code is: ... send(B, right, A), send(D, right, C), send(C, below, A), ... in which case the horizontal separations are aligned. The vertical only if the tuples a/b and c/d have the same (relative) resize properties as specified by their <-ideal_width, <-hor_stretch and <-hor_shrink parameters.

Of course, the following works as well:

... send(C, below, A), % C is under A and both have equal width send(D, below, B), % D is under B and both have equal width send(B, right, A), % stack B/D is right of A/C and the ... % joined height of these pairs is equal with all horizontal and vertical swapped in the alignment explanation.

(Up to Table of Contents)


I'd like to define a connect_gesture subclass which performs some other action than establishing the connection itself at the end

> I specialized "connect_gesture" to discriminate among different links
> (I had "verify" check a status variable). Everything works fine except
> for I would like one of the gestures to avoid actually drawing a
> connection, but doing something else instead.
> I thought that I just needed to specialize "terminate" too and not have
> it invoke terminate in the superclass for that particular connection.
> As you expect, the problem is that "terminate" also took care of
> getting rid of the line and handles indicator which remain on the
> screen even though the connection is not drawn

From the manual, I read:

            connect_gesture->terminate: event
            Invokes ->drag. Next removes the <-line and the indicatorbitmaps
            from the <-device and finally invokes ->connect using the following
            arguments:

`event<-receiver'
<-to
<-link
<-from_handle
<-to_handle
The `from' graphical
The `to' graphical
The <-link
Handle name at the `from' side
Handle name at the `to' side

So, the correct method to redefine is the ->connect method. The terminate method should always invoke the super-class method unless you want to be sure to get into compatibility problems with next releases. The ->connect of the generic class simply makes an instance of the link (a connection), but you can do anything you like instead.

(Up to Table of Contents)


How can I define multiple connections and discriminate among them depending on the connected graphicals?

> In the little graph editor I'm building I need the system to
> recognize four different kinds of connections i.e. when the
> user chooses a relation between two possibly different kinds
> of icons, I'd like the connections to show with different
> kinds of line, can you give me some hints and, if you can,
> some code?

Maintainer's Note: Jan Wielemaker really showed what kind of good hearted fellow he is on that occasion and replied:

The example I prepared for you is a bit too long for the mailing list. You can get it by clicking here or from:

ftp://swi.psy.uva.nl/pub/xpce/demos/graph_editor.pl

It defines a graph editor that puts boxes, ellipses and triangles on a drawing area and defines several different types of links between them. Including comments the example is 250 lines long.

(Up to Table of Contents)


I need to discrimanate graphicals according to which side of a connection they are connected to, but the graphical-> connected method will not work

> It's sending me crazy!
> I want to modify the look of a dialog depending on the existence of a
> certain connection starting FROM a device. The graphical-> connected
> method would do, but it does not seem to work.
> I've prepared a self-contained example
> for your happy debugging

This is where the problem should be ...

> cond_dialog(G) :- > new(D, dialog('What kind of box am I ?')), > send(D, append, new(Lab, label)), > (send(G, connected, @default, > @decomp_link, north_tdd, south_tdu) So, according to the not-so-good documentation of this method, this succeeds iff: This won't work, as what you want to state is:

If G has connections of link @decomp_link and I'm at the from side of such a link

This can be written as:

( get(G, connections, @default, @decomp_link, Connections), get(Connections, find, @arg1?from == G, _) -> The first line picks all connections from the proper link. The second checks whether there is one that has G as its <-from side. > -> send(Lab, selection, > 'I am a box at the beginning of the connection') > ; send(Lab, selection, > 'I am either a lonely box or a box at the end of > the connection')), > send(D, append, button(quit, message(D, destroy))), > send(D, open).

(Up to Table of Contents)


How can I resize an arbitrarily complex graph with a slider?

> I have implemented a specialized graph editor. Since I don't know how
> big the final graph will be, I want to attach a slider (ranging from
> 50 to 100) which uniformly reduces the dimension of the graph on the
> screen. I know how to do that with single objects, i.e. I can reduce
> uniformly all of the graph nodes on the screen, but not their relative
> distances. I think that I need to use spatials in some form, but
> exactly how is not clear to me.

The proper way to do this is by exploiting the `graphical ->resize' method, which takes x- and y scale factors and an `origin' (that may be outside the graphical). An example is PceDraw's facility to resize a collection of graphicals (select multiple graphicals and resize the bounding box).

Somewhere in the many plans is to introduce a scale-factor at the level of class device. Together with rotate, this would provide the system with graphical primitives for a much wider range of applications.

(Up to Table of Contents)


I need to relate a string and a text_item in such a way that changing the value or content of one object automatically updates the corresponding value in the other object. Is it possible?

> What I need is to automatically update the GUI if the data change
> (because of a manual modification or the concurrent access of the
> data by two different editors, for example) and not only the opposite
> way.
> For example, how can I connect in such a way a text_item string and
> a string object variable?

Basically, prepare the string to intercept changes and forward them over the hyper and do the same for the text_item. Using hypers, the following should work:

:- pce_begin_class(p_string, string). changed(S) :-> "Forward new value to visualisations":: send(S, send_hyper, v, value, S). value(S, V:char_array) :-> ( send(S, equal, V) -> true ; send(S, send_super, value, V), send(S, changed) ). :- pce_end_class. :- pce_begin_class(v_text_item, text_item). :- pce_global(@v_text_message, new(message(@receiver, send_hyper, p, value, @arg1))). initialise(TI, Label:name, P:p_string) :-> send(TI, send_super, initialise, Label, P?value, @v_text_message), new(_, hyper(TI, P, p, v)). :- pce_end_class. test :- new(@s, p_string(hello)), send(v_text_item(test, @s), open). Next, you can try: ?- test. ?- send(@s, value, gnu). <item shows `gnu'> <type gnat RETURN in the item> ?- get(@s, value, X). X = gnat Depending on your total architecture, you can also use the class - > changed_message for trapping object changes.

(Up to Table of Contents)


How can I make an editor distinguishably different from a browser?

The best thing to do is probably to put a label above them. Otherwise, yes, you can change the look of both the editor and its scrollbar. Just look at the various attributes. Note by the way that one has a cursor and the other not. Also note that most browsers are small and high, while most editors are wide and low.

(Up to Table of Contents)


Can I read coloured images in XPCE?

> Do you know how I can load quickly a great (1100x900) X11 Pixmap
> (256 colour s) into a XPCE object (image,pixmap,bitmap,...). The only
> way it seems to work is to do it pixel-by-pixel using the method
> image->pixel(x,y,colour). The time needed is then about 5Min. on a
> SPARC20...not acceptable for our purposes.

As yet, XPCE only reads monochrome X11 bitmaps. It's quite high on my agenda to support other bitmap formats and at least one pixmap format. I'm considering gif and/or jpeg (first appears to have licencing problems) and maybe ppm (portable pixmap). I hope you can wait a couple of weeks.

(Up to Table of Contents)


How can I manipulate the pixels in a window?

> I have a picture object, into which I draw many wonderful things.
> Now I want to scan all of the pixel from top left of the picture
> to bottom right.
>
> How do I find out the colour of a pixel in a picture?
> and how do I set it to a particular colour?

Basically you cannot manipulate pixels in a PCE Window. No panic however. If you want to read a window's picture, make an image object of the same size as the window and draw the graphicals in there. Next you can read the pixels from the image. This would look something like this:

picture_to_image(P, I) :- get(P, visible, area(X, Y, W, H)), new(I, image(@nil, W, H, pixmap)), new(M1, point(-X, -Y)), new(M2, point(X, Y)), send(P?graphicals, for_all, and(message(@arg1, relative_move, M1), message(I, draw_in, @arg1), message(@arg1, relative_move, M2))). After which image <-pixel wil finish the job.

I would appreciate any help or pointers. Thanks in advance...

The only way to write pixels in a picture is to display a bitmap on the picture and write the pixels in the bitmap.

(Up to Table of Contents)


Sensitive graphicals

How do I attach a popup menu to a graphical?

This snippet of code is actually an example of numerous XPCE features which might might interest absolute beginners. That is why I decided to make this question a reference for many "simple" questions: The simple application below allows the user to generate small boxes on a drawing area. Each box has a popup menu (right click) with items for self-destruction and message forwarding to the Prolog interpreter. /*************************************** * Talking Boxes: an XPCE example * ***************************************/ /* This is a rather standard way to define a complex recognizer * This recognizer will be attached to each box as soon as it is * generated. The recognizer is made of two gestures: * * 1) A move_gesture which allows for the dragging of each box * with the middle button (default) * 2) A popup_gesture which attaches a simple two item popup menu * to each box. It is activated when the right button is * pressed (default) */ :- pce_global(@icon_recogniser, make_icon_recogniser). make_icon_recogniser(G) :- new(M, move_gesture), new(P, popup_gesture(new(Pop, popup))), Graphical = @arg1, send_list(Pop, append, [ menu_item(delete, message(Graphical, free)) , menu_item(who_am_I, and(message(@prolog, write, 'Hi! I''m a little box'), message(@prolog, nl))) ]), new(G, handler_group(M, P)). /* This is the main part of the application. First it generates a frame * which will function as a container for the other windows. * Secondly it will attach a picture window for displaying the boxes * and a simple dialog above it. The dialog contains a button for * self-destruction and a label with a welcome message. * Lastly a recognizer is attached to the picture. It intercepts single * left buttons clicks and delegates the actual creation of the box * to a prolog predicate defined below */ make_talking_boxes :- new(F, frame('My Boxes Talk')), send(F, append, new(P, picture)), send(new(D, dialog), above, P), send(D, append, button(quit, message(F, destroy))), send(D, append, label(feedback, 'Welcome to the wonderful world of talking boxes'), right), send(P, recogniser, click_gesture(left, '', single, message(@prolog, make_box, P, @event?position))), send(F, open). /* This is the Prolog predicates in charge of generating each box * It simply generates a box, attaches (an instance of) the recognizer * to it and orders the picture to display it*/ make_box(P, Position) :- new(Box, box(50, 25)), send(Box, recogniser, @icon_recogniser), send(P, display, Box, Position).

(Up to Table of Contents)


How can I attach a Popup menu to a connection?

> I guess you can tell what's wrong with this code with just one look:

> make_form_in_link(FI):- > new(FI, link(prod_form_in, task_form_in, new(Line, line))), > send(Line, recogniser, @link_recognizer), > send(Line, arrows, second). > > :- pce_global(@link_recognizer, make_link_recognizer). > > make_link_recognizer(LR) :- > new(LR, popup_gesture(new(Pop, popup))), > Line = @arg1, > send_list(Pop, append, > [menu_item(delete, message(Line, free)) > ]).

Load the following bit of code (will be part of next public version) and it will work:

:- pce_extend_class(connection). event(C, Ev:event) :-> "Also consider the link's line recognisers":: ( send(C, send_super, event, Ev) -> true ; get(C?link?line, all_recognisers, @off, Recognisers), get(Recognisers, find, message(@arg1, event, Ev), _) ). :- pce_end_class.

(Up to Table of Contents)



I have a dialog with three editors, but two of them are completely "dead"

> I have a dialog with three editors.
> The first editor gets the focus naturally (i.e. I can write in it),
> but there's no way for having the other two perform the same service.
>
> Do I have to redefine the some method to achieve this?

Just click in the one you want to activate? This didn't work in older versions. If this doesn't work, you should be able to hack using:

... send(Editor, recogniser, handler(ms_left_up, and(message(@receiver, keyboard_focus, @on), new(or)))), ... The new(or) is a trick to make an always failing object, so event-handling will do this, but continue with the predefined stuff.

(Up to Table of Contents)


Performance and Errors


Why are graphical operations so incredibly slowed down on my machine when I use pen > 1?

> Your last remark seems to be quite relevant here. I.e. having a
> stippled line with pen > 1 does slow down things > significantly. Moving
> a miniwindow interactively is not smooth at all but distinctly
> "jumpy". It does seem to require a lot of processing power.
>
> MORAL: one should avoid stippled lines with pen > 1. Having pen = 1
> does not seem to have any noticable performance impact on the graphic
> operations. Is this true in general, i.e. having pen > 1 costs
> a lot while pen = 1 does not have this cost (regardless of the texture)?

XPCE's pen 1 is mapped onto X11's pen = 0, which implies `paint the thinnest line and do it fast'. X11's pen >= 1 are supposed to paint beautiful lines with optimal caps and joints. They use floating-point for doing the computations (at least 90% or so of the servers do). I don't understand the `why' here as to my best knowledge there are quite impressive bit-manipulation algorithms for this that gives results which will be hard to distinguish from what X11 use and are probably 100 or more times faster. XPCE paints shapes with pen > 1 and texture `none' by painting the same shape multiple times with pen 1 ...

Actually the only server I've seen that lacks this nonsense is the Xfree 2.1 server used by Linux and most PC-based Unix systems.

(Up to Table of Contents)


@arg1?product_name == Name, always fails, but it shouldn't?

> I have defined an object product (subtype og device, with an
> associated product_name string attribute).
>
> I'm trying to understand if there's a product on the picture with the
> same product_name attribute, but the standard and most obvious way to
> do it, doesn't seem to work:

> :- pce_begin_class(product, device, "graphical with a lot of info"). > > variable(product_name, string, both, "name of the product"). > > : > : > > dup_prod(Product, Name) :-> > "check if this product has already been defined":: > get(Product, canvas, C), > send(C?graphicals, for_all, > if(and(message(@arg1, instance_of, product), > @arg1?product_name == Name), > message(@prolog, conf_dialog, Product, @arg1))). > I traced it and I have noticed that the "@arg1?product_name == Name"
> condition always fails (after I've just created two objects with the
> same product_name.

The == object compares object *references*. Either use the method ->equal (message(@arg1?product_name, equal, Name)) or use names instead of string objects to represent the product name. Names represent (like strings) textual values, but it is guaranteed that iff two names represent the same textual value they are the same object.

Considering memory: names are slightly more expensive to store due to the table needed. Uniqueness saves space if you have enough of the same. Names are (currently) not garbage collected.

Note that graphical objects have a name and you may want to use this for storing the identification name. In that case you can use the device <-member message to locate the object.

(Up to Table of Contents)


This dialog items has lost its default behaviour for no apparent reason

My text_item used to respond to carriage return by highlighting the caret of the successive text_item. Why did it lost its default behaviour?

Maintainer's Note:This might look a bit one-off, but the same problems might arise in apparently different situations. You should be aware that a XPCE message also yields an evaluation value, i.e. it can be used as a test (see here for an example). If such conditions evaluates to false, the dialog item default response might not occur. Here is an example and the easily extensible solution

> I thought everything was alright with my application here, but
> now I realize it has lost a feature it used to have during
> development. My text_item used to respond to carriage return by
> highlighting the caret of the successive text_item. Why did
> it lost its default behaviour?
> Here is the code:

> send(D, append, new(TIN, text_item(name, '', > and(message(Product?nametext, string, @arg1), > message(Product, product_name, @arg1), > message(Product, dup_prod, @arg1))))), > send(Text_name, name, nametext) > send(D, append, new(TIS, text_item(status, '', > and(message(Product?statustext, string, @arg1), > message(Product, product_status, @arg1)))), > below), > > : > : > dup_prod(Product, Name) :-> > "check if this product has already been defined":: > get(Product, canvas, C), %C is a picture > get(C?graphicals, find, > and(@arg1 \== Product, > message(@arg1, instance_of, product), > message(@arg1?product_name, equal, Name)), > Dup), > conf_dialog(Product, Dup).

I think you should make sure the message of the text item succeeds, your implementation of the thing only succeeds if there *is* as duplicate product object. This will do:

dup_prod(Product, Name) :-> "check if this product has already been defined":: get(Product, canvas, C), %C is a picture ( get(C?graphicals, find, and(@arg1 \== Product, message(@arg1, instance_of, product), message(@arg1?product_name, equal, Name)), Dup) -> conf_dialog(Product, Dup) ; true ).

(Up to Table of Contents)


I always get this initialization errors referring to new classes variables. How do I avoid them?

> I get: > 3 ?- Call: ( 5) product:set_identities(@ 849216, @ 825207) ? creep > ^ Call: ( 6) pce_principal:new(L392, constraint(@ 849216, @ 825207, identity(product_status, pro> duct_status))) ? creep > [PCE error: product <->product_status: Argument 1 (string) should be a string > in: V @825207/product <->product_status: @nil/constant] > PCE: 15 fail: V @825207/product <->product_status: @nil/constant ? > ^ Exit: ( 6) pce_principal:new(@ 87615

You have to initialise the values to a valid string. If you want to be able to leave the slot value to its initial @nil value, you must postfix the type declaration with the `*' sign: string*

(Up to Table of Contents)


XPCE complains that it fails to grab pointer. Once it even crashed everything. Is there a solution?

> Some time XPCE complains that it fails to
> grab pointer. This normally happens relating to
> the XPCE confirmer when the user is a bit fast.
> Unfortunately this caused the appliaction to crash once.
>
> Is there any solution to this problem in terms of
> XPCE?

The problem is actually with the (many) X window managers. They send the f.delete message intercepted by XPCE when the mouse-button is *pressed* and claim the mouse. They should send this message at button *release*.

The simplest solution is to switch `frame <->confirm_done' to @off. This will stop XPCE displaying the confirmer window. You can do this for all applications by adding a line:

Pce.Frame.confirm_done: @off in your ~/.Xdefaults or the Pce resource file.

This is not supposed to lead to a crash, so please inform Jan Wielemaker if you have anything that might be reproduced.

(Up to Table of Contents)


I cannot use append with this hash_table. Any idea?

> I need to use an hash table which dinamically associates an XPCE
> reference (key) to a text_buffer (I need it to store an editor content
> throughout the life of the application). I'm trying this:

> variable(feedback_table, hash_table*, both, > "list of feedbacks produced by task"). > : > : > adjust_feedback(Generator, Receiver) :- > get_name_of_feedback(Name), > send(Generator?feedback_table, append, Receiver, new(text_buffer)), > > Now, the error I get is: > > 3 ?- [PCE warning: send: No implementation for: @nil/constant -&gt;append] Not unreasonable. By making a variable of type hash_table*, you don't *create* a hash-table object, you just define this slot can contain one. Check the definition of object ->initialise and class <-instance for details on object creation.

Normally your class looks like this:

... variable(feedback_table, hash_table, both, ".."). .. initialise(R, ....) :-> send(R, send_super, initialise, ...), send(R, feedback_table, new(hash_table)), .... Alternatively, you can use: ... variable(feedback_table, hash_table*, both, ".."). ... blabla(R, .....) :-> get(R, feedback_table, T), ( T == @nil -> send(R, feedback_table, new(T1, hash_table)) ; T1 = T ), send(T1, append, bla, gnat). > BTW Are there examples somewhere about the use of hash_tables?
> If not, I think that it would be useful.

No short ones. There is code using them in the libraries. Just grep for hash_table and you'll find it.

(Up to Table of Contents)


I cannot understand why XPCE tells me "file -> open" is not implemented

> I have some problem with the production of a Postscript dump of
> what's in my tool's picture
> Which seems rather strange since I more or less copied from the Demos
> and the method is used correctly according to the documentation:

> postscript_as(Canvas) :- %Canvas is a Picture > get(@finder, file, @off, '.ps', @default, File), > send(File, open, write), > send(File, append, Canvas?postscript), > send(File, close), > send(Canvas?frame, report, status, > string('Written PostScript to `%s''', File?base_name)). > But I get: > [PCE warning: send: No implementation for: > /home/......../Xpce_lab/scratch.ps ->open]

get(@finder, file, ...) returns the *name* of a file. This is good enough for methods that expect a file (type conversion will create an instance of class file with this name, so you can say send(View, load, 'myfile.pl')), but not good enough for just sending it an ->open message. Many classes define the open message, so what conversion would it have to do? The solution is to make the conversion explicit:

get(@finder, file, @off, '.ps', @default, FileName), new(File, file(FileName)), send(File, open, write),

(Up to Table of Contents)


I tried to print a PostScript screen-dump of a dialog by using the methods provided, but I got this error message

>[PCE error: send: No implementation for: @2661737/scroll_bar ->_draw_post_script > in: send(@2661737/scroll_bar, _draw_post_script)] > PCE: 39 fail: send(@2661737/scroll_bar, _draw_post_script) ?

No, the generation of PostScript is not supported for these classes. In general, PostScript is supported for all real graphics classes, but not for the `command' objects (menus, buttons, etc.). I don't have plans to change this on the short term, although it should not be too hard to generate images for these objects.

(Up to Table of Contents)


I get an "Out of lock stack" error. What does that mean?

> I get the message:

> > [WARNING: Out of lock stack] > > Execution Aborted > > 23 ?-

This is generally another word for `Segmentation fault', occurring in the lock-stack area. I can't be of much help in trying to debug this. What version of XPCE/SWI-Prolog are you running? If older than 4.7.2 it may be wise to upgrade as some serious bugs have been patched in this version.

When desparate and installed from the sources, you may try to replace the message in outOf() in file pl-alloc.c by calling fatalError(). This will cause an attempt to print the Prolog stacks, but in this case it is very likely to run into a recursive error. You can also contact the process from gdb and break on outOf(). When trapped you can call backTrace(environment_frame, 10) to get a Prolog backtrace. When using gdb, the symbol table should be xpce/pl/sparc-.../xpce.base.

(Up to Table of Contents)


Tricks and Hacks

Can I test a key while my application is running?

> is it possible in XPCE to test a key while
> the program is running ?
> I need this to STOP my program, when it gets into a cycle.

Basically you can check for events using

..., send(@display, synchronise), ..., So, if you want a button to stop your loop, do: :- dynamic stopped/0. test :- send(button(stop, and(message(@prolog, assert, stopped), message(@receiver?frame, destroy))), open), my_loop. my_loop :- send(@display, synchronise), retract(stopped), !. my_loop :- my_loop. send(@display, synchronise), is not particulary fast (about 2000 calls per second on a SPARC 10), so don't call it too often.

If we are talking about program development, you can normally type Control-C to interrupt your program from a loop. This should work on all versions, except for the MS-Windows versions that check explicitely for Control-C at some central points in the code, but nevertheless can loop such that it doesn't check.

(Up to Table of Contents)


How can I implement an always failing code object?

There are many ways to define this code object. For example:

new(or)
this one is the smallest, fastest and easiest to write.

It's not an hack, it's just logic:an or object can have any number of statements, succeeds as soon as it executed one successfully and fails otherwise. If there is no statement, it fails.

So, how to create an object that always succeeds (no, I don't buy not(new(or)), although it works :-)

(Up to Table of Contents)


My mouse has only two buttons. Is there a way to use XPCE for me?

> The major problem I have with the Windows port is that I don't
> have a 3-button mouse. So I can't do anything with the dialog editor!
> Any suggestions (apart from "go and buy a 3-button mouse")?

For the time being this is about the best I can think of. Mice are rather cheap these days.

If you have 2 buttons, you might try the resources:

Pce.PopupGesture.button: left Pce.PopupGesture.modifier: c which, in theory would let you have the menu's using Control-left button. Bit annoying I guess, but better then nothing :-)

As long as the code doesn't explicitely assign buttons to gestures you can play this trick with all of the gestures.

(Up to Table of Contents)


Miscellaneous

Is it really true that applications developed on, let's say AIX, will run without modifications on, e.g., DOS/Windows?

Yes, with the exception of minor things that cannot be emulated in a sensible way. For example class process (dealing with inferior processes a la GNU-Emacs) is not available for the MS-Windows version. Also, MS-Windows window-icons are 32x32 bits, while X11 window icons are unlimited. The MS-Windows version will scale the icon for you, but whether it gets pretier this way ...

(Up to Table of Contents)


Why are recognizers spelt recogni*s*ers?

Because Jan Wielemaker still loves Good Ol' Britain (certainly more than the Webster dictionary does).

(Up to Table of Contents)


Luca Passani maintains this document. Feedback can be sent to him by Email:
passani@idt.unit.no

The Humble Scribe
Luca Passani