[comp.lang.prolog] oops

jtr@expya.UUCP (Jason Trenouth) (04/16/88)

A while back somebody asked about object-orientated programming (theories,
modules, etc) in Prolog (can't remember who). Anyway here's some food for
thought.

If you're a Quintus Prolog 2.0 (or later version) user then you've already got
an OOPS (object-oriented programming system).... you didn't know that?... you
can't find it in the manual?... never fear, your saviour is here!

[I can just feel ROK looking down his nose at this article already...(presses
on with the stiffest of upper lips)...]

The latest versions of Quintus Prolog come with a module system. This allows
the partitioning of a program into separate name spaces. It also provides for
importing and exporting of predicates between modules just like a good module
system should. So far so good. It ALSO lets the programmer access any
predicate directly: bypassing the nice protection of importing and exporting
that's just been mentioned. Surely this is bad? Not so. It is just the
loophole that we need to build a toy OOPS.

[...(dons an asbestos suit to give protection against ROK's flames for
mentioning a Quintus product again)...]

By prepending the module name to a predicate we can reference it anywhere. Say
the module "william" contained a predicate called "third_edition" then we can
reference it by:

	william:third_edition(...args...)

How do we go about building our OOPS? Well, the simplest way is to introduce
the idea of delegation between modules (theories, objects, frames,...). If we
ask a module to solve a query and it fails, then we would like the query to be
delegated to another module. Our first stab might be something like this:

	solve(Goal, Module) :-
		Module:call(Goal).
	solve(Goal, Module) :-
		Module:delegate(SuperModule),
		solve(Goal, SuperModule).

Here our solver will try the original module first before looking for a
"delegate" clause.  Does this work? Well, sort of. Lets look at an example:

:- module(human, []).

	arms(2).
	legs(2).

:- module(ehud, []).

	delegate(human).
	arms(1).

[Ignore the fact that these have to be in individual files (for the moment).]

Now if we query the "ehud" module about "arms" then we will get the local
value of 1. However, if we query the "ehud" module about "legs" then the query
is delegated to the "human" module, and we get the answer 2.. So far, so good.
What about methods?  What? Methods. If this is to be anything more than a data
hierarchy then we would like to be able to have procedures in the modules.
Let's put the following definition in the "human" module:

	limbs(X) :-
		arms(Y),
		legs(Z),
		X is Y + Z.

Now suppose that we query the "ehud" module about "limbs". Splat! The solver
falls flat on its face and comes up with the answer 4. The reason is that it
evaluates the procedure in the "human" module environment. How can we get
round this? Somehow we need to tell "limbs" about where the query has come
from originally. This means that we need to be in control of the execution,
which leads us to... a good ol', all singin', all dancin',... meta
interpreter!

% interface which remembers original module queried.
% "wrt" is sort for "with respect to".

	solve(Goal, Module) :-
		solve_wrt_module(Goal, Module, Module).

% either it's a conjunction of goals,
% a built in predicate,
% a call to solve itself (message passing),
% a goal which can be replaced by a conjunction of subgoals, or
% something that needs to be delegated to a another module.

	solve_wrt_module((Goal1, Goal2), Module, Original) :-
		!,
		solve_wrt_module(Goal1, Module, Original),
		solve_wrt_module(Goal2, Module, Original).
	solve_wrt_module(Goal, _, _) :-
		predicate_property(Goal, built_in),
		!,
		call(Goal).
	solve_wrt_module(solve(Goal, OtherModule), _, _) :-
		!,
		solve(Goal, OtherModule).
	solve_wrt_module(Goal, Module, Original) :-
		predicate_property(Module:Goal, _),
		clause(Module:Goal, Body),
		solve_wrt_module(Body, Original, Original). % important bit
	solve_wrt_module(Goal, Module, Original) :-
		predicate_property(Module:delegate(_), _),
		Module:delegate(SuperModule),
		solve_wrt_module(Goal, SuperModule, Original).

[comments on style, bugs, etc welcome]

With this interpreter, the above example query comes back with the correct
answer of 3 arms. Like the first it also handles multiple delegations. These
are searched depth first (like Flavors) by Prolog's backtracking; which
incidentally violates some inheritance properties - you can't have everything!

One question must be: where are the classes and instances? Er,... there just
aren't any. In Flavors (and Smalltalk) classes contain the methods and some
data, and act as templates. These are then used to create instances, which
contain a copy of the data. This is an unnecessary restriction on object
orientated programming. The system above (POOPS?) and others (eg CommonOrbit)
have only one type of object (called a "prototype" in CommonOrbit), which can
be used more flexibly.

For more information on OOPSs, and a comparison between CommonOrbit and
Flavors, see "Artificial Intelligence Programming Environments" edited by R.
Hawley (Ellis Horwood, 1986).

Chow.

	_______________________________________
	|                                     |
	| Jason Trenouth                      |
	|  Computer Science Department        |
	|   University of Exeter              |
	|    Devon EX4 4PT                    |
	|     United Kingdom                  |
	|                                     |
	| JANET:  jtr@uk.ac.exeter.cs         |
	| UUCP:   jtr@expya.uucp              |
	| BITNET: jtr%uk.ac.exeter.cs@ukacrl  |
	|_____________________________________|

jtr@expya.UUCP (Jason Trenouth) (04/26/88)

	Help.

There were no replies to my "oops" article. Please send anything, even
flames...  Is there anybody there?

-------------------------------------------------------------------
|Jason Trenouth,       	      | JANET:  jtr@uk.ac.exeter.cs       |
|Comp.Sci.Dept., Exeter Univ.,| UUCP:   jtr@expya.uucp            |
|Devon, EX4 4PT, UK.	      | BITNET: jtr%uk.ac.exeter.cs@ukacrl|
-- 
-------------------------------------------------------------------
|Jason Trenouth,       	      | JANET:  jtr@uk.ac.exeter.cs       |
|Comp.Sci.Dept., Exeter Univ.,| UUCP:   jtr@expya.uucp            |
|Devon, EX4 4PT, UK.	      | BITNET: jtr%uk.ac.exeter.cs@ukacrl|

jeff@aiva.ed.ac.uk (Jeff Dalton) (05/14/88)

In article <422@expya.UUCP> jtr@expya.UUCP (Jason Trenouth) writes:
>
>How do we go about building our OOPS? Well, the simplest way is to introduce
>the idea of delegation between modules (theories, objects, frames,...). 

I would expect a problem with this approach: since each object is
implemented as a module, and since each module must be written out
explicitly, the number of objects is fixed when you write your
program.  It is hard to see how you could have two stacks without
having to write two "stack" modules with different names.

>Now suppose that we query the "ehud" module about "limbs". Splat! The solver
>falls flat on its face and comes up with the answer 4. The reason is that it
>evaluates the procedure in the "human" module environment. How can we get
>round this? Somehow we need to tell "limbs" about where the query has come
>from originally.

Doesn't the Quintus module system have a way around this problem?

>With this interpreter, the above example query comes back with the correct
>answer of 3 arms. Like the first it also handles multiple delegations. These
>are searched depth first (like Flavors) by Prolog's backtracking;

The so-called New Flavors (in Genera 7, say) no longer uses a simple
depth-first ordering.  Instead there are constraints such as "A flavor
preceeds its components" and the total order is determined by a
topological sort.

>One question must be: where are the classes and instances? Er,... there just
>aren't any. In Flavors (and Smalltalk) classes contain the methods and some
>data, and act as templates. These are then used to create instances, which
>contain a copy of the data. This is an unnecessary restriction on object
>orientated programming.

Why is it a restriction?  Instances can be created dynamically: how do
you do that in your system?  (See my first papagraph of remarks.)

>The system above (POOPS?) and others (eg CommonOrbit)
>have only one type of object (called a "prototype" in CommonOrbit),
>which can be used more flexibly.

It is true that classes are not strictly necessary.  See various
papers that compare deligation with inheritance.

Jeff Dalton,                      JANET: J.Dalton@uk.ac.ed             
AI Applications Institute,        ARPA:  J.Dalton%uk.ac.ed@nss.cs.ucl.ac.uk
Edinburgh University.             UUCP:  ...!ukc!ed.ac.uk!J.Dalton

johnson@csli.STANFORD.EDU (Mark Johnson) (06/03/88)

/*

I saw a message on the bboard a while ago about object-oriented
programming in Prolog.  After a few minutes thought, it struck me
that the main question about OOPS is inheritance; specifically,
who inherits what from whom.  

Anyway, below is a fragment which in which the object hierachy
is represented by an is_a graph.  Inheritance is defined
with respect to specific properties; it is assumed that
a daughter inherits a property from its mother unless explicitly
marked as not doing so.  Tweety inherits all the properties
of birds except that of flying, for example.

As it's built, using the system involves first finding an
ancestor from who a given node can inherit the relevant
property, and then calling the property on the ancestor.  However,
it would be easy to combine the two steps using meta-level
operations or (better) input preprocessing, I think.

This system differs from standard OOPS in two ways. First, *all*
accessible superordinate nodes are considered, rather than the 
"first" one reached via some particular search strategy. Second,
inheritance is not "blocked" just because a predicate is defined
for a particular object.

Even though it would be simple to build a system with the
"standard OOPS" behaviour, it's not clear to me that one
should.  I suspect that the major reason that "standard OOPS"
have the behaviour that they do is because they are based on
functional rather than relational programming systems in which
there is no sensible way to compose "properties" inherited
from different ancestors.

Anyway, this is only a first pass on the subject.  I'd like
to hear any reactions you might have,

Mark Johnson
markj@cogito.mit.edu

*/

/*  A toy object-oriented system */

:- ensure_loaded(library(not)).
:- no_style_check(discontiguous).

:- op( 100, xfx, is_a ).
:- op( 100, xfx, doesnt_inherit ).

/*  object's definitions */

tweety is_a bird.		% tweety's defs
tweety doesnt_inherit walking.	%  tweety's gotta walk
tweety doesnt_inherit flying.	%  'cause he can't fly!
walks(tweety).

polly is_a bird.		% polly's defs

bird is_a animal.		% bird's defs
bird doesnt_inherit flying.
bird doesnt_inherit walking.	%  why walk when
flies(bird).			%  you can fly?
eats( bird, seeds ).

lion is_a animal.		% lion's defs
lion doesnt_inherit food.	%  lion food is special!
eats( lion, meat ).

walks(animal).			% animal's defs
eats( animal, vegetables).	%  Most animals eat vegetables

/*  inherits(Obj,Prop,Super) iff Obj inherits Prop from Super. */

inherits(Obj, _, Obj).	% All objects inherit from themselves.
inherits(Obj, Prop, Super ) :-
	not Obj doesnt_inherit Prop,
	is_a( Obj, Parent),
	inherits( Parent, Prop, Super ).

can_fly(X) :-
	inherits( X, flying, Super),
	flies( Super ).

can_walk(X) :-
	inherits( X, walking, Super),
	walks( Super ).

can_eat(X,Food) :-
	inherits( X, food, Super),
	eats( Super, Food).

/*  Sample run.

| ?- can_walk(polly).

no
| ?- can_fly(tweety).

no
| ?- can_eat(polly,Food).

Food = seeds ;

Food = vegetables ;

no
| ?- can_walk(lion).

yes
| ?- can_eat(lion,Food).

Food = meat ;

no
*/