Converting list of clauses to a query? - list

let say i have the following facts :
book(65).
own(named('Peter'), 65).
now got the query as a list of clauses :
[what(A), own(named('Peter'), A)]
or
[who(X), book(A), own(X, A)] .
how do I make a rule that accept this list and return the result. Keep in mind that the question could be Why,When,Who...
I went the usual way :
query_lst([]).
%% query_lst([what(Q)|T], Q) :- query_lst(T).
query_lst([H|T]) :- write('?- '),writeln(H),
call(H), query_lst(T).
but this does not allow binding of Q in wh(Q) to the answer which could be in any of the facts that are called by call()
Additional complication I did not forsee is that the query :
(what(A), own(named('Peter'), A).
would fail, because there is no what(X), fact in the DB.
I have to just bind somehow the variable A /that is in what()/ to query_lst(Goals,A) and of course remove what(X) from the list /which i can do with select/3 /
any idea how to bind list-Wh-var to query_lst result ?
my current solution (assumes Q is first element):
query_lst([G|Gs],Res) :- G =.. [Q,Res], member(Q,[what,why,who,when]), lst2conj(Gs,Conj), call(Conj).

Simply convert the list of goals into a conjunction and call it:
list_to_conjunction([], true).
list_to_conjunction([Goal| Goals], Conjunction) :-
list_to_conjunction(Goals, Goal, Conjunction).
list_to_conjunction([], Conjunction, Conjunction).
list_to_conjunction([Next| Goals], Goal, (Goal,Conjunction)) :-
list_to_conjunction(Goals, Next, Conjunction).
Then:
query_list(Goals) :-
list_to_conjunction(Goals, Conjunction),
call(Conjunction).

You got an answer, but it was an answer to your question, not to what you really wanted. Also, you edited your question after you accepted that answer, which isn't very helpful. Typically it's better to open a new question when you have... a new question.
Here is an answer to what you seem to want, which is not exactly what you asked. You have lists of the form [WhPart | Rest] where the WhPart is a wh-word with a variable, and the Rest is a list of goals. You want to execute these goals and get the variable in the wh-term bound.
The good news is that, since the variable in the wh-word also occurs in the goals, it will be bound if you execute them. No extra work is needed. Executing the goals is enough. If the wh-part is really at the start of the list, you can do the whole thing like this:
query([_WhPart | Body]) :-
call_body(Body).
call_body([]).
call_body([Goal | Goals]) :-
call(Goal),
call_body(Goals).
For example:
?- query([who(X), book(A), own(X, A)]).
X = named('Peter'),
A = 65.
?- query([what(A), own(named('Peter'), A)]).
A = 65.
As you can see, there is no need to convert the query to a conjunctive goal: Executing the queries in sequence is exactly the same as executing their conjunction.
Also, it doesn't actually matter which wh-word is used; the only thing that really matters is the variable contained within the term. For this reason the above version does no checking at all, and the _WhPart could be anything. If you want to check that it is a valid term, you can do the following:
query([WhPart | Body]) :-
wh(WhPart),
call_body(Body).
wh(who(_X)).
wh(what(_X)).
wh(when(_X)).
This buys you some "type checking":
?- query([foo(A), own(named('Peter'), A)]).
false.
But not a lot, since you don't know if the wh-word actually fits what is being asked:
?- query([when(A), own(named('Peter'), A)]).
A = 65.

Related

Prolog answers Argument = Argument, instead of answer No

How can I make prolog answer No , if search_answer didn't find an answer , and
Yes with L = [Answer]
search_answer : predicate that returns a list or let's A as a free variable.
found_list(L) :-
search_answer(L).
For example , when asked found_list(L) , although search_answer didn't find an answer , Prolog still answers Yes. I print L , and it is equal to _496 , a free variable.
Given the above piece of code, found_list answers L = [...] if search_answer found a list , else returns L = L, while I want to answer no
I tried the following , but doesn't work
found_list(L) :-
search_answer(L) , is_list(L).
liar_detector is my search_answer predicate , with L = answer
and liars is my found_answer
In found_list(L) :- search_answer(A). both L and A are singleton. I assume you saw the warning. You need to fix that for this predicate to make sense. Do you really want L = [Answer] or L = Answer?
You can achieve what you're after this way:
found_list(A) :-
search_answer(A).
This will fail (result in "no") if search_answer(A) doesn't succeed, and your result will be A if it does succeed.
If you want the result as an answer within a list, you can do this:
found_list([A]) :-
search_answer(A).
I'm not sure what the value is of either of these. The first found_list/1 is just a simple wrapper on search_answer/1 without any additional logic. The second simply makes a single-element list out of the search_answer/1 result. If A is already a list, you don't need to put it inside of brackets ([...]), otherwise you just get a list within a list. I suspect you are really trying to do something else but haven't explained.
In response to the updated question, the following code should work if A is a simple unbound term:
found_list(A) :-
search_answer(A),
is_list(A).
However, is_list/1 will succeed if its argument has a list structure even though it's elements may be unbound:
| ?- X = [_], is_list(X).
X = [_]
yes
| ?-
So, for example, if search_answer(A) succeeds with A = [_], then found_list(A) will suceed with A = [_].
ground/1 can be useful here since:
| ?- ground(X).
no
| ?- ground([_|_]).
no
| ?- ground([a,b]).
yes
| ?-
Thus, the following solution should work:
found_list(A) :-
search_answer(A),
ground(A).
If your intention is not to backtrack to search_answer(A) if A is not ground, but just fail, you could implement found_list/1 as:
found_list(A) :-
search_answer(A),
( ground(A) -> true ; !, false ).
I think, though, there may be a more fundamental issue with the code, as it shouldn't have a behavior that you feel compelled to work around like this.

Get "real" prefixes/suffixes/infixes in Prolog

the Prolog notation of prefix/suffix is a quite easy one:
It pretty much puts all the work on append.
For those who don't know:
prefix(P,L):-append(P,_,L).
suffix(S,L):-append(_,S,L).
Now this means, that the result for prefix(X,[a,b,c,d]).
will be: X=[];X=[a];X=[a,b];X=[a,b,c];X=[a,b,c,d]
Here is my problem with this: I want a "real" prefix. Hence, a prefix cannot be empty, nor can the part following it be empty.
So the result to the query prefix(X,[a,b,c,d]). should be
X=[a];X=[a,b];X=[a,b,c]
and that's it.
Unfortunately, the real beaty of the standard-built in prefix predicate is, that it can use the termination of append, which is append([],Y,Y).
So it is pretty easy to know when to stop, picking the list apart one by one till the list is empty.
My termination means: Stop if there is exactly one element left in your list.
How do I do this?
My naive result would be:
prefix(P,L):-
length(P,1),append(P,E,L),E/=[].
This feels wrong though. I'm at work so I haven't checked if this actually works, but it should:
Is there any more convenient way to do this?
Same goes for suffix, which will be even harder since you do not have a way to adress the Tail as specific as the Head, I guess I'd just reverse the whole thing and then call prefix on it.
Infix will just be a combination of two.
I hope it is clear what I mean. Thanks for your input!
tl;dr: How to write a predicate prefix/2 which only filters real prefixes, so the prefix itself can not be empty, nor can the list followed by it be empty.
For the real prefix, you can try to do it like this:
list_prefix(List, [H|T]) :-
append([H|T], [_|_], List).
This just says that the first argument must have at least one element, and the rest of the list must have at least one element.
And following the suggestion by #false to make it more explicit:
list_real_prefix(List, Prefix) :-
Prefix = [_|_],
Rest = [_|_],
append(Prefix, Rest, List).
The "real" suffix will be exactly the same:
list_real_suffix(List, Suffix) :-
Front = [_|_],
Suffix = [_|_],
append(Front, Suffix, List).
You can also use a DCG for this, which is descriptive:
list_prefix(P) --> non_empty_seq(P), non_empty_seq(_).
non_empty_seq([X]) --> [X].
non_empty_seq([X|Xs]) --> [X], non_empty_seq(Xs).
| ?- phrase(list_pref(P), [a,b,c,d]).
P = [a] ? a
P = [a,b]
P = [a,b,c]
no
| ?-
You can define the suffix similarly:
list_suffix(S) --> non_empty_seq(_), non_empty_seq(S).

Return from Prolog predicate

I have a predicate, which is true, if passed such list of pairs, for instance:
translatable([(dog,perro)], [(perro,hund)], [(dog,hund)])
Means - if "dog" translates to "perro", and "perro" translates to "hund", then it is true that "dog" translates to "hund".
Here follows full code. Returns/suggests first member of pair - given ((a, b), a) returns true, given ((a, b), X) returns X = a:
first((First, _), First).
Similar to "first", but for second pair member:
second((_, Second), Second).
This returns true if translatable word exists in list of tuples, and saves translation to Translation: (dog, Translation, [(bed,cama),(dog,perro)]
translation_exists(Word, Translation, [H|T]) :-
first(H, Word), second(H, Translation), !;
translation_exists(Word, Translation, T).
And resulting:
translatable(EnglishSpanish, SpanishGerman, EnglishGerman) :-
forall(member(Pair, EnglishGerman), (
first(Pair, Word),
second(Pair, ResultTranslation),
translation_exists(Word, Translation, EnglishSpanish),
translation_exists(Translation, ResultTranslation, SpanishGerman)
)).
This code returns true/false correctly.
But why, given
translatable([(dog,perro)], [(perro,hund)], X).
It does not returns X = [(dog,hund)]?
EDIT
To be more specific, actual goal is:
to find out if LAST dictionary has translatable pairs (and them only).
Daniel, thanks a lot, I have adopted your suggested member function - great simplification, thank you! This is all the code I have now:
lastIsTranslatable(_, _, []).
lastIsTranslatable(EngSpan, SpanGerm, [(Eng, Germ) | T]) :-
member((Eng, Span), EngSpan),
member((Span, Germ), SpanGerm),
% this is to protect endless [(dog,hund), (dog, hund), ...]
not(member((Eng, Germ), T)),
lastIsTranslatable(EngSpan, SpanGerm, T),
!.
And still, this works great finding True & False:
lastIsTranslatable([(a,b)], [(b,c)], [(a,c)]).
lastIsTranslatable([(a,b)], [(b,c)], [(a,no)]).
But for
lastIsTranslatable([(a,b)], [(b,c)], X).
result is X= [], then, after hitting ";" - false. Why?
Well, running with trace option, I see execution is failing on
not(member((Eng, Germ), T))
But otherwise resulting X will be endlessly filled with (a,c), (a,c)... Maybe there is better way to protect from duplicates?
The reason, basically, is that because EnglishGerman is uninstantiated, member/2 is free to come up with possible lists for it:
?- member((perro,X), List).
member((perro,X), List).
List = [ (perro, X)|_G18493911] ;
List = [_G18493910, (perro, X)|_G18493914] ;
List = [_G18493910, _G18493913, (perro, X)|_G18493917] ;
List = [_G18493910, _G18493913, _G18493916, (perro, X)|_G18493920]
...
This is the most direct issue, but even if you change the flow of data I think you'll still have problems:
translatable1(EnglishSpanish, SpanishGerman, EnglishGerman) :-
member((English,Spanish), EnglishSpanish),
member((Spanish,German), SpanishGerman),
member((English,German), EnglishGerman).
Note that I have foregone your first/2 and second/2 predicates in favor of pattern matching; I think this reads more clearly.
Aside: If you know your list is concrete and you don't want to generate multiple solutions, you can use memberchk/2 to verify that an element exists instead of member/2; it's cheaper and deterministic.
This works better (you get solutions, anyway) but still you get a lot more solutions than you need:
?- translatable1([(dog,perro)], [(perro,hund)], X).
X = [ (dog, hund)|_G18493925] ;
X = [_G18493924, (dog, hund)|_G18493928] ;
X = [_G18493924, _G18493927, (dog, hund)|_G18493931] a
Something which we know that our code does not know is that the cardinality of the result set should be less than or equal to the lowest cardinality of our inputs; if I have fifteen English-Spanish words and twelve Spanish-German words, I can't have more than twelve words in my English-German result. The reason our code doesn't know that is because it is trying to behave like math: our code is basically saying "for every element of English-Spanish, if there exists a matching element of Spanish-German, that is also an element of English-German." This does not tell us how to construct English-German! It only tells us a fact about English-German that we can verify with English-Spanish and Spanish-German! So it's cool, but it isn't quite enough to compute English-German.
Aside: it's conventional in Prolog to use a-b instead of (a,b); it's too easy to lull yourself into believing that Prolog has tuples when it doesn't and the operator precedence can get confusing.
So, how do we tell Prolog how to compute English-German? There are probably lots of ways but I would prefer to use select/3 because our set cardinality constraints (as well as a general sense that it will converge/halt) will emerge naturally from a computation that "uses up" the input sets as it goes.
translatable2([], _, []).
translatable2(_, [], []).
translatable2([Eng-Span|EngSpanRem], SpanGerm, EngGerm) :-
(select(Span-Germ, SpanGerm, SpanGermRem) ->
translatable2(EngSpanRem, SpanGermRem, EngGermRem),
EngGerm = [Eng-Germ|EngGermRem]
;
translatable2(EngSpanRem, SpanGerm, EngGerm)
).
The base cases should be obvious; if we are out of English-Spanish or Spanish-German, there's nothing left to compute. Then the inductive case peels the first item off the English-Spanish list and searches for a Spanish-German translation that matches. If it finds one, it uses it to build the result; otherwise, it just recurs on the remaining English-Spanish list. This way, on each iteration we at least discard an English-Spanish translation from that list, and we discard Spanish-German translations as they are used. So it seems intuitively likely that this will work and terminate without producing a bunch of extra choice points.
It seems to do the trick:
?- translatable2([dog-perro], [perro-hund], X).
X = [dog-hund] ;
X = [dog-hund].
The extra result there is because we hit both terminal cases because both lists became []; this isn't attractive but it isn't anything to worry about really either.
Now one thing that sucks about this solution is that it treats the first two parameters as in-parameters and the last one as an out-parameter and there isn't really anything you can do about this. I don't know if this is an issue for you; translatable/1 should not have this limitation, but because member((Spanish,German), SpanishGerman) happens before member((English,German), EnglishGerman) it winds up generating an infinitely large list, searching in effect for the missing Spanish-German translation.
Still, it feels like it should be possible to come up with a general purpose predicate that works as long as you supply any two of these inputs. I can do that if I know that all three lists are complete and in the same order:
translatable3([], [], []).
translatable3([X-Y|XYs], [Y-Z|YZs], [X-Z|XZs]) :-
translatable3(XYs, YZs, XZs).
And you can see it work like so:
?- translatable3([dog-perro], [perro-hund], X).
X = [dog-hund].
?- translatable3([dog-perro], X, [dog-hund]).
X = [perro-hund].
?- translatable3(X, [perro-hund], [dog-hund]).
X = [dog-perro].
But I don't know enough about your constraints to know if that could be a legitimate answer. My suspicion is no, because languages don't work that way, but who knows?
Anyway, that's three different approaches; I hope one of them is helpful to you!

Add fact to list if it's not already in

I need to construct a list based on facts I have. For example I have a course list like this :
attend(student1,c1).
attend(student1,c2).
attend(student2,c1).
attend(student2,c3).
Now I want to have a predicate courselist/2 which returns a list of courses for a given student. Of course every course should be in this list only once. I can't use built-in predicates like findall but I can use member or append. So far I have something like this :
courselist(S,R) :- attend(S,C), member(C,R), courselist(S,R).
courselist(S,R) :- attend(S,C), append([C],L,R), courselist(S,R).
and I know that's wrong but I don't know how to find all facts without getting into an endless loop.
It's a silly restriction that you cannot use findall/3, because it is a natural solution for such a problem. You can do it manually like this:
student_courses(Student, Courses) :-
student_courses(Student, [], Courses).
student_courses(S, Cs0, Cs) :-
( attend(S, C), \+ member(C, Cs0) ->
student_courses(S, [C|Cs0], Cs)
; Cs = Cs0
).
Example query:
?- student_courses(student2, Cs).
Cs = [c3, c1].
Note that this is not a true relation, since this particular solution does not appear in the following more general query:
?- student_courses(Student, Cs).
Student = student1,
Cs = [c2, c1].
I leave it as an exercise for you to implement it in such a way that the most general query yields all correct results. Also notice the more readable and relational predicate names.

Prolog lists and parameters and return values

I'm new to prolog and I just can't figure this out.
I'm trying to build a simple program that receives a list of predicates, searches for a specific predicate in the list, and applies a function to that predicate's parameters.
Something along these lines:
?- program([pred1(a,b,p), pred2(d,b,p), pred2 (a,c,p)]).
program (list1) :-
search(pred2(X,Y,p),list1).
doSomething (X,Y) % with the X and Y returned from search function, both of them.
Basically, I want to use all values that would return from an objective search(pred2(X,Y,p),list1) and use them on another function.
Okay, I tried some stuff in prolog and came to this:
member(X, [X | _]).
member(X, [_ | R]) :- member(X, R).
prog(L1,Out) :- member(pred2(X,Y), L1).
?- prog ([(pred1(a,b),pred2(c,b),pred2(d,a)],Out).
It gives true 2 times as it is supposed to, but I wanted to get Out = [c,b] and Out = [d,a]. How I can achieve this?
Regarding Oak's answer: I get that it isn't a procedural language but I can't figure out how to access values and use them in prolog. Your example wasn't that helpful.
For starters, I would avoiding calling these things "functions". Prolog is not a procedural language, and rules / predicates are not functions.
Basically, when you use a rule you're really asking Prolog, "give me all the values which will satisfy this rule". The rule, by itself, does not return anything.
So say you had the following in a procedural language:
f(g(3))
How would you do it in Prolog? You would need to write some predicate f(X,Y) and some predicate g(X,Y), and then you would need to use the query f(3,Y), g(Y,Z) - which means to ask Prolog to find you values for Y and Z which will satisfy this. Z is what you're interested in.
the best way to approach these filter & project requirements in prolog in my opinion is to write your filter expression such that it takes one argument and succeeds if the input argument passes the filter -
iseven(Num) :- 0 is Num % 2 .
Then write the the projection code as taking one argument that is the input, and one that is the output -
triple(NumIn, NumOut) :- NumOut is NumIn * 3 .
Then tie them together -
triple_evens(NumIn, NumOut) :- iseven(NumIn), triple(NumIn, NumOut).
Then to run this on every member of a list, we should use findall -
triple_evens_in_list(Lin, Lout) :-
findall(Num, ( member(NumL, Lin),
triple_evens(NumL, Num)
), LOut).
This could be generalized to take as arguments the name of the filter & map predicates of course. And it could be compressed down to one stmt too in the form -
findall(Num, ( member(M, List), 0 is M % 2, Num is M * 3 ), ListOut).