[comp.lang.prolog] modules

lee@mulga.oz (Lee Naish) (05/10/88)

The main uses of a module system are
	1) avoiding accidental name clashes, and
	2) protecting procedures from being called by anyone.

THEOREM: Every module system is either too complicated or
	 not powerful enough.

COROLLARY: It is impossible to get more than two people to agree on a
	   module system (the failure of the BSI module committee was
	   therefore inevitable).

Prolog module systems have to handle a bit more than module systems of
conventional languages because of the ways in which data/code can be
converted into other representations and converted back:

	1) name/2 converts between atoms (possibly in a particular
	   module) and strings.

	2) =.. (and functor/3) converts between atoms and functors with
	   different arities (possibly in a particular module).

	3) read/1 and write/1 (etc) convert between terms and text.

	4) call/1, clause/2 and assert/1 (etc) "convert" between code
	   and data.

We must determine exactly what these operations do (eg, whether they are
reversible) and if the language is changed to introduce extra arguments
to specify module names.

Quite a while back I made a proposal for a module scheme and discussed
it with various people at Melbourne uni (the result was inevitable).
A version of the scheme was even implemented.  One advantage is that it
requires no changes to the Prolog system - our implementation was a
preprocessor which could be used with any Edinburgh Prolog system.

The scheme is atom based (the arity of a functor is irrelevant).  The
basic idea is that at "compile" time, atoms are mapped to other atoms.

To avoid accidental name clashes, module names can be added to atom
names.  For example, atom 'join' in module 'tree_util' could be mapped to
'tree_util$join'.  To implement protection, atoms can be mapped to
"random" strings, for example, ' tree_util$join 417309467298353'.

Every occurrence of 'join' (with any arity) in module tree_util should
be changed.  A 'join' predicate or call in another module will (by
default) not be renamed, so clashes are avoided.  There is no way
another module can guess the "random" string an atom is mapped to
(the string may depend on when the module was compiled) so protection
is achieved (for watertight protection in any system current_predicate
etc must be modified also).

There are many ways you can define what atoms should be
renamed/encrypted.  One implementation we have accepts the following
syntax:

?- module tree_util : public([list_to_tree, tree_insert]).

list_to_tree([], nil).
.....
join(T0, T1, T) :-
....

?- endMod : tree_util.

This renames every atom which is the name of a procedure defined in the
module except list_to_tree and tree_insert (these two atoms are
unchanged).  There are two options on the preprocessor - one for simply
adding module names and one for adding random strings also.

Another possible syntax is:

:- module tree_util :
	public [list_to_tree, tree_insert],
	import [>= from term_comparison],
	entry [join],
	local [join_1].
....
:- end_module.

This could specify that >= is renamed 'term_comparison$>=', join is
renamed 'tree_util$join' and join_1 is renamed ' tree_util$join_1 78435'.

One advantage of specifying all atoms which are to be renamed is that
only one pass is needed.  The whole module system could be implemented
by using term_expansion.  Nested modules can also be handled very
easily.

One further feature which may occasionally be useful is to provide a
procedure to convert between the original atoms and the renamed versions.
To avoid name clashes and compromising protection, this procedure should
be renamed.  For example, the system could define an is_local procedure
(which is local) for a module:

' tree_util$is_local 76835'(join_1, ' tree_util$join_1 78435').
' tree_util$is_local 76835'(is_local, ' tree_util$is_local 76835').

	Lee Naish

pds@quintus.UUCP (Peter Schachte) (05/12/88)

There are some problems with atom-based module systems.  I think that
whatever module system you choose, this test should succeed for any
atom anytime:

test(Atom) :-
	name(Atom, String),
	name(Atom, String).

Also, it should be possible to take a term representing a goal and do
both of the following to it, and get a term representing a different
goal in the same module:

prefix_term(Term, Term2) :-
	Term =.. [Pred|Args],
	name(Pred, Chars),
	append("prefix_",Chars,Chars2),
	name(Pred2,Chars2),
	Term2 =.. [Pred2|Args].

suffix_term(Term, Term2) :-
	Term =.. [Pred|Args],
	name(Pred, Chars),
	append(Chars,"_suffix",Chars2),
	name(Pred2,Chars2),
	Term2 =.. [Pred2|Args].

This is important for term_expansion/2.  An atom-based module system makes
it difficult to do both of these things.
-- 
-Peter Schachte
pds@quintus.uucp
...!sun!quintus!pds

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

In article <2747@mulga.oz>, lee@mulga.oz (Lee Naish) writes:
> The main uses of a module system are
> 	1) avoiding accidental name clashes, and
> 	2) protecting procedures from being called by anyone.
> 
> THEOREM: Every module system is either too complicated or
> 	 not powerful enough.
> 
> COROLLARY: It is impossible to get more than two people to agree on a
> 	   module system (the failure of the BSI module committee was
> 	   therefore inevitable).
> 
The initial sentence is precisely what my
algebra-for-constructing- programs paper disputed.  If you think
of a module system as an optional extra bolted on afterwards as
a means of protection, you can't expect it to work very well or
be liked much.  I claim that a better approach is to provide a
clean way of building programs out of fragments, which may have
hiding as one of its characteristics.  Examples of systems
taking this approach are CLEAR, EQLOG, Standard ML, and Lincoln
Wallen's paper last year.  I'm sure there are enough people who
like the Standard ML approach, and I _hope_ there are enough
people who like Lincoln's paper, to refute the corollary.  [As a
practical matter, everyone at Quintus likes the Quintus module
system, and the only complaints we've hard are that it isn't
powerful enough.  But then, it fails to be sufficiently powerful
in exactly the same way that Common Lisp does.]

I refrain from comment on Lee Naish's atom-based proposal.

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

In article <2747@mulga.oz> lee@mulga.UUCP (Lee Naish) writes:
>
>COROLLARY: It is impossible to get more than two people to agree on a
>	   module system (the failure of the BSI module committee was
>	   therefore inevitable).

I would like to thank you for your clear and reasonable remarks on
modules.  Your proposal too is reasonable.

The failure of the BSI module committee was perhaps inevitable, and it
was more or less because people could not agree, but that wasn't quite
all there was to it.

The main problem was that the personnel kept changing, and when new
people arrived they insisted on refighting all the old battles.  This
happened several times and made it very difficult to make progress.

My own view is that a more stable committee would have been able to
produce a proposal, or at least a document that attempted to set out
the issues fairly.  

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

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

In article <2747@mulga.oz> lee@mulga.UUCP (Lee Naish) writes:
>The main uses of a module system are
>	1) avoiding accidental name clashes, and
>	2) protecting procedures from being called by anyone.

I am pleased to see such a small list and am even willing to take out
the second item, requiring instead only that such calls cannot too
easily be made by accident.  Of course, it would be nice if module
systems had other desirable properties as well.

>Prolog module systems have to handle a bit more than module systems of
>conventional languages because of the ways in which data/code can be
>converted into other representations and converted back:

One of the disappointing aspects of the BSI work on modules was that
many of the arguments presented against atom-based schemes seemed based
almost entirely on misunderstanding, a tendency to think of modules in
terms derived from languages like Fortran and Ada, and prejudice against
Lisp, which had somehow been associated with the atom-based suggestions.
The idea seemed to be that anyone whose thinking had not been influenced
[I've tried to find a reasonably neutral word] by Lisp would immediately
see that only predicate-based schemes made sense.  It was sometimes
difficult to get them to acknowledge that Prolog might have reasons of
it's own, namely the presence of things like =..  and call/1, and
difficult to obtain a clear explanation of how their proposals would
solve such problems.

Please do not read the last paragraph as an attack on the points
made by Richard O'Keefe: it isn't.  I am thinking instead of things
presented during BSI module meetings.  Indeed, one of the things I was
hoping Richard might do is to provide a clear explanation of the sort I
have been missing.

-- Jeff

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

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

In article <958@sandino.quintus.UUCP> pds@quintus.UUCP (Peter Schachte) writes:
>
>There are some problems with atom-based module systems.

There are also problems with predicate-based systems.  I see nothing
wrong with a predicate-based scheme if those problems could be solved
in a reasonable way.  Indeed, I think enough of the Prolog community
dislikes atom-based schemes and sees no use for them that a predicate-
based system would be the less controversial choice.  As it is,
however, the choice seems to be between different imperfections, and I
don't see that making problems for things like name/2 is worse than
making problems for things like call/1.

>I think that whatever module system you choose, this test should
>succeed for any atom anytime:
>
>test(Atom) :-
>	name(Atom, String),
>	name(Atom, String).
>

I am having difficulty imagining a situation in which this test could
fail.  I suspect this is my failing rather than yours, and so I would
find an explanation useful.


>Also, it should be possible to take a term representing a goal and do
>both of the following to it, and get a term representing a different
>goal in the same module:
>
>prefix_term(Term, Term2) :-   [...]
>
>suffix_term(Term, Term2) :-   [...]

>This is important for term_expansion/2.  An atom-based module system makes
>it difficult to do both of these things.

I am not sure whether "both" is supposed to refer to prefix and suffix
or to (prefix / suffix) and test.  This may seem an minor point, but 
there are systems where suffix would work but prefix would not.  Does
term_expansion/2 require both prefix and suffix?

Anyway, it is possible to write prefix_term and suffix_term in some
atom-based schemes (ones where the module name is not part of the
atom name), just not exactly as you've given them.  Since they may
have problems in Prolog as it is now -- the prefixed or suffixed
term might already exist and be used for a different purpose --
such things might be better off with an atom-based module system.

-- Jeff

pds@quintus.UUCP (Peter Schachte) (05/17/88)

In article <439@aiva.ed.ac.uk>, jeff@aiva.ed.ac.uk (Jeff Dalton) writes:
> In article <958@sandino.quintus.UUCP> pds@quintus.UUCP (Peter Schachte) writes:
> >I think that whatever module system you choose, this test should
> >succeed for any atom anytime:
> >
> >test(Atom) :-
> >	name(Atom, String),
> >	name(Atom, String).
> I am having difficulty imagining a situation in which this test could
> fail.

Silly me.  How about this:

test(Atom) :-
	name(Atom, String),
	name(Atom2, String),
	Atom=Atom2.

This test will fail in a atom-based module system where the module name
is not part of the name proper.  This is the case with CommonLisp:

(defun test (sym)
	(eq sym (intern (symbol-name sym))))

(test 'pkg:symbol)

will fail (return nil) if pkg isn't the current package.

Of course, this is easily worked around, but the code must know about
modules.  I would like whatever module system anyone supplies to be
as compatible as possible with existing Prolog code.

> > ...[code that takes terms and creates new terms with the same args,
> >     but where the functor has some extra chars on the front or back]
> >This is important for term_expansion/2.  An atom-based module system makes
> >it difficult to do both of these things.
> 
> I am not sure whether "both" is supposed to refer to prefix and suffix
> or to (prefix / suffix) and test.

Yea, that was ambiguous.  I meant some module systems might let me do
only one, but not both, of these.  As you say, an atom-based scheme
which puts extra characters into an atom's name will have trouble with
one or both of these.

I'm afraid I have a knee-jerk reaction to atom-based module schemes,
because I've used CommonLisp.  I spent a weekend once (I mean a whole
weekend, starting Saturday morning, and not stopping until Monday
night) trying to solve symbol-visibility problems in a large system.
Ultimately, I gave up.  I just couldn't get the visibility the way I
wanted it.  And this was not the first or last time I had to do battle
with the package system.

I know that there are problems with predicate-based module systems,
too.  I don't find them quite as objectionable, though.  Maybe what I
like about the predicate-based systems is that it just makes more sense
to me to put predicates, rather than atoms, into separate modules.
-- 
-Peter Schachte
pds@quintus.uucp
...!sun!quintus!pds