How to parsing list in prolog until not fail - prolog

I am trying to parse a list, for example:
[1,3,3,2,2,7,2,9]
Let's say I have the following code, where isTwo will print No and fail if it is anything other than two. I WANT it to fail if it is anything other than two. If it is a two, it will print Yes and succeed.
isTwo(2) :-
write('Yes'), !.
isTwo(_) :-
write('No'), fail.
My issue is that I have something along the lines of an iterator defined, and I want to parse an entire list to find the first success.
iter([]).
iter([Head|Tail]) :-
isTwo(Head),
iter(Tail).
This works fine but will stop parsing the rest of the list as soon as failure is found. If we go back to the original list, [1,3,3,2,2,7,2,9], we get false as our output.
My question here is: how can I continue to parse in prolog while still ensuring that isTwo(_) (where it is not equal to two) will still fail, so that I can get an output of something such as NoNoNoYesYesNoYesNo in this case. Preferably without using an if-then-else clause.
This may help:
expected output: NoNoNoYesYesNoYesNo
observed output: No

Well an easy solution would be to use a second variable in iter that will help you understand if an number different than 2 is found:
isTwo(2, X, X) :-
write('Yes').
isTwo(_, _, 0) :-
write('No').
iter([], 0):- fail,!.
iter([], 1).
iter([Head|Tail], X) :-
isTwo(Head, X, Y),
iter(Tail, Y).
iter(L) :- iter(L, 1).

If you want a more concise solution, using maplist/2 you can do something like:
isTwo(2) :- write('Yes'), !.
isTwo(_):- write('No').
test(L):-
maplist(isTwo,L).
?- test([1,3,3,2,2,7,2,9]).
NoNoNoYesYesNoYesNo
true
test/1 is not mandatory, i've added it only for sake of clarity...

The other answers are both fine but the haphazard mixing in of side effects makes me a bit nervous. Also, you have a problem if the list you are "parsing" has a free variable (it will become 2 silently).
Why not like this:
is_two(X) :- X == 2, !, format("Yes").
is_two(X) :- X \== 2, !, format("No").
and then:
?- forall(member(X, [1,3,3,2,2,7,2,9]), is_two(X)).
NoNoNoYesYesNoYesNo
true.
?- forall(member(X, [Y, 2, Z]), is_two(X)).
NoYesNo
true.
Use == and \== to compare without unifying. Use forall and member to make it clear that you are doing it for the side effect. Traversing a list (or using maplist) is a bit deceiving.
forall is just a clearer way to do a failure-driven loop using negation instead of cuts and fails. The query above is identical to:
?- \+ ( member(X, [1,3,3,2,2,7,2,9]), \+ is_two(X) ).

Related

Prolog, predicate returns the correct result, but also false?

I found that for most of my predicates, prolog finds multiple solutions, with one of them being the correct result, the other is 'false.'
To demontrate:
%finds the last element of list, or false if empty.
last([H|L], More):-
last(L, More).
last([H], H).
running this gives:
?- last([a, b, c], W).
W = c ;
false.
Can anyone explain why it is giving 'false.' in addition? Is this something I need to fix?
You're not doing anything wrong, nor this is something to fix. What prolog is telling you by printing false at the end is that there are no other solutions than the ones it has already shown you. (Note that hitting ; tells prolog to show you more answers, you can also hit return to simply terminate the query.)
See Section 2.1.3 of https://www.swi-prolog.org/download/stable/doc/SWI-Prolog-8.2.1.pdf for details.
You can modify it a bit:
last(List, Last):- last(List, _, Last).
last([H | T], _, Last):-
last(T, H, Last).
last([], Last, Last). % Unify H and Last - no other solution
Simple solution:
last(List, Last) :-
once(append(_, [Last], List)).

I have defined multiple predicates that seem to share a common form

All of these predicates are defined in pretty much the same way. The base case is defined for the empty list. For non-empty lists we unify in the head of the clause when a certain predicate holds, but do not unify if that predicate does not hold. These predicates look too similar for me to think it is a coincidence. Is there a name for this, or a defined abstraction?
intersect([],_,[]).
intersect(_,[],[]).
intersect([X|Xs],Ys,[X|Acc]) :-
member(X,Ys),
intersect(Xs,Ys,Acc).
intersect([X|Xs],Ys,Acc) :-
\+ member(X,Ys),
intersect(Xs,Ys,Acc).
without_duplicates([],[]).
without_duplicates([X|Xs],[X|Acc]) :-
\+ member(X,Acc),
without_duplicates(Xs,Acc).
without_duplicates([X|Xs],Acc) :-
member(X,Acc),
without_duplicates(Xs,Acc).
difference([],_,[]).
difference([X|Xs],Ys,[X|Acc]) :-
\+ member(X,Ys),
difference(Xs,Ys,Acc).
difference([X|Xs],Ys,Acc) :-
member(X,Ys),
difference(Xs,Ys,Acc).
delete(_,[],[]).
delete(E,[X|Xs],[X|Ans]) :-
E \= X,
delete(E,Xs,Ans).
delete(E,[X|Xs],Ans) :-
E = X,
delete(E,Xs,Ans).
There is an abstraction for "keep elements in list for which condition holds".
The names are inclide, exclude. There is a library for those in SWI-Prolog that you can use or copy. Your predicates intersect/3, difference/3, and delete/3 would look like this:
:- use_module(library(apply)).
intersect(L1, L2, L) :-
include(member_in(L1), L2, L).
difference(L1, L2, L) :-
exclude(member_in(L2), L1, L).
member_in(List, Member) :-
memberchk(Member, List).
delete(E, L1, L) :-
exclude(=(E), L1, L).
But please take a look at the implementation of include/3 and exclude/3, here:
https://www.swi-prolog.org/pldoc/doc/_SWI_/library/apply.pl?show=src#include/3
Also in SWI-Prolog, in another library, there are versions of those predicates called intersection/3, subtract/3, delete/3:
https://www.swi-prolog.org/pldoc/doc/_SWI_/library/lists.pl?show=src#intersection/3
https://www.swi-prolog.org/pldoc/doc/_SWI_/library/lists.pl?show=src#subtract/3
https://www.swi-prolog.org/pldoc/doc_for?object=delete/3
Those are similar in spirit to your solutions.
Your next predicate, without_duplicates, cannot be re-written like that with include/3 or exclude/3. Your implementation doesn't work, either. Try even something easy, like:
?- without_duplicates([a,b], L).
What happens?
But yeah, it is not the same as the others. To implement it correctly, depending on whether you need the original order or not.
If you don't need to keep the initial order, you can simply sort; this removes duplicates. Like this:
?- sort(List_with_duplicates, No_duplicates).
If you want to keep the original order, you need to pass the accumulated list to the recursive call.
without_duplicates([], []).
without_duplicates([H|T], [H|Result]) :-
without_duplicates_1(T, [H], Result).
without_duplicates_1([], _, []).
without_duplicates_1([H|T], Seen0, Result) :-
( memberchk(H, Seen0)
-> Seen = Seen0 , Result = Result0
; Seen = [H|Seen0], Result = [H|Result0]
),
without_duplicates_1(T, Seen, Result0).
You could get rid of one argument if you use a DCG:
without_duplicates([], []).
without_duplicates([H|T], [H|No_duplicates]) :-
phrase(no_dups(T, [H]), No_duplicates).
no_dups([], _) --> [].
no_dups([H|T], Seen) -->
{ memberchk(H, Seen) },
!,
no_dups(T, Seen).
no_dups([H|T], Seen) -->
[H],
no_dups(T, [H|Seen]).
Well, these are the "while loops" of Prolog on the one hand, and the inductive definitions of mathematical logic on the other hand (See also: Logic Programming, Functional Programming, and Inductive Definitions, Lawrence C. Paulson, Andrew W. Smith, 2001), so it's not surprising to find them multiple times in a program - syntactically similar, with slight deviations.
In this case, you just have a binary decision - whether something is the case or not - and you "branch" (or rather, decide to not fail the body and press on with the selected clause) on that. The "guard" (the test which supplements the head unification), in this case member(X,Ys) or \+ member(X,Ys) is a binary decision (it also is exhaustive, i.e. covers the whole space of possible X)
intersect([X|Xs],Ys,[X|Acc]) :- % if the head could unify with the goal
member(X,Ys), % then additionally check that ("guard")
(...action...). % and then do something
intersect([X|Xs],Ys,Acc) :- % if the head could unify with the goal
\+ member(X,Ys), % then additionally check that ("guard")
(...action...). % and then do something
Other applications may need the equivalent of a multiple-decision switch statement here, and so N>2 clauses may have to be written instead of 2.
foo(X) :-
member(X,Set1),
(...action...).
foo(X) :-
member(X,Set2),
(...action...).
foo(X) :-
member(X,Set3),
(...action...).
% inefficient pseudocode for the case where Set1, Set2, Set3
% do not cover the whole range of X. Such a predicate may or
% may not be necessary; the default behaviour would be "failure"
% of foo/1 if this clause does not exist:
foo(X) :-
\+ (member(X,Set1);member(X,Set2);member(X,Set3)),
(...action...).
Note:
Use memberchk/2 (which fails or succeeds-once) instead of member/2 (which fails or succeeds-and-then-tries-to-succeed-again-for-the-rest-of-the-set) to make the program deterministic in its decision whether member(X,L).
Similarly, "cut" after the clause guard to tell Prolog that if a guard of one clause succeeds, there is no point in trying the other clauses because they will all turn out false: member(X,Ys),!,...
Finally, use term comparison == and \== instead of unification = or unification failure \= for delete/3.

Writing an unnamed variable

I am writing a program in Prolog (gprolog) that pathfinds on a graph. I based it partially off of this SO post.
Let me give an example. Here is an example graph I drew:
And here is what the code initially looked like:
path([Goal],Goal,Goal).
path(P,Start,Goal) :- adjacent(Start,X),
\+ (memberchk(X,P)),
(
Goal=X
;
path([Start|P],X,Goal)
).
Regardless of whether that base case is redundant, here is the problem. I want an input style of
| ?- path(P,a,f).
and for that input, I would get output of
P = [a,s,f]
true ?
However, the problem with the code as it stands lies with memberchk. For memberchk(a,P), it attempt to unify, calls memberchk(a,[a|_]), and returns true. I don't want this to happen, so I first check if P is instantiated using the var/1 predicate. Thus, my code changed to
path([Goal],Goal,Goal).
path(P,Start,Goal) :- var(P),
path([],Start,Goal).
path(P,Start,Goal) :- adjacent(Start,X),
\+ (memberchk(X,P)),
(
Goal=X
;
path([Start|P],X,Goal)
).
Now if P is uninstantiated, we call path/3 with the empty list. My problem is this: now I cannot print P at the end, as I call path([],Start,Goal) and P is no longer associated with [].
I have tried using the write/1 predicate, but it either printed out P at every step or printed P = _26 (meaning it's printing the uninstantiated P, not the final value of P).
I hope this is a simple problem, I'm just awfully new to Prolog.
Apologies if something similar has been asked; I would love to be pointed to other questions that could help. I searched through SO and Google before posting this.
The concept you need is that of accumulators
You were actually very close: you realized indeed that initializing P to [], and filling it with [Start|P] as you recurse was a working strategy. This is called an accumulator, and to get the final result you simply need to add another argument.
Here is your new path/3 predicate that you query:
path(P, Start, Goal) :-
path([], P, Start, Goal).
As you can see, here we add the [] as a first argument to path/4, which we implement like this:
path(L, P, Goal, Goal) :-
reverse([Goal|L], P).
path(L, P, Start, Goal) :-
adjacent(Start, X),
\+ (memberchk(X, L)),
path([Start|L], P, X, Goal).
The first clause is here to terminate the recursion. Once the Start and Goal arguments are the same as you had noted, the recursion should be over. When using an accumulator this means that we unify the accumulator with the output argument. However, the accumulator contains the answer reversed (and lacks the final goal), so we have reverse([Goal|L], P).
The second clause is very similar to what you had written, with the exception that we now need to pass P as is to the recursive clause. Note that I have removed your disjunction in that clause, it isn't needed in that case.
The complete code:
path(P, Start, Goal) :-
path([], P, Start, Goal).
path(L, P, Goal, Goal) :-
reverse([Goal|L], P).
path(L, P, Start, Goal) :-
adjacent(Start, X),
\+ (memberchk(X, L)),
path([Start|L], P, X, Goal).
I solved my problem. The solution relies on:
Keeping track of visited nodes
When recursing, recursing on a smaller list
Checking if something is not a member of a list to prevent unification when not wanted
My code is as follows:
connected(X,Y) :- adjacent(X,Y);adjacent(Y,X).
not_member(_, []).
not_member(X, [Head|Tail]) :- X \== Head, not_member(X, Tail).
path(P,A,B):-path_helper(P,A,B,[Start]).
path_helper([X,Y],X,Y,_):-connected(X,Y).
path_helper([Goal],Goal,Goal,_).
path_helper([Start|[Head|P]],Start,Goal,Visited):-connected(Start,Head),not_member(Head,Visited),path_helper([Head|P],Head,Goal,[Head|Visited]).

How to store the first returned value of a function in prolog?

I have a function like this:
myFunction(V1, V2, Result) :-
Result is V1/V1cover + V2/V2cover,
write(Result).
myFunction(0,0,0).
keepValue(V1,V2,V1cover,V2cover) :-
V1cover is V1,
V2cover is V2.
There are other functions that call myFunction many times and get the Result back. However, I would like to get the first Result that myFunction is called first time and keep it to use for calls later(In this case, it is V1cover and V2cover). For example, first time, myFunction(4,4,A) is called. Then it returns A = 2. After that I would like to keep the value of V1cover(4) and V2cover(4) to use for next called times. How I can do that? I tried to apply a cached techonology like and apply it into myFunction:
:- dynamic(cachedGoal_sol/2).
reset :-
retractall(cachedGoal_sol(_, _)).
eq(A, B) :-
subsumes_term(A, B),
subsumes_term(B, A).
cached_call(Goal) :-
\+ (cachedGoal_sol(First,_), eq(First, Goal)),
copy_term(Goal, First),
catch(
( Goal,
assertz(cachedGoal_sol(First, Goal)),
fail
),
Pat,
(reset, throw(Pat))).
cached_call(Goal) :-
cachedGoal_sol(First, Results),
eq(First, Goal),
Results = Goal.
myFunction(V1, V2, Result) :-
**cached_call(keepValue(V1,V2,V1cover,V2cover),**
Result is V1/V1cover + V2/V2cover,
write(Result).
but it doesn't work, when I try to run the second time myFunction(2,3,A) and trace the program, it actually stores solution of the first call but I couldn't get the first values of V1cover, V2cover since eq() in the second cached_call() fails. Is there a way to only get values of V1cover, V2cover without touching to V1,V2 since they are input? Thanks very much for your answer.
Your code has some errors and it's a bit too complicated. I'll try to give you an answer that might be useful to others too.
Let's suppose we need a predicate to store information about the context in which a goal was first satisfied.
I'll use a simple example. Let's say we have a rule to find pairs of numbers between 1 and 4 that add to 6.
sum_to_six(X, Y) :- between(1, 4, X), between(1, 4, Y), X + Y =:= 6.
Trying to find all pairs that satisfy the above rule, one gets the following answer:
?- findall(pair(X,Y), sum_to_six(X, Y), All).
All = [pair(2, 4), pair(3, 3), pair(4, 2)].
Now, let's return to your question. Let's suppose we need the first pair that satisfied the goal. We should modify the rule for predicate sum_to_six/2.
sum_to_six(X, Y):-
between(1, 4, X), between(1, 4, Y), X + Y =:= 6,
store_first(pair(X,Y)).
The subgoal store_first(pair(X,Y)) succeeds every time, but asserts pair(X,Y) just the first time (if there is no other pair(_,_) in the dynamic memory). So, the answer you need might be something similar to this:
store_first(Goal):-
Goal =.. [Name | Args], %% Name is the name of the predicate
length(Args, N), %% N represents its arity
length(NVars, N),
Test =.. [Name | NVars], %% Test is a goal like p(_, _, _, ...)
(
Test, !
;
assertz(Goal)
).
Now, to get the stored information:
?- retractall(pair(_,_)), findall(_, sum_to_six(_,_), _), pair(FirstX, FirstY).
FirstX = 2,
FirstY = 4.
If you want only the first answer, simply write
..., cached_call(once(Goal)), ....
using this definition.

Prolog difference routine

I need some help with a routine that I am trying to create. I need to make a routine that will look something like this:
difference([(a,b),(a,c),(b,c),(d,e)],[(a,_)],X).
X = [(b,c),(d,e)].
I really need help on this one..
I have written a method so far that can remove the first occurrence that it finds.. however I need it to remove all occurrences. Here is what I have so far...
memberOf(A, [A|_]).
memberOf(A, [_|B]) :-
memberOf(A, B).
mapdiff([], _, []) :- !.
mapdiff([A|C], B, D) :-
memberOf(A, B), !,
mapdiff(C, B, D).
mapdiff([A|B], C, [A|D]) :-
mapdiff(B, C, D).
I have taken this code from listing(subtract).
I don't fully understand what it does, however I know it's almost what I want. I didn't use subtract because my final code has to be compatible with WIN-Prolog... I am testing it on SWI Prolog.
Tricky one! humble coffee has the right idea. Here's a fancy solution using double negation:
difference([], _, []).
difference([E|Es], DL, Res) :-
\+ \+ member(E, DL), !,
difference(Es, DL, Res).
difference([E|Es], DL, [E|Res]) :-
difference(Es, DL, Res).
Works on SWI-PROLOG. Explanation:
Clause 1: Base case. Nothing to diff against!
Clause 2: If E is in the difference list DL, the member/2 subgoal evaluates to true, but we don't want to accept the bindings that member/2 makes between variables present in terms in either list, as we'd like, for example, the variable in the term (a,_) to be reusable across other terms, and not bound to the first solution. So, the 1st \+ removes the variable bindings created by a successful evaluation of member/2, and the second \+ reverses the evaluation state to true, as required. The cut occurs after the check, excluding the 3rd clause, and throwing away the unifiable element.
Clause 3: Keep any element not unifiable across both lists.
I am not sure, but something like this could work. You can use findall to find all elements which can't be unified with the pattern:
?- findall(X, (member(X, [(a,b),(b,c),(a,c)]), X \= (a,_)), Res).
gets the reply
Res = [ (b, c) ]
So
removeAll(Pattern, List, Result) :-
findall(ZZ109, (member(ZZ109, List), ZZ109 \= Pattern), Result).
should work, assuming ZZ109 isn't a variable in Pattern (I don't know a way to get a fresh variable for this, unfortunately. There may be a non-portable one in WIN-Prolog). And then difference can be defined recursively:
difference(List, [], List).
difference(List, [Pattern|Patterns], Result) :-
removeAll(Pattern, List, Result1),
difference(Result1, Patterns, Result).
Your code can be easily modified to work by making it so that the memberOF predicate just checks to see that there is an element in the list that can be unified without actually unifying it. In SWI Prolog this can be done this way:
memberOf(A, [B|_]) :- unifiable(A,B,_).
But I'm not familiar with WIN-PRolog so don't know whether it has a predicate or operator which only tests whether arguments can be unified.

Resources