Prolog findall/3: more than one bag - prolog

I'm writing AI for a Fox and Geese type of game. One of my predicates looks like this:
moveFox(+PrevState, -NextState, -PegList, +VisitedStates, -NewVisitedStates)
It takes a game state and makes a move with a fox. The resulting state is unified with NextState and the actual move is unified with PegList. Everything works as expected.
I am calculating the utility score for all of the moves' NextState. To be able to find the state with the highest utility score, I use findall/3 to get all states in a list before comparing their utility scores.
findall(NextState, moveFox(...), NextStatesList)
By finding the maximum utility score I know the NextState (as well as its position in the list) with the highest utility score. There is only one problem, currently I haven't written any predicate to infer which move was made to come to NextState, e.g.:
getMove(+PrevState, +NextState, -PegList)
Instead of writing such a predicate, I would much rather use findall/3 or equivalent. My question is if there is some way to get two different variables in two different lists. I'm thinking like this (if it would have worked):
findall([NextState, PegList], moveFox(...), [NextStatesList, MoveList])
Could I implement such functionality without having to either run findall/3 twice (ugly overhead) or write that getMove(+PrevState, +NextState, -PegList) predicate?

this problem can be tackled building a list of pairs, and then separating the elements, like library(pairs) does
...
findall(NextState-PegList, moveFox(...), Pairs),
pairs_keys_values(Pairs, NextStates, Pegs),
...
If your Prolog doesn't have pairs_keys_values/3, it's easy to write either with maplist or via a recursive predicate. Here is the maplist way:
pkv(K-V, K, V).
pairs_keys_values(Pairs, Keys, Vals) :-
maplist(pkv, Pairs, Keys, Vals).

Related

Prolog: Looping through elements of list A and comparing to members of list B

I'm trying to write Prolog logic for the first time, but I'm having trouble. I am to write logic that takes two lists and checks for like elements between the two. For example, consider the predicate similarity/2 :
?- similarity([2,4,5,6,8], [1,3,5,6,9]).
true.
?- similarity([1,2,3], [5,6,8]).
false.
The first query will return true as those two lists have 5 and 6 in common. The second returns false as there are no common elements between the two lists in that query.
I CANNOT use built in logic, such as member, disjoint, intersection, etc. I am thinking of iterating through the first list provided, and checking to see if it matches each element in the second list. Is this an efficient approach to this problem? I will appreciate any advice and help. Thank you so much.
Writing Prolog for the first time can be really daunting, since it is unlike many traditional programming languages that you will most likely encounter; however it is a very rewarding experience once you've got a grasp on this new style of programming! Since you mention that you are writing Prolog for the first time I'll give some general tips and tricks about writing Prolog, and then move onto some hints to your problem, and then provide what I believe to be a solution.
Think Recursively
You can think of every Prolog program that you write to be intrinsically recursive in nature. i.e. you can provide it with a series of "base-cases" which take the following form:
human(John). or wildling(Ygritte) In my opinion, these rules should always be the first ones that you write. Try to break down the problem into its simplest case and then work from there.
On the other hand, you can also provide it with more complex rules which will look something like this: contains(X, [H|T]):- contains(X, T) The key bit is that writing a rule like this is very much equivalent to writing a recursive function in say, Python. This rule does a lot of the heavy lifting in looking to see whether a value is contained in a list, but it isn't complete without a "base-case". A complete contains rule would actually be two rules put together: contains(X, [X|_]).
contains(X, [H|T]):-contains(X, T).
The big takeaway from this is to try and identify the simple cases of your problem, which can act like base cases in a recursive function, and then try to identify how you want to "recurse" and actually do work on the problem at hand.
Pattern Matching
Part of the great thing about Prolog is the pattern matching system that it has in place. You should 100% use this to your advantage whenever you can -- it is especially helpful when trying to do anything with lists. For example:
head(X, [X|T]).
Will evaluate to true when called thusly: head(1, [1, 2, 3]) because intrinsic in the rule is the matching of X. This sort of pattern matching on the first element of a list is incredibly important and really the key way that you will do any work on lists in Prolog. In my experience, pattern matching on the head of a list will often be one of the "base-cases" that I mentioned beforehand.
Understand The Flow of the Program
Another key component of how Prolog works is that it takes a "top-down" approach to reading code. What I mean by that is that every time a rule is called (except for definitions of the form king(James).), Prolog starts at line 1 and continues until it reaches a rule that is true or the end of the file. Therefore, the ordering of your rules is incredibly important. I'm assuming that you know that you can combine rules together via a comma to indicate logical AND, but what is maybe more subtle is that if you order one rule above another, it can act as a logical OR, simply because it will be evaluated before another rule, and can potentially cause the program to recurse.
Specific Example
Now that I've gotten all of my general advice out of the way, I'll actually reference the given problem. First, I'd write my "base-case". What would happen if you are given two lists whose first elements are the same? If the first element in each list is not the same, then they have to be different. So, you have to look through the second list to see if this element is contained anywhere in the rest of the list. What kind of rule would this produce? OR it could be the case that the first element of the first list is not contained within the second at all, in which case you have to advance once in the first list, and start again with the second list. What kind of rule would this produce?
In the end, I would say that your approach is the correct one to take, and I have provided my own solution below:
similarity([H|_], [H|_]).
similarity(H1|T1], [_|T2]):- similarity([H1|T1], T2).
similarity([_|T1], [H2|T2]):- similarity(T1, [H2|T2]).
Hope all of this helps in some way!

Prolog subBag(x, y) tests whether x, considered as a bag, is a subbag of y

I currently working on some prolog problems, one is "subBag(x, y) tests whether x, considered as a bag, is a subbag of y". My code doesn't work at all and always true. Here is my code.
delete(X,[],[]).
delete(X,[X|T],T).
delete(X,[H|T],[H|Result]):-
delete(X,T,Result).
subBag([],[]).
subBag([],[H|T]).
subBag([X|S],[H|T]):-
member(X,[H|T]),
delete(X,[H|T],Result),
subBag(S,Result).
Thank you.
What is a subbag? I take that to mean, all the items in the subbag are present in at least the same quantities as they are in the containing bag. To state it inductively, let's break it into two cases: the case where I have an empty list. Is that a subbag? Yes, of any list:
subbag([], Bag) :- is_list(Bag).
Now, the inductive case. Let's break the subbag into an item and the rest of the subbag. If this item can be removed from the containing bag, and the rest form a subbag of the remainder from the containing bag, then we have a subbag. Like so:
subbag([X|Subbag], Bag) :-
select(X, Bag, RemainingBag),
subbag(Subbag, RemainingBag).
The magic predicate select/3 is a hugely useful utility here, allowing you in one statement to say X is in Bag, and the rest of the bag is in RemainingBag. This kind of situation seems to come up all the time in processing lists in Prolog. (Note that in the SWI Prolog documentation, there is often a little orange :- icon next to the name, which will take you to the source code for that predicate, in case you've been given a stupid requirement not to use a built-in predicate by a clueless professor.)
I want to warn you that the efficiency of this solution is not great, but I actually think the nature of this problem might just be that way. The number of solutions you'll obtain from an query (like subbag(X, [1,2,3,4,5])) is going to be large; I found it to be essentially the number of permutations of a set, using the OEIS (sequence A000522).
I dont understand completely how your code should work, but i think that there is for sure too much splitting into head and tail in places where it is not necessary.
Maybe this predicate will help you to solve your problem.
isSublist(Sublist,List) :-
append([_,Sublist,_],List).
This predicate uses append/2 build-in predicate, read about it here

How to iterate through structure?

If I have a list like: [atm(abd,bubu,ha), atm(aei),atm(xyz,huhu), atm(aabb,a,e,x)], how could I 'iterate' through the elements of one of the atm structures?
For example, for atm(abd, bubu, ha), I would like to write abd, bubu and ha.
The problem is that the structures have variable length.
Is there a way to transform the structure into a list? Thanks.
Using (=..)/2
#TopologicalSort has already given a nice answer, using (=..)/2 to convert a term to a list of functor and arguments.
This obviously solves the immediate problem very generally.
However, it comes with its own drawbacks too: First and most importantly, (=..)/2 is not a general relation. For example, we have:
?- X =.. Y.
ERROR: Arguments are not sufficiently instantiated
This means that we cannot use this construct to generate solutions. It works only if its arguments are sufficiently instantiated.
Second, using (=..)/2 also comes with the time and memory overhead of constructing and representing a list in addition to the term that is already there in a different form. (And, mutatis mutandis, in the other direction too of course.)
Thus, it may be worth to ask: Are there different ways to solve this task? Are they better suited?
Alternative 1: Doing it manually
How do I convert thee? Let me count the ways.
From the example you cite, we must be able to handle—in order of their appearance—terms of the following forms:
atm/3
atm/1
atm/2
atm/4
The point here is that the number of shown cases is finite, and so we can easily handle them all like this:
atm_list(atm(A), [A]).
atm_list(atm(A,B), [A,B]).
atm_list(atm(A,B,C), [A,B,C]).
atm_list(atm(A,B,C,D), [A,B,C,D]).
To convert a list of such terms, you can use maplist/2:
?- Ls = [atm(abd,bubu,ha), atm(aei),atm(xyz,huhu), atm(aabb,a,e,x)],
maplist(atm_list, Ls, Lists).
Ls = [atm(abd, bubu, ha), atm(aei), atm(xyz, huhu), atm(aabb, a, e, x)],
Lists = [[abd, bubu, ha], [aei], [xyz, huhu], [aabb, a, e, x]].
A major advantage is that this relation is very general and can also be used to generate answers:
?- atm_list(A, Ls).
A = atm(_27464, _27466, _27468),
Ls = [_27464, _27466, _27468] ;
A = atm(_27464),
Ls = [_27464] ;
A = atm(_27464, _27466),
Ls = [_27464, _27466] ;
A = atm(_27464, _27466, _27468, _27470),
Ls = [_27464, _27466, _27468, _27470].
This is also more efficient than using (=..)/2. Clearly, it can only be done if the number of arising cases is finite. (Exercise: Write a Prolog program that generates clauses for all integers 1..N).
Alternative 2: Using lists
There are several well-known criteria for judging whether lists are an appropriate data structure. For example:
Does the empty list make sense in your use case?
Are there sensible cases for all possible lengths?
etc.
Only you can answer this question for your particular use case, so I only show what it could look like: Suppose you represent your whole initial list as follows:
[[abd,bubu,ha],[aei],[xyz,huhu],[aab,a,e,x]]
Then the whole issue does not even arise, because the elements are already specified as lists. Thus, there is no more need to convert anything.
Sure.
If First is atm(abd,bubu,ha) (for example), this code will split it into a list you can go through.
First =.. List.
Then, List will be [atm, abd, bubu, ha].
IDK if this works in your particular version of PROLOG. I'm using SWI-PROLOG. If not, maybe your version has a similar predicate.
For more information, see http://www.swi-prolog.org/pldoc/doc_for?object=(%3D..)/2 .

Prolog manual or custom labeling

I am currently writing a solver for a floor planning problem in Prolog and have some issues with the labeling part.
The current problem is my constraints are posted but when I launch the labeling, it takes forever to find a solution. I would like to bring in some heuristics.
My question is, how do I manually label my variables ? I am afraid that after defining a clpfd variable like this :
X in Xinf..Xsup
and constraining it, If I do something like :
fd_sup(X, Xmax),
X = Xmax,
...
in my custom label, I won't be using the backtrack ability of Prolog to test the other values of X's domain. Am I wrong ?
Also, is there a smarter way to label my variables than writing custom labeling procedures ? My idea of heuristics would consist in trying extrema of a variable domain alternatively (like max(X), min(X), max(X-1), min(X-1) etc...)
Hope you can help me :)
It is not difficult to write a custom labeling procedure, and with most real problems you will eventually need one anyway in order to incorporate problem-specific heuristics.
The two main components of a labeling procedure are
variable selection: from all the remaining (i.e. not yet instantiated) problem variables, pick one to consider next.
value selection or branching: explore, via backtracking, two or more alternative sub-problems by reducing the chosen variable's domain in (usually) complementary ways.
Using this scheme, the default labeling procedure can be written as
label(Xs) :-
( select_variable(X, Xs, Xs1) ->
branch(X),
label(Xs1)
;
true % done, no variables left
).
select_variable(X, [X|Xs], Xs). % 'leftmost' strategy
branch(X) :- indomain(X).
You can now redefine select_variable/3 to implement techniques such as "first-fail", and redefine branch/1 to try domain values in different orders. As long as you make sure that branch/1 enumerates all of X's domain values on backtracking, your search remains complete.
Sometimes you want to try just one domain value first (say, one suggested by a heuristics), but, if it is no good, not commit to another value immediately.
Let's say that, as in your example, you want to try the maximum domain value first. You could write this as
branch(X) :-
fd_sup(X, Xmax),
(
X = Xmax % try the maximum
;
X #\= Xmax % otherwise exclude the maximum
).
Because the two cases are complementary and cover all possible values for X, your search is still complete. However, because of the second alternative, branch/1 can now succeed with an uninstantiated X, which means you must make sure in the labeling procedure that you don't lose this variable from your list. One possibility would be:
label(Xs) :-
( select_variable(X, Xs, Xs1) ->
branch(X),
( var(X) -> append(Xs1, [X], Xs2) ; Xs2=Xs1 ),
label(Xs2)
;
true % done, no variables left
).
First, always try built-in heuristics. ff is often a good strategy.
For custom labeling strategies, it is often easiest to first convert the domain to a list, then reorder the list, and then simply use member/2 to assign the values of the domain using the new order.
A good building black is dom_integers/2, relating a finite CLP(FD) domain to a list of integers:
:- use_module(library(clpfd)).
dom_integers(D, Is) :- phrase(dom_integers_(D), Is).
dom_integers_(I) --> { integer(I) }, [I].
dom_integers_(L..U) --> { numlist(L, U, Is) }, Is.
dom_integers_(D1\/D2) --> dom_integers_(D1), dom_integers_(D2).
Your specific strategy is easily expressed on a list of such ordered integers, relating these integers to a second list where the values occur in the order you describe:
outside_in([]) --> [].
outside_in([I]) --> [I].
outside_in([First|Rest0]) --> [First,Last],
{ append(Rest, [Last], Rest0) },
outside_in(Rest).
Sample query and result:
?- phrase(outside_in([1,2,3,4]), Is).
Is = [1, 4, 2, 3] ;
false.
Combining this with fd_dom/2 and dom_integers/2, we get (bindings for variables other than X omitted):
?- X in 10..20,
fd_dom(X, Dom),
dom_integers(Dom, Is0),
phrase(outside_in(Is0), Is),
member(X, Is).
X = 10 ;
X = 20 ;
X = 11 ;
X = 19 ;
X = 12 ;
X = 18 ;
etc.
Nondeterminism is preserved by member/2.
Make sure to distinguish labeling strategies from additional propagation. These two aspects are currently a bit mixed in your question.
In SWI-Prolog, there is a predicate called clpfd:contracting/1. It does what you describe: It tries values from the domain boundaries, and removes values that can be seen as inconsistent, i.e., for which it is known that no solution exists.
Therefore, if you have a list of variables Vs, you can try: clpfd:contracting(Vs), and see if this helps.
Note that this can also significantly slow down the search, though on the other hand, also help significantly to reduce the search space before even trying any labeling!
To complement the other answers (one contrasting labeling and propagation, one showing a dedicated labeling method), I now tackle a further very important aspect of this question:
Very often, when beginners complain about the speed of their code, it turns out that their code in fact doesn't even terminate! More efficiency would not help in that case.
Hence, this answer points you towards first ensuring actual termination of your relation.
The best way to ensure termination of CLP(FD) programs is to separate them into 2 parts:
the first, called the core relation, simply posts all constraints.
the second uses labeling/2 to perform the actual search.
Have you done this in your program? If not, please do. When this is done, make sure that the core relation, say solution/2 (where the arguments are: a term denoting the task instance, and the list of variables to be labeled) terminates universally by querying:
?- solution(Instance, Vs), false.
If this terminates, then the following also terminates:
?- solution(Instance, Vs), label(Vs), false.
Of course, in larger tasks, you have no chance to actually witness the termination of the latter query, but a good chance to witness the termination of the first query, because setting up the constraints is often much faster than actually obtaining even a a single solution.
Therefore, test whether your core relation terminates!
This follows up on this previous answer by #mat.
If you have got some more CPU cycles to burn, try shave_zs/1 as defined in this previous answer.
shave_zs/1 kind of works like the auxiliary library predicate clpfd:contracting/1. Unlike contracting/1, however, all values are "up for grabs"—not just the ones at the boundary. YMMV!

State propagation during bactracking in Prolog

Let's assume, that I have a simple program in Prolog, which is searching through a certain state space:
search(State, State) :-
is_solution(State).
search(State, Solution) :-
generate(State, NewState),
search(NewState, Solution).
And I know that:
generate(State, NewState) is producing at least one NewState for any given State
the whole states space is finite
I want to modify the search predicate to ensure that it always manages to check in a finite time. So I write something like:
search(State, Solution) :-
empty_memory(EmptyMem),
add(State, EmptyMem, Memory),
search(State, Memory, Solution).
search(State, _, State) :-
is_solution(State).
search(State, Memory, Solution) :-
generate(State, NewState),
\+ exist(NewState, Memory),
add(NewState, Memory, NewMemory),
search(NewState, NewMemory, Solution).
which is working, but it's losing computed states during backtracking, so now I have a search tree with maximum height of space size.
Is it any way to propagate a state during the backtracking without losing any computed information? I want to have a whole search tree with O(space_size) nodes. Is it possible?
EDIT:
It seems that I should use assert/[1,2] in order to dynamically create new clauses which will serve as a global memory.
In SICStus Prolog, you can use the blackboard to store information across backtracks: see Blackboard Primitives in the manual. Use bb_put(Key, Value) to store something on the blackboard, and bb_get(Key, Value) to retrieve it. Note that the bloackboard is defined per module.
The most clean solution will likely be to use a Prolog compiler that supports tabling like B-Prolog, Ciao, XSB, or YAP. In this case, you would simply declare the generate/2 predicate as tabled.
Instead of using assert, why not generate all possible states with findall(N, generate(S,N),ALL). This will eliminate the need for backtracking and will explicate the search space tree, which then could be preorder-traversed while passing along the visited-so-far states as additional argument.

Resources