[comp.lang.prolog] PROLOG DIGEST V6 #40

restivo@POLYA.STANFORD.EDU (Chuck Restivo) (07/09/88)

Date: Sat 9 July 1988 02:53-PST
From: Chuck Restivo (The Moderator) <PROLOG-REQUEST@POLYA.STANFORD.EDU>
Reply-to: PROLOG@POLYA.STANFORD.EDU>
US-Mail: P.O. Box 4584, Stanford CA  94305
Subject: PROLOG Digest   V6 #40
To: PROLOG@POLYA.STANFORD.EDU


PROLOG Digest           Saturday, 9 July 1988      Volume 6 : Issue 40

Today's Topics:
				Announcement - Logix & NU,
				     Implementation - Objects
-------------------------------------------------------------------------------------------------------------------------------

From: <udi%WISDOM.BITNET@CORNELLC.CCS.CORNELL.EDU>
Date: Tue, 31 May 88 12:47:25 +0200
Subject: The Logix system version 2.0 release 7

Version 2.0 of the Logix system, release 7, is available. Licensed
users can obtain the new release by sending a 1/2" tape or a 1/4" cartridge to:

        Mr Yossef Dabby
        Dept. of Applied Math and Computer Science
        The Weizmann Institute of Science
        Rehovot 76100
        Israel

Please include a letter explaining that you are a licensed Logix user and
wish to get an updated release.

Unlicensed users can send to that address a request for a copy of
the license agreement, or send e-mail to me for an electronic copy.
There is a $250 handling fee for new licensees. Logix is available
for Sun2, Sun3, and for VAX and CCI computers running BSD/4.2 and up.

Logix is a single-user multi-tasking concurrent logic programming
environment, developed as a group effort at the Weizmann Institute of
Science.  It runs as a single Unix process.  Its low-end (abstractmachine, about 7000 lines of source code) is written in C; its
high-end (everything else, more than 10,000 lines of source code) is
written in Flat Concurrent Prolog (FCP). The model of computation of
FCP is based on dynamic light-weight (some say feather-weight)
nondeterministic processes, communicating by binding logical
variables, and synchronizing by waiting for such bindings.  Normal
computations generate thousands of concurrent processes; Logix, when idle,
consists of about 1000 suspended processes.

Logix has been heavily used at the Weizmann Institute and other places
for the past two years for various applications, including its own
development, compiler development, parallel and distributed algorithm
development, embedded-language implementation, hardware simulation,
etc. An account of its applications can be found in ``Concurrent
Prolog: Collected Papers'', E. Shapiro (ed.), MIT Press, 1987.

Since Logix's first release, the following improvements and enhancements
were made:

1. Embedded languages
        The system supports various embedded languages, including:
        - FCP(|,:,?), a superset of Oc and of Flat GHC (and hence supports
                also Flat GHC).
        - Typed FCP, a typed variant of FCP, with an accompanying type checker.

        - The implicit variables (also called framed logic programs)
                notation.
2. System support
        - Hierarchical module system, integrated with the Unix hierarchical
                file system.
        - Concurrent interactive debugger (not an algorithmic one yet,
                though one is under development).
        - Support for syntax extension and user-defined embedded languages
        - Support for meta-programming
        - Multiple execution modes: trust, failsafe, interrupt,
                interpret.
        - Support for multiple virtual machines (to be of real use only
                in future multiprocessor versions of Logix).
        - Nested, interactive computation control.
        - `lint' like analysis of common errors.
3. Emulator support
        - Foreign kernels/ C interface/ Unix interface/ Native code interface
        - Double-precision floating point arithmetic.
        - Freeze/melt primitives.
        - Speed has almost doubled since first release.  On a Sun 3/50 it
          runs the standard concurrent naive reverse benchnmark at 5K process
          reductions per second.  It creates processes at a peak rate of
          1500 a second, and can maintain up to 50,000 (fifty
          thousand) concurrent processes in a 4MB heap.


There is also an unsupported implementation of FCP for the iPSC/I Hypercube,
which does not include the Logix development environment.
If you want more info on FCP for the iPSC/I let me know.

        -- Ehud Shapiro

-----------------------------

Date: 6 Jun 88 05:08:06 GMT
From: munnari!mulga!jws@uunet.uu.net  (Jeff Schultz)
Subject: New Release of NU-Prolog System

Version 1.3 of the NU-Prolog system is now available for release to
academic institutions (schools, colleges, universities).  Commercial
licences are also available for some machines.

This release includes a much improved interpreter and debugger, both
of which now understand when declarations; floating point arithmetic;
an interface to foreign functions on many machines; and the usual
large collection of bug fixes.  Performance has been increased by 10
to 20 per cent for many applications.

NU-Prolog is a second generation Prolog system which incorporates a
number of important advances in Logic Programming implementation.

NU-Prolog was implemented as part of the Machine Intelligence Project+
in the Department of Computer Science at the University of Melbourne.
It is the successor to Lee Naish's successful MU-Prolog system and
attempts to move Prolog closer to the ideals of Logic Programming by
allowing the user to program in a style closer to first order logic.
In addition, it provides substantial performance gains over interpreted
systems such as MU-Prolog.

NU-Prolog has the following features:

* compiles Prolog programs into machine code for an enhanced version
  of the Warren abstract machine (implementing the delay/coroutine
  style of programming of MU-Prolog)

* incorporates a database system based on superimposed codeword
  indexing which can store general Prolog terms in external databases
  for fast retrieval by NU-Prolog programs; the database system
  makes use of the superjoin algorithm to perform efficient join
  operations

* uses "when" declarations (the successor to MU-Prolog's "wait") to
  control the execution of NU-Prolog programs according to the
  availability of data

* implements a large set of built-in predicates, including many Quintus
  Prolog predicates; most DEC-10/Edinburgh/MU-Prolog library predicates
  are available through compatibility libraries

The NU-Prolog system contains the following major components:

* "nc", the NU-Prolog compiler

* "np", a simple interpreter-style interface which implements the
  standard Edinburgh Prolog style debugging facilities and has a
  sophisticated query language for accessing external database
  predicates

* "nac", a program for adding control information to NU-Prolog programs
  written in a purely logical style

* "nit", a program for reporting common errors in NU-Prolog programs
  (cf. Unix/C's "lint")

NU-Prolog runs under Unix System V and Berkeley BSD Unix 4.?. It has
been implemented on a large number of machines including the following:
Sun 3 and 4, Vax, Encore, Elxsi, Perkin Elmer, Pyramid, Integrated
Solutions Workstations.  For academic licences, the system comes
complete with a manual and all source code. The preferred distribution
medium is 1/2" tape, Unix tar-format at 1600bpi.  Other distribution
media may be available on request.  There is a A$400.00 fee to cover
distribution costs.

In order to obtain a copy of the system, you must first complete a
licence agreement with the University of Melbourne. Licences can be

obtained by contacting:

	NU-Prolog Distribution
	Department of Computer Science
	University of Melbourne
	Parkville, Victoria, 3052
	AUSTRALIA

or
	mip@munnari.oz

------------------------------

Date: 2 Jun 88 19:47:05 GMT
From: csli!johnson@labrea.stanford.edu  (Mark Johnson)
Organization: Center for the Study of Language and Information, Stanford U.
Subject: Re: oops


/*

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
*/

------------------------------

Date: 7 Jun 88 20:46:13 GMT
From: csli!gandalf@labrea.stanford.edu  (Juergen Wagner)
Subject: Re: Object-oriented system in Prolog

Some weeks ago, Mark Johnson (markj@cogito.mit.edu) posted a short
Prolog program which was supposed to handle inheritance nets. In my
opinion, the program oversimplifies inheritance by just
	o  specifying properies of graph nodes,
	o  disallowing the inheritance of certain properties, and
	o  walking through in depth-first.
A *REAL* object-oriented system should at least be able to handle
examples like the following correctly (using the notation of Mark's
program): 

    truck is_a object.
    toy is_a object.

    toytruck is_a toy.
    toytruck is_a truck.
    toytruck is_a truck.

    tt is_a toytruck.

    purpose(object, nil).
    purpose(truck, transport).

    find_purpose(X,V) :-
	    inherits(X, purpose, Super),
	    purpose(Super, V).

For the query
    find_purpose(tt, X)
this will generate the solutions
    nil
    transport
    nil
which reveals the deficiency of such an algorithm. It is desirable to
get the solutions
    transport
    nil
only, because the "transport" property is defined in a more
specialized super-class of "toytruck" than "nil". Therefore, we need
some strategy tranversing nodes iff all relevant daughters have
already been searched.

The following implements such a strategy (C-Prolog 1.5).

o_recorded(Key, Form, Ref)
	test whether something has been recorded in the database.
	This can be replaced by a call to `recorded'.
o_record(Key, Form, Ref)
	record something in the database. This can be replaced by
	a call to `recordz'.
set_slot(Object, Slot, Value)
	set a slot value of an object

%
%	Compute Search Path (Breadth-First)
%

o_compute_search_path(Class,Path) :-
	% Get list of superclasses
	o_recorded(Class,superclasses(Super),_),
	% Mark all superclasses as active
	o_enter_all_super(Super),
	% Compute the actual search path
	o_compute_path([Class],Path),
	% Enter the complete search path into the object
	( o__class(Class);
	  asserta(o__class(Class)) ),
	set_slot(Class,all_superclasses,[Path]), !.

% Recursively enter all superclasses into the table.
o_enter_all_super([]).
o_enter_all_super([C|Rest]) :-
	( o_recorded(C,active,_), !;
	  o_record(C,active,_) ),
	o_recorded(C,superclasses(Super),_),
	o_enter_all_super(Super),
	o_enter_all_super(Rest).

% Basically, do a breadth-first, but superclasses are removed from
% the agenda only if their subclasses have been searched completely.
o_compute_path(Old,Result) :-
	o_expand_path(Old,Temp),
	o_remove_lock(Temp),
	( Temp = [], Result = Old;
	  append(Old,New,Result),
	  o_compute_path(Temp,New) ),
	!.

% Expand the path by considering the next candidates
o_expand_path([],[]).
o_expand_path([C|Rest],Path) :-
	o_recorded(C,superclasses(Super),_),
	o_filter_super(Super,Path1),
	append(Path1,Path2,Path), !,
	o_expand_path(Rest,Path2).

o_filter_super([],[]).
o_filter_super([C|Rest],[C|Tail]) :-
	o_recorded(C,active,Ref),
	erase(Ref),
	o_record(C,pending,_),
	o_recorded(C,subclasses(Sub),_), !,
	o_known_subclasses(Sub),
	o_filter_super(Rest,Tail).
o_filter_super([C|Rest],Tail) :-
	o_filter_super(Rest,Tail).

o_known_subclasses([]).
o_known_subclasses([C|Rest]) :-
	not(o_recorded(C,active,_)),
	not(o_recorded(C,pending,_)).

o_remove_lock([]).
o_remove_lock([X|_]) :-
	o_recorded(X,pending,Ref),
	erase(Ref),
	fail.
o_remove_lock([_|Rest]) :-
	o_remove_lock(Rest).


-- Juergen "Gandalf" Wagner

------------------------------

Date: 13 Jun 88 03:41:53 GMT
From: csli!johnson@labrea.stanford.edu  (Mark Johnson)
Subject: Re: Object-oriented system in Prolog

/* 
Finally a comment on my toy OOPS!!!

> From: gandalf@csli.STANFORD.EDU (Juergen Wagner)
> ...  the program oversimplifies inheritance by just
> 	o  specifying properies of graph nodes,
> 	o  disallowing the inheritance of certain properties, and
> 	o  walking through in depth-first.
> A *REAL* object-oriented system should at least be able to handle
> examples like the following correctly... 
> 
>     truck is_a object.
>     toy is_a object.
> 
>     toytruck is_a toy.
>     toytruck is_a truck.
> 
>     tt is_a toytruck.
> 
>     purpose(object, nil).
>     purpose(truck, transport).
> 
>     find_purpose(X,V) :-
> 	    inherits(X, purpose, Super),
> 	    purpose(Super, V).
> 
> For the query
>     find_purpose(tt, X)
> this will generate the solutions
>     nil
>     transport
>     nil
> which reveals the deficiency of such an algorithm. It is desirable to
> get the solutions
>     transport
>     nil
> only, because the "transport" property is defined in a more
> specialized super-class of "toytruck" than "nil". Therefore, we need
> some strategy tranversing nodes iff all relevant daughters have
> already been searched.

  ... a bunch of code deleted...

Hmm.  Declaratively speaking, the solutions { nil, transport, nil }
and { transport, nil } are the same set of solutions.  

But I think the criticism is valid - particularly since the redundancies
are fairly easily avoided by defining find_purpose as follows:

find_purpose(X,V) :-
	setof( S, inherits(X, purpose, S), Supers),
	member( Super, Supers ),
	purpose( Super, V ).

If one was dealing with a cyclic inheritance "hierarchy" then
the 'inherits' predicate would have to be augmented so it never
processed the same node twice, eg. by maintaining a list of the
nodes already visited.  Also, the "setof" solution may be inefficient
on large hierarchies, but that's beside the point...

The notion of "more specialized superclass" doesn't strike me as
being well-defined declaratively, unless one wants to say that
a node has an ordered list of parents or something.  Again, my
question is not so much whether one can code such a thing up in
Prolog (which one certainly can do without using recordz), but
how one might build an OOPS facility in Prolog that is reasonably
consistent with the declarative style of good Prolog programming.
I don't think that slot-filler style fits this requirement, for
example.

Any comments?

-- Mark Johnson

/*  A toy object-oriented system, modified as per Gandalf's suggestion */

:- ensure_loaded(library(basics)).
:- ensure_loaded(library(not)).

:- no_style_check(discontiguous).

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

/*  object's definitions */

truck is_a object.
toy is_a object.

toytruck is_a toy.
toytruck is_a truck.

tt is_a toytruck.
 
purpose(object, nil).
purpose(truck, transport).

/*  inherits(Obj,Prop,Super) iff Obj inherits Prop from Super. */
/*     as i previous version                                  */

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 ).

find_purpose(X,V) :-	% modified in response to Gandalf's suggestion
	setof( S, inherits(X, purpose, S), Supers),
	member( Super, Supers ),
	purpose( Super, V ).

------------------------------

End of PROLOG Digest