[comp.lang.prolog] Atom-based module systems

ok@quintus.UUCP (Richard A. O'Keefe) (05/07/88)

In article <395@aiva.ed.ac.uk>, jeff@aiva.ed.ac.uk (Jeff Dalton) writes:
> By saying call/1 is basically an EVAL, I meant that it brings in the
> problems that EVAL does while APPLY does not.

One extremely important problem that EVAL brings in which APPLY does not,
and which call/1 does not bring in either, is the need for QUOTE.

> By the way, Richard, are you still opposed to the so-called atom-based
> module schemes?  I suppose it should be a separate topic...

My objections to atom-based schemes are:
    Lisp associates an amazingly pile of rubbish with atoms (function cell,
    property list, package cell, pname, maybe even other stuff) with atoms.
    Prolog doesn't.  [Hand-wave about operator properties, which are
    notionally stored only in the current_op/3 table.]  Lisp has grounds
    for protecting atoms, Prolog hasn't.  In Prolog there is a one-to-one
    correspondence between atoms and character strings; all atoms are
    deemed to exist at all times  [Hand-wave about current_atom/1] and
    the names cannot be changed.  The elementary units with which Prolog
    associates information are _predicates_, so that's what the module
    system should be based on.  [A typed system could handle constructor
    functions as well as predicates.]

    Atom-based systems reveal too much:  if I have a predicate f_to_s_graph/2
    with auxiliary predicates f_to_s_graph/[3,4] -- this is a real example
    from the latest internal version of library(graphs); it converts a
    forest to a graph -- and want to export f_to_s_graph/2, I do *NOT* want
    the auxiliary predicates to be exported as well.

    Atom-based systems make basic data operations such as term comparison
    inordinately complicated.  [* see below]

    The only atom-based module systems with which I have any familiarity
    are those in Common Lisp and M-Prolog.  I find both appallingly
    complicated.

Someone could well produce a coherent logic programming language with an
atom-based module system.  (I don't know LM-Prolog well enough to tell
whether it satisfies this description.)  It couldn't be a compatible
extension of "Edinburgh" Prolog, that's all.  None the worse for that.

[* see here]
Of course, a Prolog system which is embedded in or otherwise closely
coupled with a Common Lisp implementation has to cope with the fact that
Common Lisp *has* an atom-based package system, like it or not.  Since
this is a reasonable approach to implementing a Prolog system (I am
saying this in the hope of tricking potential competitors into trying it...)
I think that a Prolog standard should address this issue.  (And yes, this
_is_ a swipe at the BSI/ISO substandard.)

Prolog need not be able to perform all the Common Lisp symbol/package
operations, but the Prolog operations should be defined so as to do
something sensible when given any atoms that the Lisp part manages to
throw at it.  I actually have a specification for this.  The main gap at
the moment is defining the term comparison order of distinct atoms with
the same name; it looks as though this has to be implementation-
dependent, and may have to be allowed to change between queries.

micha@ecrcvax.UUCP (Micha Meier) (05/11/88)

In article <943@cresswell.quintus.UUCP> ok@quintus.UUCP (Richard A. O'Keefe) writes:
>My objections to atom-based schemes are:
>    Lisp associates an amazingly pile of rubbish with atoms (function cell,
>    property list, package cell, pname, maybe even other stuff) with atoms.
>    Prolog doesn't.  [Hand-wave about operator properties, which are
>    notionally stored only in the current_op/3 table.] 

	I don't know what is the current_op/3 table and how does the read/1
	predicate access it, but in any case even in Prolog, there is
	more information one might want to associate with a functor:
	counters, recorded terms, arrays (except for recorded terms
	extended data types, but they *are* used). Apart from that,
	there are Prolog extensions that might want to associate even
	more information with a functor. In SEPIA, we have introduced
	property lists exactly because of this.

--Micha

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

In article <943@cresswell.quintus.UUCP> ok@quintus.UUCP (Richard A. O'Keefe) writes:
>In article <395@aiva.ed.ac.uk>, jeff@aiva.ed.ac.uk (Jeff Dalton) writes:
>> By saying call/1 is basically an EVAL, I meant that it brings in the
>> problems that EVAL does while APPLY does not.
>
>One extremely important problem that EVAL brings in which APPLY does not,
>and which call/1 does not bring in either, is the need for QUOTE.

Well, if that were true, R3RS Scheme would not need QUOTE, because it
doesn't have EVAL.  Lisp needs QUOTE even in cases like (CONS 'A 'B)
which don't involve EVAL.  Of course, Lisp could use some other
convention, such as a different type face, instead.  But EVAL doesn't
bring in the need for QUOTE: the need is already there.

One reason Prolog doesn't need QUOTE is that it uses another
convention (capitalization in Edinburgh Prolog) to distinguish
variables from constant symbols.

And, if we take a call/1-like APPLY, which can call fexprs, we
can define EVAL thus:

   (defun eval (expr) (apply #'if (list 't expr))) 

Can the analogous construction be made in Prolog?

Perhaps, though, you have in mind that if Lisp used some other
convention than QUOTE and then added EVAL it would also have to add
QUOTE.  I'll have to think about that.

-- Jeff

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

In article <943@cresswell.quintus.UUCP> ok@quintus.UUCP (Richard A. O'Keefe) writes:
>In article <395@aiva.ed.ac.uk>, jeff@aiva.ed.ac.uk (Jeff Dalton) writes:
>> By the way, Richard, are you still opposed to the so-called atom-based
>> module schemes?  I suppose it should be a separate topic...

The reason I asked is that your recent remarks on the impossibility of
sharply distinguishing code from data would tend to support "atom-
based" designs.

It also seems strange that (with non-text schemes) in

     p(a).

p/1 is subject to modules, but in

     q(p(a)).

it is not -- even though q/1 may use call/1 or otherwise be dealing with
the same p/1 as in the first example.  (Is portray an example?)

I'll respond more fully to your reasons against in a separate message.

-- Jeff

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

In article <943@cresswell.quintus.UUCP> ok@quintus.UUCP (Richard A. O'Keefe) writes:
>My objections to atom-based schemes are:
>    Lisp associates an amazingly pile of rubbish with atoms (function cell,
>    property list, package cell, pname, maybe even other stuff) with atoms.
>    Prolog doesn't.  [Hand-wave about operator properties, which are
>    notionally stored only in the current_op/3 table.]  Lisp has grounds
>    for protecting atoms, Prolog hasn't.  

I'm not sure why Lisp gets brought in in this way.  No one has argued
that Prolog should do something because Lisp does, and not all Lisps
use atom-based schemes.  In any case, although what you say is true,
it can be misleading.

The key word is "associates".  In some Lisps, the things you mention
are actually part of the symbol object, which may make the difference
between Lisp and Prolog seem greater than it is.  That is just an
implementation convenience, however, and not a fundamental aspect of
Lisp.  If we think of looser associations instead, and that is often
what we actually have, we find:

  * The package cell is an artifact of the module scheme and
    therefore not a reason for atom-based modules.

  * The function and value cells are just an implementation
    convenience.  It is better to think of values being held
    in environments.

  * Both Lisp and Prolog tie a symbol to a string, namely its
    print name, in about the same way.

  * Both Lisp and Prolog can use symbols as symbolic data and
    associate other data with them.  A convention in some Lisps
    is to use symbol properties in sufficiently simple cases. 
    So you might say

      (setf (get 'apple 'color) 'red)

    where in Prolog you might say

      color(apple,red).

    These have, in my view, almost exactly the same implications
    for modules.

Actually, I think Lisp has *less* need for atom-based schemes than
Prolog because it has the alternative of using environments.  To
expand a bit on my remarks in previous messages (about call/1 vs.
APPLY), the situation in Lisp is as follows:

     text --(package)--> symbol --(environment)--> procedure

You do not want to decide what module a procedure is in at call time
because the module should be based on where the procedure argument
came from, not on where the procedure that finally uses call/1 or
APPLY is.  So in Lisp you have two choices: if you want to be able to
pass symbols around, you can make the module division at the package
point.  This is what Common Lisp does.  If instead you plan to pass
around procedures only, distinct from their names, you can base
modules on environments.  That is what T and MIT's CScheme do, and
Common Lisp has limited capabilities of this sort.  Both methods
work, because the things you pass around are already resolved with
respect to modules.

But Prolog doesn't have procedures as separate objects and so can't
pass them around.  Terms and atoms get passed instead.  The Quintus
module scheme attaches module qualifications to terms when it thinks
the terms might eventually be called.  This seems (a) a kludge and
(b) incompatible with Edinburgh Prolog, strictly speaking (you get
these funny terms to call, and if you look at them rather that just
call them, you will see this strangeness).

Note that I mention the Quintus scheme only becauase it is the one I am
most familiar with.  (This gives you an opportunity to show how little
I know even it, I suppose.)  Actually, I think the Quintus scheme is
better than most.

The rest of your points are good, and I will not have much to say
against them.  My own view is that there may not be a completely
satisfactory design for Prolog modules.  I have certainly not seen
any proposal that has the ring of truth.

>    In Prolog there is a one-to-one
>    correspondence between atoms and character strings; all atoms are
>    deemed to exist at all times  [Hand-wave about current_atom/1] and
>    the names cannot be changed.

I am not yet convinced that all atom-based (so-called) schemes, and in
particular schemes that cannot be dynamically reconfigured, will fail
to have this property.

>    The elementary units with which Prolog associates information are
>    _predicates_, so that's what the module system should be based on. 

I don't see how that follows.

Nor do I see why that is the only association that matters.  Do I not
associate information with a term or atom when I use it in a relation?

>    Atom-based systems reveal too much:  if I have a predicate f_to_s_graph/2
>    with auxiliary predicates f_to_s_graph/[3,4] -- this is a real example
>    from the latest internal version of library(graphs); it converts a
>    forest to a graph -- and want to export f_to_s_graph/2, I do *NOT* want
>    the auxiliary predicates to be exported as well.

There may be good reasons to suppose that f/1 and f/2 are just as
different as f/1 and g/1, but I have not heard a convincing argument.
(I know there's a technical sense in which its true, but your own
example of aux predicates shows that is not the only way to think.)
At the moment, Prolog has no modules and so all predicates are
visible.  Since I think an imperfect scheme will be necessary in any
case, I do not mind this imperfection (that all f/n will have the same
visibility) all that much.

>    Atom-based systems make basic data operations such as term comparison
>    inordinately complicated.  [* see below]

I seem to recall that there have been atom-based schemes.  I wonder
how they addressed this problem.

>    The only atom-based module systems with which I have any familiarity
>    are those in Common Lisp and M-Prolog.  I find both appallingly
>    complicated.

That is a valid point, but I don't find the Quintus or NIP schemes
particularly simple.  They also seem to require some ad hoc patches
to deal with things (like setof) that use call/1.

You should also know that many in the Common Lisp community are not
entirely happy with Common Lisp packages.  Some feel that the earlier
package system in Zetalisp was better.  Certainly it was more static,
with less chance for symbols to be created accidently in the wrong
place.

>Someone could well produce a coherent logic programming language with an
>atom-based module system.  (I don't know LM-Prolog well enough to tell
>whether it satisfies this description.)  It couldn't be a compatible
>extension of "Edinburgh" Prolog, that's all.  None the worse for that.

What incompatibilities do you have in mind?  Can a predicate-based
scheme have zero incompatibilities?

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

ok@quintus.UUCP (05/13/88)

In article <531@ecrcvax.UUCP>, micha@ecrcvax.UUCP (Micha Meier) writes:
> In article <943@cresswell.quintus.UUCP> ok@quintus.UUCP (Richard A. O'Keefe) writes:
> 	I don't know what is the current_op/3 table and how does the read/1
> 	predicate access it, but in any case even in Prolog, there is
> 	more information one might want to associate with a functor:
> 	counters, recorded terms, arrays (except for recorded terms
> 	extended data types, but they *are* used). Apart from that,
> 	there are Prolog extensions that might want to associate even
> 	more information with a functor. In SEPIA, we have introduced
> 	property lists exactly because of this.
> 
> --Micha
The current_op/3 table is the built-in predicate current_op/3, what else?

The point is that information about atoms and functors is held in
predicates.  Property lists in Lisp are something of a disaster (you
cannot use properties freely, but have to check that the system isn't
using the name you have in mind; I have been burned by this) and hash
tables in Common Lisp provide a *much* better approach.  Using
predicates in Prolog is the analogue of using hash tables in Common Lisp.
Using predicates, you can associate arbitrary chunks of information
*without* complicating the implementation of atoms and functors, and you
have to support predicates anyway!

ok@quintus.UUCP (Richard A. O'Keefe) (05/14/88)

In article <424@aiva.ed.ac.uk>, jeff@aiva.ed.ac.uk (Jeff Dalton) writes:
> One reason Prolog doesn't need QUOTE is that it uses another
> convention (capitalization in Edinburgh Prolog) to distinguish
> variables from constant symbols.

ZYX's Z-Prolog *does* have some rather complex quoting facilities,
because they have a "source variable" data type (roughly, a pair of
a name and a quote level) which is distinct from "logical variable"s.
Perhaps someone from ZYX would care to comment on this.

> Perhaps, though, you have in mind that if Lisp used some other
> convention than QUOTE and then added EVAL it would also have to add
> QUOTE.  I'll have to think about that.

That was it.

ok@quintus.UUCP (Richard A. O'Keefe) (05/14/88)

In article <425@aiva.ed.ac.uk>, jeff@aiva.ed.ac.uk (Jeff Dalton) writes:
> The reason I asked is that your recent remarks on the impossibility of
> sharply distinguishing code from data would tend to support "atom-
> based" designs.

It is possible to distinguish code from data *PROVIDED* you add declarations
to the language.  The Mycroft & O'Keefe type checking paper suggests on the
last page having a family of types void, void(T1), ..., void(T1,...,T93), ...
where if :- pred p(<t1>,<t2>,<t3>) then
	p(X,Y,Z) : void	if X:<t1> and Y:<t2> and Z:<t3>
	p(X,Y) : void(<t3>) if X:<t1> and Y:<t2>
	p(X) : void(<t2>,<t3>) if X:<t1>
	p : void(<t1>,<t2>,<t3>)
and so on.  As I recall it, this was Alan Mycroft's idea.
The :- meta_predicate declarations in Quintus Prolog are just such type
declarations, where void(_1,...,_n) is abbreviated to n, and the other
types are abbreviated to +,-,or ?.  Thus the type of maplist/2 is
	:- pred maplist(void(T), list(T)).
but this is abbreviated to
	:- meta_predicate(1, +).

The BSI substandard, however, attempts to draw a distinction between code
and data *solely* by means of syntax, without the aid of any such
declarations.

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

In article <963@cresswell.quintus.UUCP> ok@quintus.UUCP (Richard A. O'Keefe) writes:
] The point is that information about atoms and functors is held in
] predicates.  Property lists in Lisp are something of a disaster (you
] cannot use properties freely, but have to check that the system isn't
] using the name you have in mind;

You also have to check that anything you load in doesn't use the same
properties.

] Using
] predicates in Prolog is the analogue of using hash tables in Common Lisp.
] Using predicates, you can associate arbitrary chunks of information
] *without* complicating the implementation of atoms and functors, and you
] have to support predicates anyway!

Using predicates are to me much more like using property lists: they
are a single, global data base, and so it is always possible that different
code will use the same predicate or the same data structure for different
things.

     (setf (get 'apple 'color) 'red)


and

     color(apple,red).

seem much closer to each other than to something like

(let ((color-table (make-hash-table)))
  (defun get-color (object) ...)
  (defun set-color (object color) ...))

where the hash table is known only to those two functions.  Here
the table plays the role of the globally visible name "color" in
the first two cases, but it is not global.

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