[comp.lang.prolog] PROLOG Digest V5 #36

PROLOG-REQUEST@SUSHI.STANFORD.EDU (Chuck Restivo, The Moderator) (05/10/87)

PROLOG Digest            Monday, 11 May 1987       Volume 5 : Issue 36

Today's Topics:
                      Puzzle - Metainterpreter,
                       Query - Standardization,
              Implementation - Self Reproducing Programs
----------------------------------------------------------------------

Date: 9 May 87 07:49:49 GMT
From: Arun Lakhotia <cbatt!cwruecmp!arun@ucbvax.Berkeley.EDU>  
Subject: A meta puzzle

While the subject of meta-interpreters is still on, let me give an
interesting coffee time puzzle.

  solve(true,true).
  solve((GoalA,GoalB),(GoalC,GoalD)):-
      solve(GoalA,GoalC),
      solve(GoalB,GoalD).
  solve(GoalA,GoalB) :-
      sys(GoalA),
      sys(GoalB),
      call(GoalA),
      call(GoalB).
  solve(HeadA,HeadB) :-
      clause(HeadA,BodyA),
      clause(HeadB,BodyB),
      solve(BodyA,BodyB).

Q? For what class of programs would solve(GoalA,GoalB)
   be equivalent to solve(GoalA), solve(GoalB).

Q? If solve(GoalA,GoalB) is true then can one make any comment about
   the relation between the proof-tree, search tree for the two goals.
   with (or without :-)) respect to solve(GoalA) and solve(GoalB).

Q? Can any comment be made about the relation between the clauses that
   are used for asserting GoalA and GoalB for solve(GoalA,GoalB) to be
   true.

   where solve(Goal) is as follows.

solve(true).
solve((GoalA,GoalB)) :-
     solve(GoalA),
     solve(GoalB).
solve(Goal) :-
     sys(Goal),
     call(Goal).
solve(Head) :-
     clause(Head,Body),
     solve(Body).


BACKGROUND

For people who may be interested in the source of this program.
The program is the result of composition of  meta-interpreters.

I took the clause

    solve(GoalA,GoalB) :- solve(GoalA), solve(GoalB).

and applied some simple fold/unfold transformation on it, with a
strategy to unfold the same clause for both the goals simultaneously.
With a little more story I got the program solve(GoalA,GoalB).

The complete semantics of the program is still a puzzle to me.

One statement that I could make is

   solve(GoalA,GoalB) implies (solve(GoalA), solve(GoalB))

-- Arun Lakhotia

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

Date: 5 May 87 10:38:00 EST
From: John Cugini <cugini@icst-ecf.arpa>
Subject: Standardization

I haven't seen any messages on the net lately about standardization
for Prolog.  Is anything going on?  Maybe someone who is involved
could send us a summary of recent activities?

For what it's worth, the CommonLisp people have been very busy,
both in the US, through X3J13, and abroad - I believe there is
a Lisp working group forming within ISO.  The Lispers make very
active use of their mailing list to thrash out technical issues.
This is nice, because those who don't have the time or money
to attend meetings can still participate in technical discussions.
Personally, I'd like to see a similar arrangement for Prolog.

-- John Cugini

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

Date: 5 May 87 03:44:02 GMT
From: Arun Lakhotia <cbatt!cwruecmp!arun@ucbvax.Berkeley.EDU>  
Subject: Self Peproducing Program With Variables

Reference a comment in my previous posting regarding
   Variables in a self-reproducing Prolog program.

Here is a s-r program (clone/0) generator. The program when run would
produce a prolog program that when run would reproduce itself Variable
for Variable, and blank for blank.  (a la Kernigham's Turing award
lecture style)

%% -----
numbervars(Name, N, N1) :-
    var(Name),
    Temp is 65 + N,                    % 65 = 'A'
    name(Name, [Temp]),
    N1 is N +1.
numbervars(Term, N1, N2) :-
    nonvar(Term),
    functor(Term, Name, N),
    numbervars(0,N,Term,N1,N2).

numbervars(N,N,Term,N1,N1).
numbervars(I,N,Term,N1,N3) :-
    I < N,
    I1 is I +1,
    arg(I1,Term,Arg),
    numbervars(Arg,N1,N2),
    numbervars(I1,N,Term,N2,N3).

display_clause(X) :-
    numbervars(X,0,_),
    write(X),
    write('.'),
    nl,
    fail.
display_clause(X).

display_clauses(F/A) :-
    functor(X,F,A),
    clause(X,B),
    display_clause((X:-B)),
    fail.
display_clauses(_).

clone :-
    display_clauses(numbervars/3),
    display_clauses(numbervars/5),
    display_clauses(display_clause/1),
    display_clauses(display_clauses/1),
    display_clauses(clone/0).

%% ---
Ofcourse i take my words back regarding the the difficulty
(or impossibility) of writing a 'portable' s-r Prolog program
with variables.

The correctness of the above program is constrained by the
assumption that there exist no other clauses in the program
database of same functor and arity as in the program above.

-- Arun Lakhotia

PS: The program would not run on Prolog implementation that
    cannot readback 'write/1' output.

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

Date: 5 May 87 17:45:19 GMT
From: Barton E. Schaefer <hp-pcd!uoregon!omepd!littlei!ogcvax!schaefer
                         @hplabs.hp.com>
Subject: Self Reproducing Programs

The following predicate, invoked as

        ?- everyclause(everyclause(_,_),X).

will remove itself from the database, binding X to a list of all its
clauses in the process, then put itself back again.

/* `everyclause(X,Y)' returns in Y a list of all clauses whose heads have the
    same functor and arity as X.

   `everyclause' works by  calling the primitive `clauses', retracting the
    clause found, recurring to find the next clause, and then re-asserting the
    retracted clause.  It cannot be used to test directly that a list contains
    every clause; its second argument must be a variable.
 */

/* Since `clause' fails with an error if called with a variable in its first
   argument, `everyclause' fails if it would have to make such a call.
*/

everyclause(X,Y) :-
    var(X), !,
    fail.

/* The useful part of `everyclause'.
*/
everyclause(X,[]) :-
    not clause(X,_), !.
everyclause(X,[Y|Z]) :-
    var(Y), !,
    functor(X,F,N),
    X =.. [F|N1],
    newvars(N1,N2),
    A =.. [F|N2],
    clause(A,C),
    Y = (A :- C),
    functor(B,F,N),
    clause(B,D),
    retract((B :- D)),
    ((everyclause(X,Z), !,
    asserta((B :- D)));
    (asserta((B :- D)), !)).

newvars(X,X) :- atomic(X).
newvars(X,Y) :- var(X).
newvars((X1,Y1),(X2,Y2)) :- !,
    newvars(X1,X2),
    newvars(Y1,Y2).
newvars([H1|R1],[H2|R2]) :- !,
    newvars(H1,H2),
    newvars(R1,R2).
newvars(X,Y) :-
    X =.. [F|A],
    newvars(A,B),
    Y =.. [F|B].

-- Bart Schaefer

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

End of PROLOG Digest
********************