How do add degree of separation? - prolog

In Prolog, how would I make a rule that checks how many people come in one persons network and then query it on degree of separation?
For example, if in Facebook my name is John; and I have one friend Tom, and Tom has one friend Lucy, and Lucy has one friend Ben, and Ben has one friend Josh, and Josh has one friend Nancy.
I want to create a rule in Prolog that tests how many people are in my network and also tell Prolog to return names up to a given number of degree of separation.
e.g. if I query something like;
?- mynetwork(josh,2).
Prolog should return
John
Tom
Lucy
or
John is friends with Tom
Tom is friends with Lucy

Welcome to Prolog!
First you're going to need some facts:
friend(john, tom).
friend(tom, lucy).
friend(lucy, ben).
...
For simplicity, let's consider the case where friendships are directed: I can friend you, but that doesn't mean you friend me.
Let's say we're friends of degree 1 if I have friended you. That would look like this:
network(Person, 1, Friend) :- friend(Person, Friend).
Now the inductive case is one in which we've found a friend through a friend. That's going to look like this:
network(Person, N1, FoaF) :-
N1 > 1,
N0 is N1-1,
network(Person, N0, Friend),
network(Friend, 1, FoaF).
Using is/2 you can be sure the predicate will be ill-behaved. For instance, if you omit the > 1 constraint, you will be able to ask questions and get N back that you won't if you include it. But you'll also get errors about being out of local stack. So if you can afford to, bring in clpfd now:
:- use_module(library(clpfd)).
network(Person, 1, Friend) :- friend(Person, Friend).
network(Person, N1, FoaF) :-
N1 #> 0,
N0 #= N1-1,
network(Person, N0, Friend),
network(Friend, 1, FoaF).
This should work for all input cases you care to try, though it still has no way to know when you're out of friendship levels.
?- network(john, N, X).
N = 1,
X = tom ;
N = 2,
X = lucy ;
N = 3,
X = ben ;
^CAction (h for help) ? abort
% Execution Aborted
?- network(john, 3, X).
X = ben ;
false.
?- network(john, 2, X).
X = lucy ;
false.
Edit Let me answer your questions out of order.
Where is the print statement?
By design, I haven't used one. Until here, we're just using the Prolog REPL (read-eval-print loop) to do our I/O. This is the natural way to work with Prolog. You'll save yourself a lot of heartache later if you go to some trouble to separate predicates that do I/O and user presentation from predicates concerned with meaning. This is just a petite application of model-view separation. You also benefit from keeping side-effects quarantined in their own predicates. As long as the pure logical part of your program is self-contained, you will always be able to build and compose with it.
How would you print upto a given number of people. e.g. if you type in network(john, 3, X). then it should print out upto N=3 X=ben
I would be inclined to call this predicate show_network/2 instead and keep the separation going. You could do it on the cheap with a failure-driven loop like so:
show_network(Person, Max) :-
between(1, Max, N),
network(Person, N, Friend),
format('~w is friends with ~w\n', [Person, Friend]),
fail.
show_network(_, _).
This will work like so:
?- show_network(john, 3).
john is friends with tom.
john is friends with lucy.
john is friends with ben.
true.
There are other approaches too, for instance, you could use forall/2:
show_network(Person, Max) :-
forall(
(between(1, Max, N), network(Person, N, Friend)),
format('~w is friends with ~w\n', [Person, Friend])).
The relationship between the failure-driven loop and that one should be pretty clear. You could also manually get the list and then process it with maplist/2 or something:
show_network(Person, Max) :-
findall(friend(Person,Friend),
(between(1, Max, N), network(Person, N, Friend)),
Friends),
maplist(show_friend, Friends).
show_friend(friend(Person, Friend)) :-
format('~w is friends with ~w\n', [Person, Friend]).

Related

How to check order in prolog?

I am trying to solve this puzzle in prolog
Five people were eating apples, A finished before B, but behind C. D finished before E, but behind B. What was the finishing order?
My current solution has singleton variable, I am not sure how to fix this.
finishbefore(A, B, Ls) :- append(_, [A,B|_], Ls).
order(Al):-
length(Al,5),
finishbefore(A,B,Al),
finishbefore(C,A,Al),
finishbefore(D,E,Al),
finishbefore(B,D,Al).
%%query
%%?- order(Al).
Here is a pure version using constraints of library(clpz) or library(clpfd). The idea is to ask for a slightly different problem.
How can an endpoint in time be associated to each person respecting the constraints given?
Since we have five persons, five different points in time are sufficient but not strictly necessary, like 1..5.
:- use_module(library(clpz)). % or clpfd
:- set_prolog_flag(double_quotes, chars). % for "abcde" below.
appleeating_(Ends, Zs) :-
Ends = [A,B,C,D,E],
Zs = Ends,
Ends ins 1..5,
% alldifferent(Ends),
A #< B,
C #< A,
D #< E,
B #< D.
?- appleeating_(Ends, Zs).
Ends = [2, 3, 1, 4, 5], Zs = [2, 3, 1, 4, 5].
There is exactly one solution! Note that alldifferent/1 is not directly needed since nowhere is it stated that two persons are not allowed to end at precisely the same time. In fact, above proves that there is no shorter solution. #CapelliC's solution imposes an order, even if two persons finish ex aequo. But for the sake of compatibility, lets now map the solution back to your representation.
list_nth1(Es, N, E) :-
nth1(N, Es, E).
appleeatingorder(OrderedPeople) :-
appleeating_(Ends, Zs),
same_length(OrderedPeople, Ends),
labeling([], Zs), % not strictly needed
maplist(list_nth1(OrderedPeople), Ends,"abcde"). % effectively enforces alldifferent/1
?- appleeatingorder(OrderedPeople).
OrderedPeople = [c,a,b,d,e].
?- appleeatingorder(OrderedPeople).
OrderedPeople = "cabde".
The last solution using double quotes produces Scryer directly. In SWI use library(double_quotes).
(The extra argument Zs of appleeating_/2 is not strictly needed in this case, but it is a very useful convention for CLP predicates in general. It separates the modelling part (appleeating_/2) from the search part (labeling([], Zs)) such that you can easily try various versions for search/labeling at the same time. In order to become actually solved, all variables in Zs have to have an actual value.)
Let's correct finishbefore/3:
finishbefore(X, Y, L) :-
append(_, [X|R], L),
memberchk(Y, R).
then let's encode the known constraints:
check_finish_time(Order) :-
forall(
member(X<Y, [a<b,c<a, d<e,d<b]),
finishbefore(X,Y,Order)).
and now let's test all possible orderings
?- permutation([a,b,c,d,e],P),check_finish_time(P).
I get 9 solutions, backtracking with ;... maybe there are implicit constraints that should be encoded.
edit
Sorry for the noise, have found the bug. Swap the last constraint order, that is b<d instead of d<b, and now only 1 solution is allowed...

Prolog beginner, combining rules question?

I'm trying to write a program thats based on these facts:
Boyle was born in 1627 and died in 1691.
Newton was born in 1642 and died in 1727.
(and so on)
I want to create a rule that determines if a person was alive during a specified year. Here is what I've come up with so far:
scientist(boyle, 1627, 1691).
scientist(newton, 1642, 1727).
alive_after(X) :- scientist(A, B, C), B < X.
alive_before(X) :- scientist(A, B, C), C > X.
alive_during(X, Year) :- alive_after(X), alive_before(X).
I believe that my first two rules are correct, but they don't seem to be working as intended when I combine them for my alive_during rule. When I run my code with this as my input:
alive_during(1628).
X = boyle
It doesn't work.
What am I missing here?
Prolog cannot unify variables that are hidden inside predicate bodies. There is no relationship between the A in alive_after/1 and the A in alive_before/1. Prolog actually told you that it didn't know what you were doing when it reported these warnings: `
|: alive_after(X) :- scientist(A, B, C), B < X.
Warning: user://2:19:
Singleton variables: [A,C]
|: alive_before(X) :- scientist(A, B, C), C > X.
Warning: user://2:23:
Singleton variables: [A,B]
|: alive_during(X, Year) :- alive_after(X), alive_before(X).
Warning: user://2:27:
Singleton variables: [Year]
It is extremely important that you read these messages as if they are errors, especially when you are new to Prolog!
The solution is to make it so that Prolog is able to unify the scientists across these predicates:
alive_after(Scientist, Year) :- scientist(Scientist, Birth, _), Year > Birth.
alive_before(Scientist, Year) :- scientist(Scientist, _, Death), Year < Death.
alive_during(Scientist, Year) :-
alive_before(Scientist, Year), alive_after(Scientist, Year).
You may also find that it is a little easier to follow the logic when you give your variables meaningful names. I am guilty of using extremely terse variable names when writing very general predicates, but these are actually very specific predicates and a good name can help you understand the structure of what you're doing. It would be, I think a little harder to see how this is more correct than what you wrote:
alive_after(A, X) :- scientist(A, B, _), X > B.
alive_before(A, X) :- scientist(A, _, C), X < C.
alive_during(A, X) :- alive_before(A, X), alive_after(A, X).
With better names, it is much easier to see why your original code is incorrect, because the scientist is not actually shared between the alive_before/2 and alive_after/2 calls.
Another hint that you were confused was that this response to a query makes no sense:
?- alive_during(1628).
X = boyle
Where did X come from? Variables get unified with values from the query, they do not arrive from inside predicate bodies.
An even more direct solution would be to use Prolog's built-in between/3 predicate:
alive_during(Scientist, Year) :-
scientist(Scientist, Birth, Death),
between(Birth, Death, Year).
This has the added advantage that it will actually generate solutions for you:
?- alive_during(boyle, X).
X = 1627 ;
X = 1628 ;
X = 1629 ;
X = 1630 ;
X = 1631 ;
The other solution does not have this property. There are interesting predicates you can write if you do have this generating property, such as contemporaries/2:
contemporaries(S1, S2) :-
alive_during(S1, Y),
alive_during(S2, Y),
dif(S1, S2).
Which generates a lot of not interesting copies of solutions, but you can get rid of them by using setof/3:
?- setof(X-Y, contemporaries(X, Y), Contemporaries).
Contemporaries = [boyle-newton, newton-boyle].

How to assert new data dynamically in Prolog

I have previously define a few facts dynamically as below.
% declare dynamic facts
:- dynamic title/2.
:- dynamic author/2.
:- dynamic publisher/2.
:- dynamic price/2.
:- dynamic call_number/2.
:- dynamic edition/2.
:- dynamic data_disk/2.
and assert these facts every time the program runs
:- assert(title(book1, 'Elementary Statistics')).
:- assert(title(book2, 'Statistics for Engineers')).
:- assert(title(book3, 'Statistics for Engineers and Scientists')).
:- assert(title(book4, 'IT in Language Learning')).
:- assert(author(book1, 'Patricia Wilson')).
:- assert(author(book2, 'James Mori')).
:- assert(author(book3, 'James Mori')).
:- assert(author(book4, 'O Ivan')).
:- assert(publisher(book1, 'Addison Wesley')).
:- assert(publisher(book2, 'World Scientific')).
:- assert(publisher(book3, 'World Scientific')).
:- assert(publisher(book4, 'Universal Press')).
:- assert(price(book1, 75)).
:- assert(price(book2, 125)).
:- assert(price(book3, 125)).
:- assert(price(book4, 5)).
:- assert(call_number(book1, 'QA373')).
:- assert(call_number(book2, 'QA673')).
:- assert(call_number(book3, 'QA674')).
:- assert(call_number(book4, 'QA007')).
:- assert(edition(book1, 1)).
:- assert(edition(book2, 3)).
:- assert(edition(book3, 2)).
:- assert(edition(book4, 1)).
:- assert(data_disk(book1, 'No')).
:- assert(data_disk(book2, 'Yes')).
:- assert(data_disk(book3, 'Yes')).
:- assert(data_disk(book4, 'No')).
As you can see the facts are in a certain order
book1
book2
book3
book4
How can I get the last X, where X is bookX, and increment by 1 so that the new book to be inserted will always be (X+1)?
You found one solution (i.e., count the existing facts, and add 1), which works but has one major drawback: It makes the run time of adding a single new fact proportional to the number of already asserted facts. This means that asserting a series of N facts takes time proportional to N2.
Ideally, we would like to have a situation where asserting a single fact is in &Oscr;(1), and asserting N facts is thus in &Oscr;(N).
One way to achieve this is to reconsider your initial representation of books.
For example, suppose that you present your books like this (some data omitted for brevity):
book([title('Elementary Statistics'),
author('Patricia Wilson'),
price(75)]).
book([title('Statistics for Engineers'),
author('James Mori'),
publisher('World Scientific')]).
Note that this representation allows us to omit fields that are only present in some of the books. Other representations would also make sense.
We can easily fetch all these facts with findall/3:
?- findall(Book, book(Book), Books).
That's linear in the number of such facts.
Further, let us define assert_book_/3 as follows:
assert_book_(Book, N0, N) :-
memberchk(title(Title), Book),
memberchk(author(Author), Book),
assertz(title(N0,Title)),
assertz(author(N0,Author)),
N #= N0 + 1.
For the sake of example, I am focusing on the title and author. I leave extending this as an exercise.
The arguments of this predicate are:
the book to be asserted, represented as a list of attributes
the current index N0
the next index N1, which is simply one greater than N0.
Now the main point: These arguments are in a suitable order to fold the predicate over a list of books, using the meta-predicate foldl/4:
?- findall(Book, book(Book), Books),
foldl(assert_book_, Books, 1, _).
After running this query, we have:
?- title(N, T).
N = 1,
T = 'Elementary Statistics' ;
N = 2,
T = 'Statistics for Engineers'.
And similar facts for author/2 in the database:
?- author(N, T).
N = 1,
T = 'Patricia Wilson' ;
N = 2,
T = 'James Mori'.
Thus, we have used foldl/4 to implicitly keep track of the running index we need, and achieved a solution that has the desired running time.
Note that there is also a wise-cracking solution for your task:
assert_title(Book, Title) :-
atom_concat(book, N0, Book),
atom_number(N0, N),
assertz(title(N, Title)).
This is obviously not what you looking for, but would work for the example you show, if you use for example:
:- assert_title(book1, 'Elementary Statistics').
:- assert_title(book2, 'Statistics for Engineers').
Now we have again:
?- title(N, Title).
N = 1,
Title = 'Elementary Statistics' ;
N = 2,
Title = 'Statistics for Engineers'.
The joke here is that you have actually entered the running index already, and we can use atom_concat/3 to obtain it:
?- atom_concat(book, N0, book1),
atom_number(N0, N).
N0 = '1',
N = 1.
;-)
I cleared my mind at the nearest Starbucks and came up with the simplest answer.
add_book :-
aggregate_all(count, title(_,_), Count),
NewCount is Count + 1,
atom_concat('book', NewCount, NewBook).
The aggregate_all function will count number of title predicates that's available in my knowledge base and some calculation will be performed.
I am open to better suggestion though, do reply if you have a better approach.

Fastest way between two cities

I need to find the fastest way to travel from one city to another. I have something like
way(madrid, barcelona, 4).
way(barcelona, paris, 5).
way(madrid, londres, 3).
way(londres,paris,1).
I have come up with a predicate shortway(A,B,C,D) where C is the list of towns between A and B and D the distance.
so I have
shortway(A,B,C,D):-
way(A,B,_,_) , (A,_,C,D). D<C.
shortway(A,_,C).
I trying my best but I really cant get it to work!
You have a bunch of problems with your code! First of all, way/3 has arity 3, not 4, so calling way(A,B,_,_,) is clearly not going to do what you think. Second, I have no idea what you're trying to do with (A,_,C,D). The period after this signifies the end of the predicate! So the next line, D<C. is just a free-floating query that cannot be fulfilled. And then shortway(A,_,C) is basically a fact, with three singletons, but it would define a shortway/3 clause when the previous one is a shortway/4 clause.
There really isn't enough that's on the right track here to try and recover. It looks here like you are extremely confused about even the basics of Prolog. I would strongly encourage you to go back to the beginning and start over. You can't rush Prolog! And this code looks like you're trying to make a combustion engine by banging rocks together.
I wrote some line of code to help you, but as https://stackoverflow.com/users/812818/daniel-lyons said, it's better than you learn something easier before.
To solve your problem I advice you to read, at least, the first 3 chapters of this book: http://www.learnprolognow.org/lpnpage.php?pageid=online and do the practical session at paragraph 3.4.
Then, you could take a look at my code (you can find some explenation of it here:Out of local stack error in Prolog route planner .
Here the code
way(madrid, barcelona, 4).
way(barcelona, paris, 5).
way(madrid, londres, 3).
way(londres,paris,1).
shortway(From, To):- findall(Journey, travel(From, To, Journey, _) , Travels_list),
findall(Total_distance, travel(From, To, _, Total_distance) , Distances_list),
min_member(Y, Distances_list), find_minimum_index(Y, Distance_list, 1, Distance_index),
find_journey(Distance_index, Travels_list, 0, Shortest_path),
format('The shortest path is ~w', [Shortest_path]).
travel(From, To, Journey, Total_distance) :- dif(From, To),
AccDistance is 0,
path(From, To, [From], Journey, AccDistance, Total_distance).
path(From, To, Passed_cities, go(From, To), AccDistance, Total_distance) :- way(From, To, Way_distance),
Total_distance is AccDistance + Way_distance.
path(From, To, Passed_cities, go(From, Intermediate, GO), AccDistance, Total_distance) :- way(From, Intermediate, Way_distance),
dif(Intermediate, To),
\+ member(Intermediate, Passed_cities),
NewAccDistance is AccDistance + Way_distance,
path(Intermediate, To, [Intermediate|Passed_cities], GO, NewAccDistance, Total_distance).
min_member(Min, [H|T]) :- min_member_(T, H, Min).
min_member_([], Min, Min).
min_member_([H|T], Min0, Min) :-
( H >= Min0
-> min_member_(T, Min0, Min)
; min_member_(T, H, Min)
).
find_minimum_index(X, [], N, I) :- fail.
find_minimum_index(X, [X|T], N, I) :- I is N, !.
find_minimum_index(X, [H|T], N, I) :- H \= X, increment(N, N1), find_minimum_index(X, T, N1, I).
find_journey(I, [H|T], N, Elemento) :- N = I, Elemento = H, !.
find_journey(I, [H|T], N, Elemento) :- N \= I, increment(N, N1), find_journey(I, T, N1, Elemento).
increment(X, X1) :- X1 is X+1.
Then you call, for example
?:- shortway(madrid,paris).
and it will return
"The shortest path is go(madrid, londres, go(londres,paris))"
which distance is, 4
rather than
go(madrid, barcelona, go(barcelona, madrid)
which distance is 9.
Summing up: calling shortway/2, with the predicates findall/3 you'll find the lists of all possible pathes and their relative distances, respectively, then you'll browse the list of the distances to find the index of the minimum element and so using it to find the shortest path from the list of all pathes found previously.

A prolog program that reflects people sitting at a round table

I've got a prolog homework to do: There are 5 persons sitting at a round table of different nationalities (french, english, polish, italian, turkish). Each of them knows only one other language other than their own. They sit at the round table in such a way that each of them can talk with their 2 neighbors (with one neighbor they talk in their native tongue and with the other in the single foreign language they know). The english person knows italian, the polish person knows french, the turkish person doesn't know english. The question is what foreign language does the turkish person know?
I've done something using only clauses and predicates but I reached a dead end, teacher suggested the easiest way would be to use lists.
Any thoughts on what that list would contain or any code ideas at all?
UPDATE (weak logic code):
predicates
knowTheLanguage(symbol,symbol)
knowNotTheLanguage(symbol,symbol)
isNeighbor(symbol,symbol,symbol,symbol)
aTheory(symbol,symbol,symbol,symbol)
anotherTheory(symbol,symbol,symbol,symbol)
clauses
knowTheLanguage(englishman,italian).
knowTheLanguage(polishman,franch).
%native tongues
knowTheLanguage(englishman,english).
knowTheLanguage(frenchman,franch).
knowTheLanguage(polishman,polish).
knowTheLanguage(italianman,italian).
knowTheLanguage(turk,turkish).
knowNotTheLanguage(turk,english).
aTheory(centralPerson, languageCntrlPers, personOnOneSide,languagePrsnOnOneSide) if knowTheLanguage(personOnOneSide,languageCntrlPers)
and not( knowTheLanguage(centralPerson,languagePrsnOnOneSide))
and not(knowNotTheLanguage(centralPerson,languagePrsnOnOneSide)).
anotherTheory(centralPerson, languageCntrlPers, personOnOneSide,languagePrsnOnOneSide) if knowTheLanguage(centralPerson,languagePrsnOnOneSide)
and not( knowTheLanguage(personOnOneSide,languageCntrlPers))
and not(knowNotTheLanguage(centralPerson,languagePrsnOnOneSide)).
isNeighbor(centralPerson, languageCntrlPers, personOnOneSide,languagePrsnOnOneSide) if aTheory(centralPerson, languageCntrlPers, personOnOneSide,languagePrsnOnOneSide)
or
anotherTheory(centralPerson, languageCntrlPers, personOnOneSide,languagePrsnOnOneSide).
Update - programming environment : turbo prolog 2.0 '86,'88 by Borland, also I'm a complete beginer in prolog, so... I'd apreciate at least a full sketch of the program and explanations outside of the code body. I process things slow :D
You can work with cyclic list, try this code to understand.
t :-
L = [1,2,3 | L],
my_write(5, L).
my_write(0, _).
my_write(N, [H | T]) :-
write(H), nl,
N1 is N - 1,
my_write(N1, T).
Cyclic list may be very usefull for you.
Describe what are the elements of the list, then what is the constraint for the languages
EDIT : Here is my solution, works with SWI-Prolog :
% #arg1 : list of nationalities around the table
% #arg2 : list of persons
dinner(Languages, Table) :-
length(Languages, Len),
length(Table, Len),
% set Natianalities and languages
init_1(Table, Languages, Languages),
% create cyclic list
% works with SWI-Prolog
append(Table, L, L),
% set languages constraint
init_2(Len, L).
init_1([], [], []).
init_1([person(N, L) | T], Nations, Languages):-
select(N, Nations, New_Nations),
% problem specific
( N = english
-> L = italian
; N = polish
-> L = french
; true),
select(L, Languages, New_Languages),
% problem specific
( N = turkish
-> L \= english
; true),
init_1(T, New_Nations, New_Languages).
% persons speaks with theirs two neighbors
init_2(Tr, [person(_N1, L1), person(N2, L2), person(N3, L3) | T]) :-
Tr > 0,
member(N2, [L1, L3]),
Tr1 is Tr - 1,
init_2(Tr1, [person(N2, L2), person(N3, L3) | T]).
init_2(0, _).
Normally, I would solve such a puzzle using constraints, but that would probably be too advanced for your homework. So, instead of using constraints to restrict the search space, we have to use tests to check whether the solution is feasible.
You will need to work with two lists, say People and Languages. Each element of the lists corresponds to one seat at the table. Both lists can have the same domain, [f,e,p,i,t]. The semantics of the domain should be clear.
To generate the solution, you first set up the lists, then instantiate the lists and check whether the instantiation fulfils your constraints:
puzzle(People, Languages) :-
Domain = [f,e,p,i,t],
length(People, 5),
length(Languages, 5),
% symmetry break:
People = [f|_],
% instantiate People
people(People, Domain),
% instantiate languages and check constraints
languages(Languages, People, Domain).
Note that the first element of list People is set to f. This is to rule out symmterical solutions, which will otherwise be returned since the table is round. Without this restriction, each solution would have four additional symmetrical solutions.
Try to come up with your own solution before reading on... :-)
The list People is instantiated first. We need to take care that each element appears only once:
people([], []) :- !.
people([P|RestP], Domain) :-
delete(P, Domain, RestD),
people(RestP, RestD).
Your dialect of Prolog may have select/3 instead of delete/3.
When instantiating the list Languages, we also check that the puzzle constraints are not violated:
languages(Languages, People, Domain) :-
Term =.. [[]|People],
languages0(Languages, People, Term, 1, Domain).
languages0([], _, _, _, _) :- !.
languages0([L|RestL], [P|RestP], Term, I, Domain) :-
delete(L, Domain, RestD),
L \= P, % language needs to be foreign
check_l(P, L),
check_n(L, I, Term),
I1 is I+1,
languages0(RestL, RestP, Term, I1, RestD).
Again, each element can only appear once.
check_l checks the constraints regarding the foreign languages:
check_l(e, i).
check_l(p, f).
check_l(t, L) :- L \= e.
check_l(f, _).
check_l(i, _).
check_n ensures that language and nationality of either left or right neighbour match:
check_n(L, I, Term) :-
( I == 1 -> NL = 5 ; NL is I-1 ),
( I == 5 -> NR = 1 ; NR is I+1 ),
( arg(NL, Term, L) ; arg(NR, Term, L) ).
There are two solutions:
?- puzzle(P, L).
P = [f, e, i, t, p]
L = [e, i, t, p, f]
Yes (0.00s cpu, solution 1, maybe more)
P = [f, p, t, i, e]
L = [e, f, p, t, i]
Yes (0.01s cpu, solution 2, maybe more)
No (0.01s cpu)
Generally, when modelling a problem, it's important to identify a compact representation, eliminating irrelevant details. Here having, for instance, polishman and polish is useless. We can agree that polish stands for both the man and the language.
I sketch the solution, please fill in the ellipsis, adding the constraints:
puzzle(L) :-
L = [P1,P2,P3,P4,P5],
cadj(P5,P1,P2),
...
member(p(english, italian), L),
member(p(french, _ ), L),
...
\+ member(p(turk, english), L).
% constrain adjacents
cadj(p(Pl, Ll), p(P, K), p(Pr, Lr)) :-
P = Ll, K = Pr ; P = Lr, K = Pl.
p/2 stands for the man and the language he knows.
cadj/3 says that if the man at left knowns my language, I must know the language of the man at right, or viceversa.
To get the required language, try
puzzle :-
puzzle(L),
memberchk(p(turk, T), L),
writeln(T:L).
There are more solutions, but the language T is consistently constrained to a single value...

Resources