Write a Prolog program to model a gorilla moving across a grid - prolog

I have done very little programming in Prolog and find it quite difficult so far.
I was given the question: A gorilla moves along an 8x8 grid and can only move right or up. it has to remain within the grid and must finish at (8,8) starting at any arbitrary location.
Write a move predicate that describes all the possible moves.
My attempt:
move(X,Y,X+1,Y).
move(X,Y,X,Y+1).
Write a path predicate that uses the move predicate to determine the path thte robot shuld take.
My attempt:
path('right'):-
move(X,Y,X+1,Y).
path('up'):-
move(X,Y,X,Y+1).
Write prolog predicates that model blockages at (1,2), (4,2), and (4,1).
So far, from what I have found it seems I need to set up a list that would give all possible positions.
I have written a list of the possible positions but do not understand how to implement it:
[(1,1),(1,2),(1,3),(1,4),(1,5),(1,6),(1,7),(1,8),
(2,1),(2,2),(2,3),(2,4),(2,5),(2,6),(2,7),(2,8),
(3,1),(3,2),(3,3),(3,4),(3,5),(3,6),(3,7),(3,8),
(4,1),(4,2),(4,3),(4,4),(4,5),(4,6),(4,7),(4,8),
(5,1),(5,2),(5,3),(5,4),(5,5),(5,6),(5,7),(5,8),
(6,1),(6,2),(6,3),(6,4),(6,5),(6,6),(6,7),(6,8),
(7,1),(7,2),(7,3),(7,4),(7,5),(7,6),(7,7),(7,8),
(8,1),(8,2),(8,3),(8,4),(8,5),(8,6),(8,7),(8,8)]
This seems like it would be a simple program but I cannot seem to grasp the concepts or at least put them all together into a workable program.
Any help in direction would be greatly appreciated.

There are quite some issues with your code. Let's go through it one at a time.
1. Possible positions
Although your list of possible positions is OK, I wouldn't hard-code it like that. It's very easy to do a check if a position is on the grid:
grid_position(X, Y) :-
X >= 1,
X =< 8,
Y >= 1,
Y =< 8.
Do note that this can only be used to verify a given position. If you want to be able to generate all possible positions, you can use in/2 from library(clpfd).
2. Allowed positions
If there is no simple logic as above for positions that are blocked, there is no other way than to enumerate them yourself.
blocked(1, 2).
blocked(4, 2).
blocked(4, 1).
Using this, we can determine which are the allowed positions for our gorilla: any position that is on the grid, but is not blocked.
allowed_position(X, Y) :-
grid_position(X, Y),
\+blocked(X, Y).
3. move
The main problem here is that writing X+1 in the head of the clause doesn't do what you think it does. To evaluate arithmetic expressions, you need to use the is predicate.
Additionally, I would only allow a move if the next location is allowed. Since the gorilla is already at the current location, I don't include a check to see if this location is actually allowed.
move(X, Y, X2, Y) :-
X2 is X + 1,
allowed_position(X2, Y).
move(X, Y, X, Y2) :-
Y2 is Y + 1,
allowed_position(X, Y2).
4. path
Here's how I interpret the requirement: given a start position, return the list of moves used to reach the end position.
To do this, we're going to need 3 arguments: the X and Y positions, and the output. The output here will be a list of positions rather than a list of moves, I'll leave it up to you to change that if needed.
So what makes up our path? Well, first you make one move, and then you find the rest of the path from the next position.
path(X, Y, [(X,Y)|Ps]) :-
move(X, Y, X2, Y2),
path(X1, Y1, Ps).
Of course we have to make sure this ends at the target position, so for base case we can use:
path(8, 8, (8, 8)).
You may also want to verify that the initial position is an allowed position, which I have left out.
Combine everything, and you get output such as below.
?- path(5,6,L).
L = [(5,6),(6,6),(7,6),(8,6),(8,7)|(8,8)] ? ;
L = [(5,6),(6,6),(7,6),(7,7),(8,7)|(8,8)] ? ;
L = [(5,6),(6,6),(7,6),(7,7),(7,8)|(8,8)] ? ;
...
This may not be exactly what you're looking for, but I hope it helps you well on the way.

So you might want to say where you are moving while you're doing that. So I'll suggest a predicate move/3 like this:
% move(From_Position, To_Position, Direction).
move((X,Y),(X,Y1), up) :-
grid(G),
member((X,Y1),G),
Y1 is Y + 1.
move((X,Y),(X1,Y), rigth):-
grid(G),
member((X1,Y),G),
X1 is X + 1.
The grid calls are there to ensure that you'll always stay on the grid. you also could use a smarter predicate in_grid and avoid the member call (which is quite time consuming).
grid([(1,1),(1,2),(1,3),(1,4),(1,5),(1,6),(1,7),(1,8),
(2,1),(2,2),(2,3),(2,4),(2,5),(2,6),(2,7),(2,8),
(3,1),(3,2),(3,3),(3,4),(3,5),(3,6),(3,7),(3,8),
(4,1),(4,2),(4,3),(4,4),(4,5),(4,6),(4,7),(4,8),
(5,1),(5,2),(5,3),(5,4),(5,5),(5,6),(5,7),(5,8),
(6,1),(6,2),(6,3),(6,4),(6,5),(6,6),(6,7),(6,8),
(7,1),(7,2),(7,3),(7,4),(7,5),(7,6),(7,7),(7,8),
(8,1),(8,2),(8,3),(8,4),(8,5),(8,6),(8,7),(8,8)]).
A path should probably be a list of directions:
path((8,8), []).
path(Position, [Direction| Before]):-
\+ Position = (8,8),
move(Position, NewPosition, Direction),
path(NewPosition,Before).
To Accumulate, you can use bagof or setof
all_paths(Position,Paths):-
setof(Path,path(Position,Path),Paths).

Related

Prolog - Check winning condition in X and O game

I have a simple game of tic tac toe, there are many examples of this online that use min maxing however I just want to use a simple example for my own understanding.
I have displayed the board in a 3x3 box that have numbering system that users can pick from, in the following way:
:- dynamic o/1.
:- dynamic x/1.
% The computer has made a turn, print O
printBox(N) :- o(N), write('[o]').
% The player makes a turn, print X
printBox(N) :- x(N), write('[x]').
% We just want to print the empty board
printBox(N) :- blankSpace(N), write('[_]').
buildBoard :- printBox(1),printBox(2),printBox(3),nl,
printBox(4),printBox(5),printBox(6),nl,
printBox(7),printBox(8),printBox(9),nl.
playersMove :-
read(X),
blankSpace(X),
assert(x(X)).
When a user select from the above options (1-9) the board is filled with an X for the human player and O for the computer.
Now I also have facts for the winning lines:
winningLine(1,2,3).
winningLine(4,5,6).
winningLine(7,8,9).
%Winning rows from left to right
winningLine(1,4,7).
winningLine(2,5,8).
winningLine(3,6,9).
%Winning diagnolly
winningLine(7,5,3).
winningLine(9,5,1).
So after each move I want to check if one of the winning line combinations has been played ie does the board contain any of the winningLine combinations and with player has that combination. I have been thinking about it and a findall method could be used here however I would be open to suggestion.
My Question: How do I check the board for the winning conditions?
The simple answer
Since you are working with a global game position, we can assume the existence of a predicate checked(Player, Square) which holds iff player Player has checked the square Square.
Then all you need to check in order to see if a player has won the game is to ask whether there is a winning line where all three squares are checked by the same player:
is_win(Player) :-
winning_line(P1,P2,P3),
checked(Player,P1),
checked(Player,P2),
checked(Player,P3).
You can generate checked/2 by use of assertz:
:- dynamic checked/2.
player_move(Player, Square) :- assertz(checked(Player, Square)).
The better Way
However, if you want to go beyond simulating a simple game you should represent your state in a single data item and not put in in the global database, for example:
initial_state(board([empty, empty, empty],
[empty, empty, empty],
[empty, empty, empty]).
and adjust player_move and checked accordingly:
/* Should make a new board from Position0 by adding the move */
player_move(Player, Square, Position0, Position) :- ...
/* Should check if a player has checked a square inside Position */
checked(Player, Square, Position) :- ...
With the above global state representation, you basically have to call the winningLine(I, J, K) to obtain a triple of indices, then for all these indices, either x(X) (with X replaced by I, J and K) should hold; or for all indices o(X) should hols, like:
xwin :-
winningLine(I, J, K),
x(I),
x(J),
x(K).
nwin :-
winningLine(I, J, K),
o(I),
o(J),
o(K).
win :-
xwin.
win :-
owin.
So here xwin/0 is satisfied, given the player for x has a winning line, owin/0 is satisfied, given the player for o has a winning line, and win/0 is satisfied if any of the players has won.
But personally I think using a global state is not an elegant way to solve problems (actually in most, if not all programming paradigms). Here you can not make use of Prolog's powerful backtracking mechanism, and furthermore if you for example would like to search if there still exists a way how a user can win, you can thus not simply duplicate the board, and run a solver on the duplicated board.

How to implement a board(with fixed dimensions) in Prolog

I need to implement a board game, using Prolog. The game consists of a board(10x5), two characters(a cop and a thief) and some objects scattered over the board. The objective is to find wheter there is a path from the cop to the thief, provided that the thief cannot move. I tried to define the cop's movement as follows:
/*Defining the movement along the x-axis*/
cop(0). /*Initial position.*/
cop(W) :- cop(X), W is X+1, W < 10.
In doing so, I encountered two major problems: the solution above enters an infinite loop, when presented with the query "?- cop(X).", and prints the following
and when I try to make the cop move left, with : cop(W) :- cop(X), W is X+1, W > 0., i get the same error message. How can I do it?
The essential problem here is that you define a left-recursive function:
cop(W) :-
cop(X),
...
this means that Prolog can keep calling cop/1, since if you call cop(W), you call cop(X), and that cop(X), will again result in a call to cop(Y), etc. You only set bounds at the end, and thus there is no "guard" that protects against the recursion. Even if the "filtering" at the end lets all the suggested solutions fail, then nothing will prevent Prolog from retrying this, but with one recursive call extra. So after a while the filtering will discard all proposed solutions, but Prolog will keep searching for a valid solution.
A trick is thus here to limit the recursion, we can for example use the clpfd library to "limit" the bound of the W variable, and eventually obtain an empty domain, like:
:- use_module(library(clpfd)).
cop(0).
cop(W) :- W #> 0, W #=< 10, W #= X+1, cop(X).
that being said, I am not confident that the above way to handle this puzzle. It looks like you will need to use linear temporal logic (LTL), or branching temporal logic (BTL) here.

How to check whether two vertices are connected or not in prolog?

Here my problem is I want to check whether two nodes are connected or not.
My Knowledge base is,
edge(a,b):-!.
edge(b,a):-!.
edge(a,e):-!.
edge(e,a):-!.
edge(b,c):-!.
edge(c,b):-!.
edge(b,d):-!.
edge(d,b):-!.
edge(c,e):-!.
edge(e,c):-!.
edge(d,e):-!.
edge(e,d):-!.
edge(a,f):-!.
edge(f,a):-!.
isConnected(X,X):-!.
isConnected(X,Y):-edge(X,Y),!.
isConnected(X,Z):-not(edge(X,Y)),edge(X,Y),isConnected(Y,Z),!.
isConnected(X,Z):not(edge(X,Y)),edge(X,Z),not(isConnected(Y,Z)),isConnected(Z,Y),!.
Whoa there. That's a lot of cuts. Cuts are sometimes helpful in Prolog for pruning unnecessary answers, but when you have a fact like this:
edge(a, b).
There is absolutely nothing to be gained by writing it as:
edge(a, b) :- !.
After all, there's no choice point there, because there are no variables there and no alternate solutions. So first, let's fix your facts by removing all those cuts.
Next let's look at what isConnected is saying. Let's read it aloud in English and see if it makes sense.
X is connected to X.
X is connected to Y if there is an edge from X to Y.
X is connected to Z if there is not an edge from X to Y, but there is an edge from X to Y and Y is connected to Z. (???)
X is connected to Z if there is not an edge from X to Y, but there is an edge from X to Z, and Y is not connected to Z but Z is connected to Y. (???)
The first two seem quite reasonable. The third one seems to contradict itself right away. How can not(edge(X, Y)) be true at the same time as edge(X, Y)? Keep in mind that the comma in Prolog means and, not just then. The rest of the clause is meaningless because these two conditions cannot ever both be true. Probably what you meant to say was something like this: X is connected to Z if there is an edge from X to Y and Y is connected to Z. That would look like this in Prolog:
isConnected(X, Z) :- edge(X, Y), isConnected(Y, Z).
Logically, this is certainly true, but for any kind of complex graph this is going to be monstrously expensive to calculate, because checking if X is connected to Z might imply checking if Y is connected to Z for all the same nodes.
Your fourth clause has a typo in that the : should be a :-. More importantly, it looks like you're trying to compensate here for the directionality of your edges. A better place to do this would have been around step 2, providing both cases:
isConnected(X, Y) :- edge(X, Y) ; edge(Y, X).
I'm not sure, based on your fact database, whether you actually mean this though; you've duplicated all your facts to account for both directions. If the fact database represents a directed graph, this is probably necessary and the rules should not try inverting the nodes. If it instead represents an undirected graph, your predicate should just account for it with a rule like this that checks both sides, and you should only list each edge once. Doing it both ways, you're telling Prolog to do a bunch of unnecessary work, as it first checks edge(a, b), then the rule inverts it to edge(b, a), then moves on to the next fact edge(b, a) and then the rule inverts it to edge(a, b), in effect checking everything twice.
The elephant in the room here is that even if you do successfully turn this into a logical solution to the problem it's going to be hideously inefficient. There are algorithms for determining if two things are connected that keep track of what has been seen and what has not, and I think you'd be much better off implementing one of those.

Prolog: temporary list storage

I'm new to Prolog and I'm stuck on a predicate that I'm trying to do. The aim of it is to recurse through a list of quads [X,Y,S,P] with a given P, when the quad has the same P it stores it in a temporary list. When it comes across a new P, it looks to see if the temporary list is greater than length 2, if it is then stores the temporary list in the output list, if less than 2 deletes the quad, and then starts the recursion again the new P.
Heres my code:
deleteUP(_,[],[],[]).
deleteUP(P,[[X,Y,S,P]|Rest],Temp,Output):-
!,
appends([X,Y,S,P],Temp,Temp),
deleteUP(P,[Rest],Temp,Output).
deleteUP(NextP,[[X,Y,S,P]|Rest],Temp,Output):-
NextP =\= P,
listlen(Temp,Z),
Z > 1, !,
appends(Temp,Output,Output),
deleteUP(NextP,[_|Rest],Temp,Output).
listlen([], 0).
listlen([_|T],N) :-
listlen(T,N1),
N is N1 + 1.
appends([],L,L).
appends([H|T],L,[H|Result]):-
appends(T,L,Result).
Thanks for any help!
Your problem description talks about storing, recursing and starting. That is a very imperative, procedural description. Try to focus first on what the relation should describe. Actually, I still have not understood what minimal length of 2 is about.
Consider to use the predefined append/3 and length/2 in place of your own definitions. But actually, both are not needed in your example.
You might want to use a dedicated structure q(X,Y,S,P) in place of the list [X,Y,S,P].
The goal appends([X,Y,S,P],Temp,Temp) shows that you assume that the logical variable Temp can be used like a variable in an imperative language. But this is not the case. By default SWI creates here a very odd structure called an "infinite tree". Forget this for the moment.
?- append([X,Y,S,P],Temp,Temp).
Temp = [X, Y, S, P|Temp].
There is a safe way in SWI to avoid such cases and to detect (some of) such errors automatically. Switch on the occurs check!
?- set_prolog_flag(occurs_check,error).
true.
?- append([X,Y,S,P],Temp,Temp).
sto. % ERROR: lists:append/3: Cannot unify _G392 with [_G395,_G398,_G401,_G404|_G392]: would create an infinite tree
The goal =\=/2 means arithmetical inequality, you might prefer dif/2 instead.
Avoid the ! - it is not needed in this case.
length(L, N), N > 1 is often better expressed as L = [_,_|_].
The major problem, however, is what the third and fourth argument should be. You really need to clarify that first.
Prolog variables can't be 'modified', as you are attempting calling appends: you need a fresh variables to place results. Note this code is untested...
deleteUP(_,[],[],[]).
deleteUP(P,[[X,Y,S,P]|Rest],Temp,Output):-
!,
appends([X,Y,S,P],Temp,Temp1),
deleteUP(P, Rest, Temp1,Output). % was deleteUP(P,[Rest],Temp,Output).
deleteUP(NextP,[[X,Y,S,P]|Rest],Temp,Output1):-
% NextP =\= P, should be useless given the test in clause above
listlen(Temp,Z),
Z > 1, !, % else ?
deleteUP(NextP,[_|Rest],Temp,Output),
appends(Temp,Output,Output1).

Finding letters in a word that have different orders

Here is a description of a prolog program that I am working on:
user might enter a 5 letter word, and the only letters allowed are a,b,c,d,e. He may not enter all words, so he may enter something like userWord(A,b,C,d,E) - so only b and d are filled in. These letters may be entered in any order. I have to make this work without using lists or functions and using only grounded facts.
This is what I have:
values(a,b,c,d,e).
userWord(U,W,X,Y,Z):-
values(A1,A2,A3,A4,A5),
findletters(U,W,X,Y,Z,A1,A2,A3,A4,A5). % U-Z are outputs and A1-A5 are inputs
findletters(A1,A2,A3,A4,A5,A1,A2,A3,A4,A5):-
findletters(A2,A1,A3,A4,A5,A1,A2,A3,A4,A5).
I need to have findletters that changes orders of letters, until it finds a good match. Of course, I may need several findletters that change the order in different ways. But what I can't seem to get, is how to
call findletters with possible values
make it remember values are only a,b,c,d,e
make it take the last order it generated (which failed) and work on that and change the orders until it finds a good match.
Any assistance is extremely appreciated
Break your predicates down further, use letter(a). letter(b). ... letter(e). This will help to find that only valid letters were entered.
Maybe use it like so:
userWord(A,B,C,D,E) :-
letter(A), letter(B), ...,letter(E), /* this will fail here on
non-valid letter */
.... /* if it gets here the letters form a valid(?) word */
Alternatively, if you feel like typing, you can add facts for all the combinations of 'abcde' :) or you can let prolog generate it: word(AA,BB,CC,DD,EE):- letter(AA), ..., letter(EE).This will generate 'words' like 'aaaaa' which may not be what you want, in which case you need to add: AA!=BB,AA!=CC,...,DD!=EE. to the word()-clause.
values(a,b,c,d,e).
userWord(A,B,C,D,E):-
values(A,B,C,D,E).
userWord(A,B,C,D,E):-
reArr(A,B,F,G),reArr(B,C,H,I),reArr(C,D,J,K),reArr(D,E,L,M).
userWord(F,G,I,K,M).
reArr(X,Y,X,Y):-X<Y. %For this check the variables must be bound and must be converted into ASCII code..
reArr(X,Y,X,Y):-reArr(Y,X,Y,X).
I think the above logic would help you... Try and post your success code..
Thanks,
Cling :)
This could be pointless, but your task can be solved with just a call:
userWord(A,B,C,D,E) :- permutation([a,b,c,d,e], [A,B,C,D,E]).
Permuting 5 distinct values requires 120 facts.
It's not reasonable to do that by hand. If you are allowed to cheat, then use permutation/2 to generate all facts, and assert them, or write to a Prolog file, to be consulted.
I'm sorry I don't know any simpler algorithm than permutation/2, and I'm looking forward to see if such algorithm or some interesting trick exists.
Actually, it's easier than I thought.
letter(a).
letter(b).
letter(c).
letter(d).
letter(e).
userword(V, W, X, Y, Z) :-
letter(V),
letter(W),
letter(X),
letter(Y),
letter(Z),
V \= W,
V \= X,
V \= Y,
V \= Z,
W \= X,
W \= Y,
W \= Z,
X \= Y,
X \= Z,
Y \= Z.
We want all letters in a userword to be, well, letters. We also need them to be unique. That's all.

Resources