how to solve when the number of variables in the goal/query varies - Prolog Constrain Solver - prolog

Here's a snippet on the classic SENDMORY crypt-arithmetic problem solutiong using prolog constraint solving mechanism-
:- lib(ic).
sendmore(Digits) :-
Digits = [S,E,N,D,M,O,R,Y],
Digits :: [0..9],
alldifferent(Digits),
S #\= 0,
M #\= 0,
1000*S + 100*E + 10*N + D
+ 1000*M + 100*O + 10*R + E
#= 10000*M + 1000*O + 100*N + 10*E + Y,
labeling(Digits).
Now, to execute this, I would send a goal/query like this:
?- sendmore(Digits).
And that would return me the possible solutions for the digits.
Now, my question is, I do not want to sort of "hard-code" the variables (like S,E,N,...) this way, but the goal/query would give the number of variables. For example, if the query I pass is something like:
?- sendmore(S,E,N,D,M).
then, it should compute only the values of SENDM and assume that the other variables are not applicable, and hence assign 0 to those variables and then proceed with the computation. And the next time I query, I may pass a different number of variables in the query.. like example:
?- sendmore(S,N,D,M,O,Y).
and the program should compute likewise.
What I am trying to achieve is a more generalised problem solver for the above scenario. Any directions on this is really appreciated. I am quite new to prolog,and am using ECLIPSE constraint solver.
Thank You.

Here are 2 ideas:
You can define sendmore() with different numbers of parameters, which would call the "real" version with the missing ones filled in. But you couldn't have different versions with the same NUMBER of parameters but DIFFERENT ones (since Prolog matches args to parameters by position).
You could expand/complicate your list format to allow the specification of which parameters you are passing; something line [(s,S),(e,E),(n,N),(d,D),(m,M)] for your middle example. A little tedious, but gives you the flexibility you seem to want.

Normally, variables in a goal and variables in a clause head are matched by their positions, not their names. So a call ?- sendmore0([S,E,N,D,M]). should be implemented as:
sendmore0([S,E,N,D,M]) :- sendmore([S,E,N,D,M,_,_,_]).
However, this would mean that you would need to implement this for every possible combination.
If you really want to implement what you describe, then you need to give the variable stable names. In ECLiPSe, you can do this with the library var_name. It's quite a hack, though...
:- lib(var_name).
sendmore0(L) :-
build_arg(["S","E","N","D","M',"O","R","Y"], L, A),
sendmore(A).
build_arg([], _, []) :- !.
build_arg([H|T], L, [HA|HT]) :-
match_arg(L, H, HA),
build_arg(T, L, HT).
match_arg([], _, _). % or use 0 as last argument if you want
match_arg([H|T], Base, A) :-
(
get_var_name(H, S),
split_string(S,"#","",[Base,_])
->
A = H
;
match_arg(T, Base, A)
).
Then you can call sendmore0/1 with a shorter list of variables. Don't forget to set the variable names!
?- set_var_name(S, "S"), set_var_name(E, "E"), sendmore0([S, E]).
S = 9
E = 5
Yes (0.00s cpu, solution 1, maybe more)
Disclaimer: this is not what stable names are for. They are meant for debugging purposes. If Joachim ever sees this, he'll give me a sharp clip round the ears...

Related

Prolog - subsitution and evaluation

Hello good people of programming .
Logic programming is always fascinating compare to imperative programming.
As pursuing unknown of logic programming, there is some problems encountering arithmetic expressions.
Here is the code I have done so far.
number_atom(N) :-
(number(N) -> functor(N, _, _); functor(N, _, _), atom(N)).
arithmeticAdd_expression(V,V,Val,Val).
arithmeticAdd_expression(N, _Var, _Val, N) :-
number_atom(N).
arithmeticAdd_expression(X+Y, Var, Val, R) :-
arithmeticAdd_expression(X, Var, Val, RX),
arithmeticAdd_expression(Y, Var, Val, RY),
(number(RX), number(RY) -> R is RX + RY; R = RX + RY).
Taking add operation as example:
arithmeticAdd_expression(Expression, Variable, Value, Result)
?- arithmeticAdd_expression(a+10, a, 1, Result).
?- Result = 11;
?- Result = a + 10.
?- arithmeticAdd_expression(a+10, b, 1, Result).
?- Result = a + 10.
What I would like to achieve is that
if the atom(s) in the Expression can only be substituted by given Variable and value, then Result is the number only like the example shown above(Result = 11). Else, the Result is the Expression itself only. My problem with the code is somewhere there, I just could figure it out. So, Please someone can help me? Thank you.
An important attraction of logic programming over, say, functional programming is that you can often use the same code in multiple directions.
This means that you can ask not only for a particular result if the inputs are given, but also ask how solutions look like in general.
However, for this to work, you have to put some thought into the way you represent your data. For example, in your case, any term in your expression that is still a logical variable may denote either a given number or an atom that should be interpreted differently than a plain number or an addition of two other terms. This is called a defaulty representation because you have to decide what a variable should denote by default, and there is no way to restrict its meaning to only one of the possible cases.
Therefore, I suggest first of all to change the representation so that you can symbolically distinguish the two cases. For example, to represent expressions in your case, let us adopt the convention that:
atoms are denoted by the wrapper a/1
numbers are denoted by the wrapper n/1.
and as is already the case, (+)/2 shall denote addition of two expressions.
So, a defaulty term like b+10 shall now be written as: a(b)+n(10). Note the use of the wrappers a/1 and n/1 to make clear which case we are dealing with. Such a representation is called clean. The wrappers are arbitrarily (though mnemonically) chosen, and we could have used completely different wrappers such as atom/1 and number/1, or atm/1 and nmb/1. The key property is only that we can now symbolically distinguish different cases by virtue of their outermost functor and arity.
Now the key advantage: Using such a convention, we can write for example: a(X)+n(Y). This is a generalization of the earlier term. However, it carries a lot more information than only X+Y, because in the latter case, we have lost track of what these variables stand for, while in the former case, this distinction is still available.
Now, assuming that this convention is used in expressions, it becomes straight-forward to describe the different cases:
expression_result(n(N), _, _, n(N)).
expression_result(a(A), A, N, n(N)).
expression_result(a(A), Var, _, a(A)) :-
dif(A, Var).
expression_result(X+Y, Var, Val, R) :-
expression_result(X, Var, Val, RX),
expression_result(Y, Var, Val, RY),
addition(RX, RY, R).
addition(n(X), n(Y), n(Z)) :- Z #= X + Y.
addition(a(X), Y, a(X)+Y).
addition(X, a(Y), X+a(Y)).
Note that we can now use pattern matching to distinguish the cases. No more if-then-elses, and no more atom/1 or number/1 tests are necessary.
Your test cases work as expected:
?- expression_result(a(a)+n(10), a, 1, Result).
Result = n(11) ;
false.
?- expression_result(a(a)+n(10), b, 1, Result).
Result = a(a)+n(10) ;
false.
And now the key advantage: With such a pure program (please see logical-purity for more information), we can also ask "What do results look like in general?"
?- expression_result(Expr, Var, N, R).
Expr = R, R = n(_1174) ;
Expr = a(Var),
R = n(N) ;
Expr = R, R = a(_1698),
dif(_1698, Var) ;
Expr = n(_1852)+n(_1856),
R = n(_1896),
_1852+_1856#=_1896 ;
Expr = n(_2090)+a(Var),
R = n(_2134),
_2090+N#=_2134 .
Here, I have used logical variables for all arguments, and I get quite general answers from this program. This is why I have used clpfd constraints for declarative integer arithmetic.
Thus, your immediate issue can be readily solved by using a clean representation, and using the code above.
Only one very small challenge remains: Maybe you actually want to use a defaulty representation such as c+10 (instead of a(c)+n(10)). The task you are then facing is to convert the defaulty representation to a clean one, for example via a predicate defaulty_clean/2. I leave this as an easy exercise. Once you have a clean representation, you can use the code above without changes.

How can I verify if a coordinate is in a list

I'm generating random coordinates and adding on my list, but first I need verify if that coordinate already exists. I'm trying to use member but when I was debugging I saw that isn't working:
My code is basically this:
% L is a list and Q is a count that define the number of coordinate
% X and Y are the coordinate members
% check if the coordniate already exists
% if exists, R is 0 and if not, R is 1
createCoordinates(L,Q) :-
random(1,10,X),
random(1,10,Y),
convertNumber(X,Z),
checkCoordinate([Z,Y],L,R),
(R is 0 -> print('member'), createCoordinates(L,Q); print('not member'),createCoordinates(L,Q-1).
checkCoordinate(C,L,R) :-
(member(C,L) -> R is 0; R is 1).
% transforms the number N in a letter L
convertNumber(N,L) :-
N is 1, L = 'A';
N is 2, L = 'B';
...
N is 10, L = 'J'.
%call createCoordinates
createCoordinates(L,20).
When I was debugging this was the output:
In this picture I'm in the firts interation and L is empty, so R should be 1 but always is 0, the coordinate always is part of the list.
I have the impression that the member clause is adding the coordinate at my list and does'nt make sense
First off, I would recommend breaking your problem down into smaller pieces. You should have a procedure for making a random coordinate:
random_coordinate([X,Y]) :-
random(1, 10, XN), convertNumber(XN, X),
random(1, 10, Y).
Second, your checkCoordinate/3 is converting Prolog's success/failure into an integer, which is just busy work for Prolog and not really improving life for you. memberchk/2 is completely sufficient to your task (member/2 would work too but is more powerful than necessary). The real problem here is not that member/2 didn't work, it's that you are trying to build up this list parameter on the way out, but you need it to exist on the way in to examine it.
We usually solve this kind of problem in Prolog by adding a third parameter and prepending values to the list on the way through. The base case then equates that list with the outbound list and we protect the whole thing with a lower-arity procedure. In other words, we do this:
random_coordinates(N, Coordinates) :- random_coordinates(N, [], Coordinates).
random_coordinates(0, Result, Result).
random_coordinates(N, CoordinatesSoFar, FinalResult) :- ...
Now that we have two things, memberchk/2 should work the way we need it to:
random_coordinates(N, CoordinatesSoFar, FinalResult) :-
N > 0, succ(N0, N), % count down, will need for recursive call
random_coordinate(Coord),
(memberchk(Coord, CoordinatesSoFar) ->
random_coordinates(N, CoordinatesSoFar, FinalResult)
;
random_coordinates(N0, [Coord|CoordinatesSoFar], FinalResult)
).
And this seems to do what we want:
?- random_coordinates(10, L), write(L), nl.
[[G,7],[G,3],[H,9],[H,8],[A,4],[G,1],[I,9],[H,6],[E,5],[G,8]]
?- random_coordinates(10, L), write(L), nl.
[[F,1],[I,8],[H,4],[I,1],[D,3],[I,6],[E,9],[D,1],[C,5],[F,8]]
Finally, I note you continue to use this syntax: N is 1, .... I caution you that this looks like an error to me because there is no distinction between this and N = 1, and your predicate could be stated somewhat tiresomely just with this:
convertNumber(1, 'A').
convertNumber(2, 'B').
...
My inclination would be to do it computationally with char_code/2 but this construction is actually probably better.
Another hint that you are doing something wrong is that the parameter L to createCoordinates/2 gets passed along in all cases and is not examined in any of them. In Prolog, we often have variables that appear to just be passed around meaninglessly, but they usually change positions or are used multiple times, as in random_coordinates(0, Result, Result); while nothing appears to be happening there, what's actually happening is plumbing: the built-up parameter becomes the result value. Nothing interesting is happening to the variable directly there, but it is being plumbed around. But nothing is happening at all to L in your code, except it is supposedly being checked for a new coordinate. But you're never actually appending anything to it, so there's no reason to expect that anything would wind up in L.
Edit Notice that #lambda.xy.x solves the problem in their answer by prepending the new coordinate in the head of the clause and examining the list only after the recursive call in the body, obviating the need for the second list parameter.
Edit 2 Also take a look at #lambda.xy.x's other solution as it has better time complexity as N approaches 100.
Since i had already written it, here is an alternative solution: The building block is gen_coord_notin/2 which guarantees a fresh solution C with regard to an exclusion list Excl.
gen_coord_notin(C, Excl) :-
random(1,10,X),
random(1,10,Y),
( memberchk(X-Y, Excl) ->
gen_coord_notin(C, Excl)
;
C = X-Y
).
The trick is that we only unify C with the new result, if it is fresh.
Then we only have to fold the generations into N iterations:
gen_coords([], 0).
gen_coords([X|Xs], N) :-
N > 0,
M is N - 1,
gen_coords(Xs, M),
gen_coord_notin(X, Xs).
Remark 1: since coordinates are always 2-tuples, a list representation invites unwanted errors (e.g. writing [X|Y] instead of [X,Y]). Traditionally, an infix operator like - is used to seperate tuples, but it's not any different than using coord(X,Y).
Remark 2: this predicate is inherently non-logical (i.e. calling gen_coords(X, 20) twice will result in different substitutions for X). You might use the meta-level predicates var/1, nonvar/1, ground/1, integer, etc. to guard against non-sensical calls like gen_coord(1-2, [1-1]).
Remark 3: it is also important that the conditional does not have multiple solutions (compare member(X,[A,B]) and memberchk(X,[A,B])). In general, this can be achieved by calling once/1 but there is a specialized predicate memberchk/2 which I used here.
I just realized that the performance of my other solutions is very bad for N close to 100. The reason is that with diminishing possible coordinates, the generate and test approach will take longer and longer. There's an alternative solution which generates all coordinates and picks N random ones:
all_pairs(Ls) :-
findall(X-Y, (between(1,10,X), between(1,10,Y)), Ls).
remove_index(X,[X|Xs],Xs,0).
remove_index(I,[X|Xs],[X|Rest],N) :-
N > 0,
M is N - 1,
remove_index(I,Xs,Rest,M).
n_from_pool(_Pool, [], 0).
n_from_pool(Pool, [C|Cs], N) :-
N > 0,
M is N - 1,
length(Pool, L),
random(0,L,R),
remove_index(C,Pool,NPool,R),
n_from_pool(NPool, Cs, M).
gen_coords2(Xs, N) :-
all_pairs(Pool),
n_from_pool(Pool, Xs, N).
Now the query
?- gen_coords2(Xs, 100).
Xs = [4-6, 5-6, 5-8, 9-6, 3-1, 1-3, 9-4, 6-1, ... - ...|...] ;
false.
succeeds as expected. The error message
?- gen_coords2(Xs, 101).
ERROR: random/1: Domain error: not_less_than_one' expected, found0'
when we try to generate more distinct elements than possible is not nice, but better than non-termination.

Fold over a partial list

This is a question provoked by an already deleted answer to this question. The issue could be summarized as follows:
Is it possible to fold over a list, with the tail of the list generated while folding?
Here is what I mean. Say I want to calculate the factorial (this is a silly example but it is just for demonstration), and decide to do it like this:
fac_a(N, F) :-
must_be(nonneg, N),
( N =< 1
-> F = 1
; numlist(2, N, [H|T]),
foldl(multiplication, T, H, F)
).
multiplication(X, Y, Z) :-
Z is Y * X.
Here, I need to generate the list that I give to foldl. However, I could do the same in constant memory (without generating the list and without using foldl):
fac_b(N, F) :-
must_be(nonneg, N),
( N =< 1
-> F = 1
; fac_b_1(2, N, 2, F)
).
fac_b_1(X, N, Acc, F) :-
( X < N
-> succ(X, X1),
Acc1 is X1 * Acc,
fac_b_1(X1, N, Acc1, F)
; Acc = F
).
The point here is that unlike the solution that uses foldl, this uses constant memory: no need for generating a list with all values!
Calculating a factorial is not the best example, but it is easier to follow for the stupidity that comes next.
Let's say that I am really afraid of loops (and recursion), and insist on calculating the factorial using a fold. I still would need a list, though. So here is what I might try:
fac_c(N, F) :-
must_be(nonneg, N),
( N =< 1
-> F = 1
; foldl(fac_foldl(N), [2|Back], 2-Back, F-[])
).
fac_foldl(N, X, Acc-Back, F-Rest) :-
( X < N
-> succ(X, X1),
F is Acc * X1,
Back = [X1|Rest]
; Acc = F,
Back = []
).
To my surprise, this works as intended. I can "seed" the fold with an initial value at the head of a partial list, and keep on adding the next element as I consume the current head. The definition of fac_foldl/4 is almost identical to the definition of fac_b_1/4 above: the only difference is that the state is maintained differently. My assumption here is that this should use constant memory: is that assumption wrong?
I know this is silly, but it could however be useful for folding over a list that cannot be known when the fold starts. In the original question we had to find a connected region, given a list of x-y coordinates. It is not enough to fold over the list of x-y coordinates once (you can however do it in two passes; note that there is at least one better way to do it, referenced in the same Wikipedia article, but this also uses multiple passes; altogether, the multiple-pass algorithms assume constant-time access to neighboring pixels!).
My own solution to the original "regions" question looks something like this:
set_region_rest([A|As], Region, Rest) :-
sort([A|As], [B|Bs]),
open_set_closed_rest([B], Bs, Region0, Rest),
sort(Region0, Region).
open_set_closed_rest([], Rest, [], Rest).
open_set_closed_rest([X-Y|As], Set, [X-Y|Closed0], Rest) :-
X0 is X-1, X1 is X + 1,
Y0 is Y-1, Y1 is Y + 1,
ord_intersection([X0-Y,X-Y0,X-Y1,X1-Y], Set, New, Set0),
append(New, As, Open),
open_set_closed_rest(Open, Set0, Closed0, Rest).
Using the same "technique" as above, we can twist this into a fold:
set_region_rest_foldl([A|As], Region, Rest) :-
sort([A|As], [B|Bs]),
foldl(region_foldl, [B|Back],
closed_rest(Region0, Bs)-Back,
closed_rest([], Rest)-[]),
!,
sort(Region0, Region).
region_foldl(X-Y,
closed_rest([X-Y|Closed0], Set)-Back,
closed_rest(Closed0, Set0)-Back0) :-
X0 is X-1, X1 is X + 1,
Y0 is Y-1, Y1 is Y + 1,
ord_intersection([X0-Y,X-Y0,X-Y1,X1-Y], Set, New, Set0),
append(New, Back0, Back).
This also "works". The fold leaves behind a choice point, because I haven't articulated the end condition as in fac_foldl/4 above, so I need a cut right after it (ugly).
The Questions
Is there a clean way of closing the list and removing the cut? In the factorial example, we know when to stop because we have additional information; however, in the second example, how do we notice that the back of the list should be the empty list?
Is there a hidden problem I am missing?
This looks like its somehow similar to the Implicit State with DCGs, but I have to admit I never quite got how that works; are these connected?
You are touching on several extremely interesting aspects of Prolog, each well worth several separate questions on its own. I will provide a high-level answer to your actual questions, and hope that you post follow-up questions on the points that are most interesting to you.
First, I will trim down the fragment to its essence:
essence(N) :-
foldl(essence_(N), [2|Back], Back, _).
essence_(N, X0, Back, Rest) :-
( X0 #< N ->
X1 #= X0 + 1,
Back = [X1|Rest]
; Back = []
).
Note that this prevents the creation of extremely large integers, so that we can really study the memory behaviour of this pattern.
To your first question: Yes, this runs in O(1) space (assuming constant space for arising integers).
Why? Because although you continuously create lists in Back = [X1|Rest], these lists can all be readily garbage collected because you are not referencing them anywhere.
To test memory aspects of your program, consider for example the following query, and limit the global stack of your Prolog system so that you can quickly detect growing memory by running out of (global) stack:
?- length(_, E),
N #= 2^E,
portray_clause(N),
essence(N),
false.
This yields:
1.
2.
...
8388608.
16777216.
etc.
It would be completely different if you referenced the list somewhere. For example:
essence(N) :-
foldl(essence_(N), [2|Back], Back, _),
Back = [].
With this very small change, the above query yields:
?- length(_, E),
N #= 2^E,
portray_clause(N),
essence(N),
false.
1.
2.
...
1048576.
ERROR: Out of global stack
Thus, whether a term is referenced somewhere can significantly influence the memory requirements of your program. This sounds quite frightening, but really is hardly an issue in practice: You either need the term, in which case you need to represent it in memory anyway, or you don't need the term, in which case it is simply no longer referenced in your program and becomes amenable to garbage collection. In fact, the amazing thing is rather that GC works so well in Prolog also for quite complex programs that not much needs to be said about it in many situations.
On to your second question: Clearly, using (->)/2 is almost always highly problematic in that it limits you to a particular direction of use, destroying the generality we expect from logical relations.
There are several solutions for this. If your CLP(FD) system supports zcompare/3 or a similar feature, you can write essence_/3 as follows:
essence_(N, X0, Back, Rest) :-
zcompare(C, X0, N),
closing(C, X0, Back, Rest).
closing(<, X0, [X1|Rest], Rest) :- X1 #= X0 + 1.
closing(=, _, [], _).
Another very nice meta-predicate called if_/3 was recently introduced in Indexing dif/2 by Ulrich Neumerkel and Stefan Kral. I leave implementing this with if_/3 as a very worthwhile and instructive exercise. Discussing this is well worth its own question!
On to the third question: How do states with DCGs relate to this? DCG notation is definitely useful if you want to pass around a global state to several predicates, where only a few of them need to access or modify the state, and most of them simply pass the state through. This is completely analogous to monads in Haskell.
The "normal" Prolog solution would be to extend each predicate with 2 arguments to describe the relation between the state before the call of the predicate, and the state after it. DCG notation lets you avoid this hassle.
Importantly, using DCG notation, you can copy imperative algorithms almost verbatim to Prolog, without the hassle of introducing many auxiliary arguments, even if you need global states. As an example for this, consider a fragment of Tarjan's strongly connected components algorithm in imperative terms:
function strongconnect(v)
// Set the depth index for v to the smallest unused index
v.index := index
v.lowlink := index
index := index + 1
S.push(v)
This clearly makes use of a global stack and index, which ordinarily would become new arguments that you need to pass around in all your predicates. Not so with DCG notation! For the moment, assume that the global entities are simply easily accessible, and so you can code the whole fragment in Prolog as:
scc_(V) -->
vindex_is_index(V),
vlowlink_is_index(V),
index_plus_one,
s_push(V),
This is a very good candidate for its own question, so consider this a teaser.
At last, I have a general remark: In my view, we are only at the beginning of finding a series of very powerful and general meta-predicates, and the solution space is still largely unexplored. call/N, maplist/[3,4], foldl/4 and other meta-predicates are definitely a good start. if_/3 has the potential to combine good performance with the generality we expect from Prolog predicates.
If your Prolog implementation supports freeze/2 or similar predicate (e.g. Swi-Prolog), then you can use following approach:
fac_list(L, N, Max) :-
(N >= Max, L = [Max], !)
;
freeze(L, (
L = [N|Rest],
N2 is N + 1,
fac_list(Rest, N2, Max)
)).
multiplication(X, Y, Z) :-
Z is Y * X.
factorial(N, Factorial) :-
fac_list(L, 1, N),
foldl(multiplication, L, 1, Factorial).
Example above first defines a predicate (fac_list) which creates a "lazy" list of increasing integer values starting from N up to maximum value (Max), where next list element is generated only after previous one was "accessed" (more on that below). Then, factorial just folds multiplication over lazy list, resulting in constant memory usage.
The key to understanding how this example works is remembering that Prolog lists are, in fact, just terms of arity 2 with name '.' (actually, in Swi-Prolog 7 the name was changed, but this is not important for this discussion), where first element represents list item and the second element represents tail (or terminating element - empty list, []). For example. [1, 2, 3] can be represented as:
.(1, .(2, .(3, [])))
Then, freeze is defined as follows:
freeze(+Var, :Goal)
Delay the execution of Goal until Var is bound
This means if we call:
freeze(L, L=[1|Tail]), L = [A|Rest].
then following steps will happen:
freeze(L, L=[1|Tail]) is called
Prolog "remembers" that when L will be unified with "anything", it needs to call L=[1|Tail]
L = [A|Rest] is called
Prolog unifies L with .(A, Rest)
This unification triggers execution of L=[1|Tail]
This, obviously, unifies L, which at this point is bound to .(A, Rest), with .(1, Tail)
As a result, A gets unified with 1.
We can extend this example as follows:
freeze(L1, L1=[1|L2]),
freeze(L2, L2=[2|L3]),
freeze(L3, L3=[3]),
L1 = [A|R2], % L1=[1|L2] is called at this point
R2 = [B|R3], % L2=[2|L3] is called at this point
R3 = [C]. % L3=[3] is called at this point
This works exactly like the previous example, except that it gradually generates 3 elements, instead of 1.
As per Boris's request, the second example implemented using freeze. Honestly, I'm not quite sure whether this answers the question, as the code (and, IMO, the problem) is rather contrived, but here it is. At least I hope this will give other people the idea what freeze might be useful for. For simplicity, I am using 1D problem instead of 2D, but changing the code to use 2 coordinates should be rather trivial.
The general idea is to have (1) function that generates new Open/Closed/Rest/etc. state based on previous one, (2) "infinite" list generator which can be told to "stop" generating new elements from the "outside", and (3) fold_step function which folds over "infinite" list, generating new state on each list item and, if that state is considered to be the last one, tells generator to halt.
It is worth to note that list's elements are used for no other reason but to inform generator to stop. All calculation state is stored inside accumulator.
Boris, please clarify whether this gives a solution to your problem. More precisely, what kind of data you were trying to pass to fold step handler (Item, Accumulator, Next Accumulator)?
adjacent(X, Y) :-
succ(X, Y) ;
succ(Y, X).
state_seq(State, L) :-
(State == halt -> L = [], !)
;
freeze(L, (
L = [H|T],
freeze(H, state_seq(H, T))
)).
fold_step(Item, Acc, NewAcc) :-
next_state(Acc, NewAcc),
NewAcc = _:_:_:NewRest,
(var(NewRest) ->
Item = next ;
Item = halt
).
next_state(Open:Set:Region:_Rest, NewOpen:NewSet:NewRegion:NewRest) :-
Open = [],
NewOpen = Open,
NewSet = Set,
NewRegion = Region,
NewRest = Set.
next_state(Open:Set:Region:Rest, NewOpen:NewSet:NewRegion:NewRest) :-
Open = [H|T],
partition(adjacent(H), Set, Adjacent, NotAdjacent),
append(Adjacent, T, NewOpen),
NewSet = NotAdjacent,
NewRegion = [H|Region],
NewRest = Rest.
set_region_rest(Ns, Region, Rest) :-
Ns = [H|T],
state_seq(next, L),
foldl(fold_step, L, [H]:T:[]:_, _:_:Region:Rest).
One fine improvement to the code above would be making fold_step a higher order function, passing it next_state as the first argument.

Counter in prolog

I want to create a counter in prolog.
Something like starting it init/0.
Adding 1 increment/0,
and something like get_counter/1. To get the value.
But I don't know how to start something if you have init/0 with no inputs how to set something to 0.
Can someone give me some tips how I should try to do this?
I'm not a native speaker, so if it's not clear what I mean I'm sorry.
Here is something that sort of does what you are trying to achieve:
?- X0 = 0 /* init */, succ(X0, X1) /* inc */, succ(X1, X2) /* inc */.
X0 = 0,
X1 = 1,
X2 = 2.
The init is just giving the variable a value, incrementing is done with succ/2, and the getval is implicit.
However, as I already said in the comment, consider your use case! If you are trying to keep track of how deep inside a loop you are, it is perfectly fine to do it with succ/2 or even following the suggestion by #mat.
So, to count the number of foos in a list:
list_foos([], 0).
list_foos([X|Xs], N) :-
( dif(X, foo)
-> list_foos(Xs, N)
; list_foos(Xs, N0),
succ(N0, N) % or: N0 + 1 #= N
).
You should try out both succ(N0, N) and N0 + 1 #= N to see how you can use them when either one or both of the arguments to list_foos/2 are not ground.
If, however, you need to maintain a global state for some reason: say, you are dynamically changing the database and you need to generate an increasing integer key for a table. Then, you should consider the answer by #coredump. Keep in mind that it is not super easy to write code that runs on any Prolog implementation once you start using "global" variables. One attempt would be to use the predicates for manipulating the database:
:- dynamic foocounter/1.
initfoo :-
retractall(foocounter(_)),
assertz(foocounter(0)).
incrfoo :-
foocounter(V0),
retractall(foocounter(_)),
succ(V0, V),
assertz(foocounter(V)).
And then, you can now count with a global state (it does not need to be in a conjunction like your example use):
?- initfoo.
true.
?- incrfoo.
true.
?- incrfoo.
true.
?- foocounter(V).
V = 2.
This is perfectly valid code but there are many pitfalls, so use with care.
I would use ECLiPSe's non-local variables:
init :- setval(counter, 0).
increment :- incval(counter).
get_counter(V) :- getval(counter, V).
Your implementation might provide something similar. In SWI-prolog, it seems that the same can be achieved with nb_setval (non-backtrackable setval).
A declarative way to solve this is to see this as a relation between two counter values: One before the increment, and one after the increment.
You can use CLP(FD) constraints to relate the two counter values:
counter_next(C0, C) :- C0 + 1 #= C.
Such a predicate is completely pure and can be used in all directions.
A sequence of such relations describes repeatedly incrementing the counter, relating an initial value to its final state:
?- S0 = 0, counter_next(S0, S1), counter_next(S1, S).
S = 2,
S0 = 0,
S1 = 1
EDIT: Suppose you go the other way and manage to implement a 0-ary predicate increment/0, as you ask for, destructively incrementing a global resource. Then you will have severe declarative problems. For example, incrementing the counter must succeed, so we can expect to see:
?- increment.
true.
But this means that the original query is no longer equivalent to its own answer, because the query:
?- true.
true.
certainly does not increment the counter.
It also means you can no longer test and reason about your predicates in isolation, but have to think about the global resource all the time.
This in turn will make it much harder to understand and correct mistakes in your code.
Therefore, I strongly recommend you adopt a declarative way to think about this task, and make the relation between counter values before and after incrementing explicit. As an additional benefit, you can then also use these relations in the other direction, and ask for example: "Which initial counter values, if any, yield a given value when incremented?", or even more generally: "For which arguments does this relation even hold?"

CLP Prolog - Logic Programming

we have a list of list think an example ?- solve([[40,A,B],[30,B],[60,A,B,C]]),label([A,B,C]). will succeed with replacing B=30,A=10 and C=20.
The constraint with this example is A+B=40, A+B+C=60 and generally every variable are in between 0 and 100. Every list must begin with a constant and it includes at least one variable.
:- use_module(library(clpfd)).
sum([],0). % if the list is empty.
sum([X|XS],Z) :-
sum(XS,Z1),
X in 0..100,
Z #= X+Z1.
solveOne([Const|Var]) :-
sum(Var,Const).
solve([]). % if the list of list is also empty
solve([First|Others]) :-
solveOne(First),
solve(Others).
I am a bit skeptic the idea of base case,facts. Because every list must include at list one variable according to constraints, on the other hand we think about the "empty list" situation.?
First, the obvious problem: you define both a solve/2 and a solve/1 predicate (solve([],0)). The ",0" is probably unwanted.
Apart from that, if you have only a constant, like [X], then solveOne succeeds only if X is zero; otherwise, it fails according to sum([],0). So, in a sense, you indirectly check that you can have at least one variable if you assume your sum is always strictly positive.
In order to explicitely check that there is effectively at least one variable, then you can modify solveOne as follows:
solveOne([Const,V1|Vars]) :-
sum([V1|Vars], Const).
#coredump answer should put you on right track. If you are interested in writing lean code, consider this more succint definition (tested in SWI-Prolog)
solve(L) :- maplist(solveOne, L).
solveOne([C|Vs]) :- Vs ins 0..100, sum(Vs, #=, C).
?- solve([[40,A,B],[30,B],[60,A,B,C]]).
A = 10,
B = 30,
C = 20.

Resources