[comp.lang.prolog] Probabilistic 'or'?

jha@lfcs.ed.ac.uk (Jamie Andrews) (08/04/88)

     Does anyone know of a Prolog or other LP system with a
probabilistic 'or' or probabilistic clause selection?  What I mean by
this is a clause selection rule or disjunct selection rule which
randomly selects which branch to follow and which to put in the
backtrack stack.  A weighting on the branches would be useful, too.

     I guess I'm mainly interested in this for game program purposes.
The only thing it would accomplish is a random permutation of the
solutions to a query, but this would be very useful for (say) a maze
generation program; there may be thousands of possible mazes, but
you might just want some random one out of those, without having to
generate all of them.  With the probablistic 'or', you could just
specify what something has to be to be a maze, and let the system
give you a random instance.

     I guess it would be easy enough to write a predicate with
clause/1 and some system random call, but this would make the code
more messy, and (if we care about such things today) would raise
logical problems.

thanks
--Jamie.
  jha@lfcs.ed.ac.uk
"I wanted to be with you alone, and talk about the weather"

ok@quintus.uucp (Richard A. O'Keefe) (08/06/88)

In article <613@etive.ed.ac.uk> jha@lfcs.ed.ac.uk (Jamie Andrews) writes:
>
>     Does anyone know of a Prolog or other LP system with a
>probabilistic 'or' or probabilistic clause selection?  What I mean by
>this is a clause selection rule or disjunct selection rule which
>randomly selects which branch to follow and which to put in the
>backtrack stack.  A weighting on the branches would be useful, too.

This doesn't need to be a language primitive.  For example, Quintus
Prolog comes with library(random), which includes things like

	random(Lower, Upper, Choice)
	random_permutation(List, Perm)

amongst others.  Suppose you have

	p(~args~) :- ~clause 1~.
	...
	p(~args~) :- ~clause 7~.

and you would like to try the clauses in random order.  Just do

	p(~args~) :-
		random_permutation([1,2,3,4,5,6,7], Perm),
		member(Index, Perm),
		p(Index, ~args~).

	p(1, ~args~) :- ~clause 1~.
	...
	p(7, ~args~) :- ~clause 7~.

If you want to pick a clause at random and stick to it, it's even easier:

	p(~args~) :-
		random(1, 7, Index),
		p(Index, ~args~).

Just use standard methods for generating and applying random numbers.

ok@quintus.uucp (Richard A. O'Keefe) (08/06/88)

In article <613@etive.ed.ac.uk> jha@lfcs.ed.ac.uk (Jamie Andrews) writes:
>
>generate all of them.  With the probablistic 'or', you could just
>specify what something has to be to be a maze, and let the system
>give you a random instance.
>
>     I guess it would be easy enough to write a predicate with
>clause/1 and some system random call, but this would make the code
>more messy, and (if we care about such things today) would raise
>logical problems.

Um, "a random instance" doesn't mean a lot.  What DISTRIBUTION do you
want?  Are mazes with 500,000 cells to be as likely as ones with 5?
Take a simpler example: a random graph with vertices 1..N for given fixed N.
Just what _is_ a "random graph"?  Are all arcs equally likely?  HOW likely?
What distribution of out-degrees?  Just think about this:
if I write a random predicate
	random_list([]) <*- true.
	random_list([_|L]) <*- random_list(L).
and ask
	| ?* random_list(L).
_any_ length is permitted:  if your random LP system goes off for a million
years computing a list of 10**30 elements, it has a perfect right to.  I
wouldn't even be entitled to object if it did this nearly every time.  By
the time you've specified the distribution (what if it is input-dependent?)
you've written as much code as if you'd called library routines.

Having thought about it a bit, I believe that it would raise far worse
logical problems to try to build randomness into the language; pseudo-random
number generators can after all be specified with pure predicates--they're
just ordinary arithmetic functions.

debray@arizona.edu (Saumya Debray) (08/06/88)

In article <613@etive.ed.ac.uk>, jha@lfcs.ed.ac.uk (Jamie Andrews) writes:
> 
>      Does anyone know of a Prolog or other LP system with a
> probabilistic 'or' or probabilistic clause selection?  What I mean by
> this is a clause selection rule or disjunct selection rule which
> randomly selects which branch to follow and which to put in the
> backtrack stack. 

This is something I've thought about on and off.  One reason it would be
useful is that while a complete logic programming system would require
a fair clause selection rule (fair literal selection if you have negation),
and fairness is typically expensive to implement.  However, one could use
randomized clause selection to implement a system that would be complete
with probability 1 (i.e., almost always).  Of course, you randomize if and
only if you're about to create a choice point, so deterministic goals
aren't penalized.
-- 
Saumya Debray		CS Department, University of Arizona, Tucson

     internet:   debray@arizona.edu
     uucp:       arizona!debray

lee@mulga.oz (Lee Naish) (08/07/88)

In article <6570@megaron.arizona.edu> debray@arizona.edu (Saumya Debray) writes:
>one could use
>randomized clause selection to implement a system that would be complete
>with probability 1

What about the following program?

	p :- loop.
	p.
	loop :- loop.

Unless you also abandon depth first search, selecting the first clause
for p will result in the successful derivation not being found.

	lee

jha@lfcs.ed.ac.uk (Jamie Andrews) (08/08/88)

     I liked Richard's idea of
rand_pred(...) :-
  random_permutation([1,2,3,4,5,6,7], perm),
  mem(clause_no, perm),
  rand_pred(clause_no, ...).
rand_pred(1, ...) :-
  ...
  ...
rand_pred(7, ...) :-
  ...

...but I still think this is a little messy, and not as natural
as having random clause selection.  Besides, random_permutation
either generates 7! calls to every clause (if it returns all
permutations on backtrack) or else it adds some more
incompleteness to the system (if it returns only one).

In article <257@quintus.UUCP> ok@quintus.UUCP (Richard A. O'Keefe) writes:
>Um, "a random instance" doesn't mean a lot.  What DISTRIBUTION do you
>want?  Are mazes with 500,000 cells to be as likely as ones with 5?

     This is essentially what I meant by wanting a weighting on
the probability of picking a clause.

>Having thought about it a bit, I believe that it would raise far worse
>logical problems to try to build randomness into the language; pseudo-random
>number generators can after all be specified with pure predicates--they're
>just ordinary arithmetic functions.

     What I meant was:  we get the system to select clauses
randomly (but without repeating the selection of a clause),
instead of always selecting them in sequence.  This does not
affect the soundness of the system.  Also, we would still have
the same degree of incompleteness, in the sense that if the
system happens to pick a clause which leads to an infinite loop,
it's sunk, just as if the first clause happens to lead to an
infinite loop.

--Jamie.
  jha@lfcs.ed.ac.uk
"I want the answers quickly, but I don't have no energy"

ok@quintus.uucp (Richard A. O'Keefe) (08/11/88)

In article <628@etive.ed.ac.uk> jha@lfcs.ed.ac.uk (Jamie Andrews) writes:
>In article <257@quintus.UUCP> ok@quintus.UUCP (Richard A. O'Keefe) writes:
>>Um, "a random instance" doesn't mean a lot.  What DISTRIBUTION do you
>>want?  Are mazes with 500,000 cells to be as likely as ones with 5?
>
>     This is essentially what I meant by wanting a weighting on
>the probability of picking a clause.

I see that I did not express myself plainly.
The point is that
 -- simple distributions defined on clause selection may yield complicated
    or unintuitive distributions on *results*
 -- simple distributions on *results* may require complicated distributions
    on clause selection
 -- therefore obtaining the distribution one wants on results may
    require at least as much ``programming'' to specify the elementary
    choice probabilities as calling library routines would have involved.

To try to make this clearer, let's consider just about the simplest
possible example.  Let's have a version of member/2 which tries its
clauses in a randomly chosen order so that each element has an equal
chance of being chosen first.  (To keep things simple, assume that
the list argument is ground and the element argument unbound.)

membof(L, X) :<prob1>- L = [X|_].
membof(L, X) :<prob2>- L = [_|T], membof(T, X).

where the idea is that with probability prob1 we try the first clause,
then the second clause, or with probability prob2=1-prob1 we try the
second clause, then the first clause.

THERE IS NO FIXED NUMBER prob1 WHICH WILL YIELD THE DESIRED RESULT.

We have to *compute* prob1 from the arguments.  Specifically,
prob1=1/length(L).  Now, if we just plug that formula in, and write

membof(L, X) :< 1/length(L) >- L = [X|_].
membof(L, X) :<1-1/length(L)>- L = [_|T], membof(T, X).

then we're doing a huge amount of extra work.  It would be a VERY
clever compiler (able to prove theorems in probability theory) which
could optimise this.  We could do it ourselves, producing

membof(L, X) :-
	length(L, N),
	N > 0,
	membof(L, N, X).

membof(L, N, X) :< 1/N >, L = [X|_].
membof(L, N, X) :<1-1/N>, L = [_|T], M is N-1, membof(T, M, X).

By the time you have done this much programming, you find that the
built-in randomising has helped you very little.