Prolog, testing labeling heuristics - prolog

I'm working on some experiments for comparing different labeling heuristics in Sicstus Prolog.
But I keep getting into 'Resource error: insufficient memory'.
I'm pretty sure I'm doing something wrong in my testcode.
The following code will replicate my problem:
:- use_module(library(clpfd)).
:- use_module(library(lists)).
atest( R, C ):-
X is R * C,
length( M, X),
domain( M, 0, X),
all_distinct( M ),
statistics(walltime, [_,_SinceLast]),
labeling( [],M ),
statistics(walltime, [_,SinceLast]),
write('Labeling time: '), write(SinceLast),write('ms'),nl.
% Testcode for looping through alot of variations and run one test for each variant
t1:-
Cm = 1000,
Cr = 1000,
(
for(C,0, Cm),
param([Cm,Cr])
do
(
for(R, 0, Cr ),
param([C])
do
atest( C, R )
)
).
A short time after I call the t1 predicate, I get a 'Resource error: insufficient memory' exception.
I guess I should do something after I call atest to release resources?
Also: Is this the correct way to measure labeling-time? Any better way to do this?

You are not doing anything strictly wrong, but you are trying to run
length(Xs,N), domain(Xs,0,N), all_distinct(Xs), labeling([],Xs).
for N up to 1000000. The system constructs a search tree with depth N, and has to store intermediate states of the variables and the constraint system for each level. This takes a lot of memory for large N, and it is quite possible that you get a memory overflow already for a single run with large N.
The second issue is that you are running your benchmarks in a recursive loop, i.e. you are effectively creating a conjunction
atest(0,0), ..., atest(1000,1000)
and since each call to atest/2 succeeds with its first solution and keeps its search state around, this means you are trying to create a search tree with 250500250000 levels...
The simplest improvement is to cut each search after the first solution by changing your code to once(atest(C,R)). A further improvement is to run the benchmarks in a failure-driven loop
(
between(0,Cm,C),
between(0,Cr,R),
once(atest(C,R)),
fail
;
true
)
which will free memory sooner and faster, and reduce distortion of your measurements due to garbage collection.

Toplevel hides alternate answers
If you are testing t1 on SICStus' toplevel shell with some smaller values you might get the wrong impression that t1 has exactly one answer/solution. However, this is not the case! So the toplevel hides from you the other answers. This is a special behavior in the SICStus toplevel which does not show further answers if the query does not contain variables. But there is a total of x! many solutions for your labeling, x! for each test case and the timing for the other solutions is some random value. You are out of memory because for each test case, Prolog keeps a record to continue producing the next solution for each test case.
Looping
I do not recommend using a failure driven loop for testing, instead, use the following loop which is very similar but much safer:
\+ (
between(0, Cm, C),
between(0, Cr, R),
\+ atest(C, R)
).
The big difference to a failure driven loop is when atest/2 accidentally fails for some C and R. In a failure driven loop this will go essentially unnoticed, whereas above construct will fail.
Some systems provide a predicate forall/2 for this purpose.
Timing
If you do timing, better only use the first element of the list and compute the difference:
statistics(walltime, [T0|_]),
Goal,
statistics(walltime, [T1|_]),
D is T1 - T0.
In this manner alternate answers to Goal will give you a more meaningful value.

Related

Branch and bound without assert / retract

This exercise asked me to find the best combination of three products, given the prices and specific combinations to avoid. The textbook employs assertz and retractall to emulate a state variable.
price(a1, 1900).
price(a2, 750).
price(a3, 900).
price(b1, 300).
price(b2, 500).
price(b3, 450).
price(b4, 600).
price(c1, 700).
price(c2, 850).
incompatible(a2, c1).
incompatible(b2, c2).
incompatible(b3, c2).
incompatible(a2, b4).
incompatible(a1, b3).
incompatible(a3, b3).
:- dynamic bound/1.
bound(5000).
solution(A, B, C, P) :-
member(A, [a1, a2, a3]),
price(A, PA),
member(B, [b1, b2, b3, b4]),
\+ incompatible(A, B),
price(B, PB),
P0 is PA + PB,
bound(Bound),
write('Current bound: '), writeln(Bound),
P0 =< Bound,
member(C, [c1, c2]),
\+ incompatible(A, C),
\+ incompatible(B, C),
price(C, PC),
P is PA + PB + PC,
P =< Bound,
retractall(bound(_)),
assertz(bound(P)).
Is it possible to use branch and bound in Prolog without resorting to dynamic predicates?
Is there a consensus on state variables in Prolog?
Is there a way to restrict the scope of a state variable (or whatever the proxy would be) to a single rule?
The biggest problem with this code is that it is not re-entrant. It implicitly assumes that at any point in time there is exactly one instance of searching. But if some part inside wants to use a similar search all by themselves, no warning no error prevents this from happening.
There is not much consensus on how the precise mechanism should look like, existing systems all differ. To understand this, look at the implementation of findall/3 or call_nth/2 where there are specific solutions for SICStus, SWI, and Eclipse. Precisely this mechanism would be needed here too.
But also consider to make this search more generic. Presumably the textbook you are referring to was written prior to the general acceptance of call/N.
Is it possible to use branch and bound in Prolog without resorting to dynamic predicates?
Yes, you just hand the bounds around as additional arguments across recursive calls (as is done in functional programming). IMHO, this is actually a cleaner solutions than asserting into the Prolog database. The trick of changing the database and then performing a redo is confusing, as it's not the same program that is being redone. It's a "neat trick" to put into a textbook though.
Is there a consensus on state variables in Prolog?
Just hand them around as arguments. If need be, you can use Global Variables if supported. See also: Database in SWI-Prolog. To keep argument lists small-ish, you may want to consider using associative arrays (SWI-Prolog dicts, library(assoc)) as "argument bundle". But as usual, this has implications on efficiency.
Is there a way to restrict the scope of a state variable (or whatever the proxy would be) to a single rule?
Evidently, arguments are local, but there is, sadly, nothing beyond. I would like to have "local visibility scopes", especially for predicates so as to unequivocally associate "helper predicates" to their "parent predicate" but "modules" (implemented variously) is the best we have. (This is not made better by a tradition which finds module sizes of enormous size acceptable, something for which I would berate the intern in no uncertain terms, same as writing an object of several thousand lines, but I digress)
Your solution is not always using the proper Bound upon backtracking. The problem is that the variable gets bound too soon and then even if the fact gets updated with assertz/retract the variable will still be bound to the previous value. You can see the effects by letting the toplevel backtrack through all the solutions. There are some solutions intersped that have higher cost than a previous one.
Here goes an iterative solution customized to your problem, though you could probably make it more general by using call/N instead of the fixed calls to price/2 and any_incompatible/2
solution2(Bound, Best):-
branch_and_bound([[a1,a2,a3],[b1,b2,b3,b4],[c1,c2]], Bound, [], Best).
branch_and_bound([[]|_], _, Best, Best).
branch_and_bound([[Item|Layer]|Layers], Bound, CurrentBest, Best):-
price(Item, ItemPrice),
( ItemPrice >= Bound
-> Bound1-CurrentBest1=Bound-CurrentBest
; branch_and_bound(Layers, Bound, Bound1, current(ItemPrice, [Item]), CurrentBest, CurrentBest1)
),
branch_and_bound([Layer|Layers], Bound1, CurrentBest1, Best).
branch_and_bound([], Bound, CurrentPrice, current(CurrentPrice, Items), PreviousBest, [best(CurrentPrice, RItems)|OtherBest]):-
reverse(Items, RItems),
( CurrentPrice==Bound -> OtherBest=PreviousBest ; OtherBest=[] ).
branch_and_bound([[]|_], Bound, Bound, _, Best, Best).
branch_and_bound([[Item|Layer]|Layers], Bound, Bound2, current(CurrentPrice, Items), CurrentBest, Best):-
price(Item, ItemPrice),
NewPrice is CurrentPrice + ItemPrice,
(
( NewPrice > Bound ; any_incompatible(Items, Item) )
-> Bound1-CurrentBest1=Bound-CurrentBest
; branch_and_bound(Layers, Bound, Bound1, current(NewPrice, [Item|Items]), CurrentBest, CurrentBest1)
),
branch_and_bound([Layer|Layers], Bound1, Bound2, current(CurrentPrice, Items), CurrentBest1, Best).
any_incompatible([OneItem|Items], Item):-
incompatible(OneItem, Item) -> true ; any_incompatible(Items, Item).
It will list all the best solutions, trimming the search space with the current Bound defined by the currently found best solution.
Sample run:
?- solution2(5000, Best).
Best = [best(1900, [a3, b1, c1]), best(1900, [a2, b1, c2])].

Stack limit exceeded prolog with append

I get an error
Stack limit exceeded
in Prolog using append
I am writing a Spanish grammar and need to use append to separate clauses (to separate subject and predicate, get verbs, etc...).
Here I write a simplified use of append that I do not understand why is overflow. I get the answers that I want, but then loops to infinity and beyond!
complejidad(1,0).
complejidad(2,0).
complejidad(2,1).
lista(['A'], 0).
lista(['B'], 0).
lista(Frase, J) :-
lista(Prefijo, 0),
lista(Sufijo, Js),
append(Prefijo, Sufijo, Frase),
complejidad(J, Js).
If I query:
lista(X,_)
I get:
Y put the comlejidad statement to limit the recursion a 2 steps. But something happens with append.
Here is the live example: https://swish.swi-prolog.org/p/stack-limit-exceeded-with-append.pl
And here is my grammar: https://swish.swi-prolog.org/p/mini-gramatica-castellana.v2.pl
I show my grammar to illustrate why I need append!
As you see the error message shows the totally allocated stack 0.2G, which is smaller than in the standalone version, where one gets 1.0G by default. This is to assure that more pengines can run simultaneously on the SWISH server.
The SWI-Prolog stack needs a window for parameter passing. The error message does not show the window size. This is a hard coded parameter, SWI-Prolog needs to be recompiled. Maybe for SWISH the window size should be also reduced.
The stackover flow happens because Js=2 has no solution in complejidad(J, Js). So its backtracking again and again, producing larger and larger intermediate derivations without showing an answer. Until it gets into a stack overflow.
This is not a problem of append/3, rather of lista/2 and depth first search. Try using a Prolog debugger to see what happens.
To limit depth of recursion programatically I add a number parameter:
lista(['A'], N) :- N>=0.
lista(['B'], N) :- N>=0.
lista(Frase, N) :-
N > 0,
N_1 is N-1,
lista(Prefijo, N_1),
lista(Sufijo, N_1),
append(Prefijo, Sufijo, Frase).
In the atomic clauses y put N with N>=0 (that is because I want than the depth was a limit not an exact number; previously I try with N equal to 0).
In the recursive clause y add N>0 and define a N_1 variable to N-1

Finding whether a number is a multiple of another

Looking at the code below:
multiple(X,0).
multiple(X,Y) :- lt(0,X), lt(0,Y), diff(Y,X,D), multiple(X,D).
There happens to be something wrong. For your reference:
lt/2 is whether the first argument is less than the second.
diff/3 is whether the third argument is equal to the first argument minus the second.
lt/2 and diff/3 are defined correctly.
Is there a logical mistake in the definition? Is assuming that 0 is the multiple of every number problematic or is the logical mistake somewhere else? I get correct answers but the query goes to infinite loop I think.
EDIT:
here are the other definitions.
natNum(0).
natNum(s(X)) :- natNum(X).
lt(0,s(X)) :- natNum(X).
lt(s(X),s(Y)) :- lt(X,Y).
sum(0,X,X).
sum(s(X),Y,s(Z)) :- sum(X,Y,Z).
diff(X,Y,Z) :- sum(Z,Y,X).
?- multiple(X, s(s(s(s(s(s(0))))))).
where s(0) is 1, s(s(0)) is 2 etc. It gives all the desired answers for X but after the last answer, it gets stuck. I assume in an infinite recursive loop?
What is happening in your program? Does it loop forever, or does it only take some time since you haven't updated your hardware in recent decades? We cannot tell. (Actually, we could tell by looking at your program, but that is much too complex for the moment).
What we can do with ease is narrow down the source of this costly effort. And this, without a deep understanding of your program. Let's start with the query:
?- multiple(X, s(s(s(s(s(s(0))))))).
X = s(0)
; X = s(s(0))
; X = s(s(s(0)))
; X = s(s(s(s(s(s(0))))))
; loops. % or takes too long
Isn't there an easier way to do this? All this semicolon typing. Instead, simply add false to your query. In this manner the solutions found are no longer shown and we can concentrate on this annoying looping. And, if we're at it, you can also add false goals into your program! By such goals the number of inferences might be reduced (or stays the same). And if the resulting fragment (called a failure-slice) is looping, then this is a reason why your original program loops:
multiple(_X,0) :- false.
multiple(X,Y) :- lt(0,X), false, lt(0,Y), diff(Y,X,D), multiple(X,D).
natNum(0) :- false.
natNum(s(X)) :- natNum(X), false.
lt(0,s(X)) :- natNum(X), false.
lt(s(X),s(Y)) :- false, lt(X,Y).
?- multiple(X, s(s(s(s(s(s(0))))))), false.
loops.
Do your recognize your program? Only those parts remained that are needed for a loop. And, actually in this case, we have an infinite loop.
To fix this, we need to modify something in the remaining, visible part. I'd go for lt/2 whose first clause can be generalized to lt(0, s(_)).
But wait! Why is it OK to generalize away the requirement that we have a natural number? Look at the fact multiple(X,0). which you have written. You have not demanded that X is a natural number either. This kind of over-generalizations often appears in Prolog programs. They improve termination properties at a relatively low price: Sometimes they are too general but all terms that additionally fit into the generalization are not natural numbers. They are terms like any or [a,b,c], so if they appear somewhere you know that they do not belong to the solutions.
So the idea was to put false goals into your program such that the resulting program (failure-slice) still loops. In the worst case you put false at a wrong place and the program terminates. By trial-and-error you get a minimal failure-slice. All those things that are now stroked through are irrelevant! In particular diff/3. So no need to understand it (for the moment). It suffices to look at the remaining program.

Prolog manual or custom labeling

I am currently writing a solver for a floor planning problem in Prolog and have some issues with the labeling part.
The current problem is my constraints are posted but when I launch the labeling, it takes forever to find a solution. I would like to bring in some heuristics.
My question is, how do I manually label my variables ? I am afraid that after defining a clpfd variable like this :
X in Xinf..Xsup
and constraining it, If I do something like :
fd_sup(X, Xmax),
X = Xmax,
...
in my custom label, I won't be using the backtrack ability of Prolog to test the other values of X's domain. Am I wrong ?
Also, is there a smarter way to label my variables than writing custom labeling procedures ? My idea of heuristics would consist in trying extrema of a variable domain alternatively (like max(X), min(X), max(X-1), min(X-1) etc...)
Hope you can help me :)
It is not difficult to write a custom labeling procedure, and with most real problems you will eventually need one anyway in order to incorporate problem-specific heuristics.
The two main components of a labeling procedure are
variable selection: from all the remaining (i.e. not yet instantiated) problem variables, pick one to consider next.
value selection or branching: explore, via backtracking, two or more alternative sub-problems by reducing the chosen variable's domain in (usually) complementary ways.
Using this scheme, the default labeling procedure can be written as
label(Xs) :-
( select_variable(X, Xs, Xs1) ->
branch(X),
label(Xs1)
;
true % done, no variables left
).
select_variable(X, [X|Xs], Xs). % 'leftmost' strategy
branch(X) :- indomain(X).
You can now redefine select_variable/3 to implement techniques such as "first-fail", and redefine branch/1 to try domain values in different orders. As long as you make sure that branch/1 enumerates all of X's domain values on backtracking, your search remains complete.
Sometimes you want to try just one domain value first (say, one suggested by a heuristics), but, if it is no good, not commit to another value immediately.
Let's say that, as in your example, you want to try the maximum domain value first. You could write this as
branch(X) :-
fd_sup(X, Xmax),
(
X = Xmax % try the maximum
;
X #\= Xmax % otherwise exclude the maximum
).
Because the two cases are complementary and cover all possible values for X, your search is still complete. However, because of the second alternative, branch/1 can now succeed with an uninstantiated X, which means you must make sure in the labeling procedure that you don't lose this variable from your list. One possibility would be:
label(Xs) :-
( select_variable(X, Xs, Xs1) ->
branch(X),
( var(X) -> append(Xs1, [X], Xs2) ; Xs2=Xs1 ),
label(Xs2)
;
true % done, no variables left
).
First, always try built-in heuristics. ff is often a good strategy.
For custom labeling strategies, it is often easiest to first convert the domain to a list, then reorder the list, and then simply use member/2 to assign the values of the domain using the new order.
A good building black is dom_integers/2, relating a finite CLP(FD) domain to a list of integers:
:- use_module(library(clpfd)).
dom_integers(D, Is) :- phrase(dom_integers_(D), Is).
dom_integers_(I) --> { integer(I) }, [I].
dom_integers_(L..U) --> { numlist(L, U, Is) }, Is.
dom_integers_(D1\/D2) --> dom_integers_(D1), dom_integers_(D2).
Your specific strategy is easily expressed on a list of such ordered integers, relating these integers to a second list where the values occur in the order you describe:
outside_in([]) --> [].
outside_in([I]) --> [I].
outside_in([First|Rest0]) --> [First,Last],
{ append(Rest, [Last], Rest0) },
outside_in(Rest).
Sample query and result:
?- phrase(outside_in([1,2,3,4]), Is).
Is = [1, 4, 2, 3] ;
false.
Combining this with fd_dom/2 and dom_integers/2, we get (bindings for variables other than X omitted):
?- X in 10..20,
fd_dom(X, Dom),
dom_integers(Dom, Is0),
phrase(outside_in(Is0), Is),
member(X, Is).
X = 10 ;
X = 20 ;
X = 11 ;
X = 19 ;
X = 12 ;
X = 18 ;
etc.
Nondeterminism is preserved by member/2.
Make sure to distinguish labeling strategies from additional propagation. These two aspects are currently a bit mixed in your question.
In SWI-Prolog, there is a predicate called clpfd:contracting/1. It does what you describe: It tries values from the domain boundaries, and removes values that can be seen as inconsistent, i.e., for which it is known that no solution exists.
Therefore, if you have a list of variables Vs, you can try: clpfd:contracting(Vs), and see if this helps.
Note that this can also significantly slow down the search, though on the other hand, also help significantly to reduce the search space before even trying any labeling!
To complement the other answers (one contrasting labeling and propagation, one showing a dedicated labeling method), I now tackle a further very important aspect of this question:
Very often, when beginners complain about the speed of their code, it turns out that their code in fact doesn't even terminate! More efficiency would not help in that case.
Hence, this answer points you towards first ensuring actual termination of your relation.
The best way to ensure termination of CLP(FD) programs is to separate them into 2 parts:
the first, called the core relation, simply posts all constraints.
the second uses labeling/2 to perform the actual search.
Have you done this in your program? If not, please do. When this is done, make sure that the core relation, say solution/2 (where the arguments are: a term denoting the task instance, and the list of variables to be labeled) terminates universally by querying:
?- solution(Instance, Vs), false.
If this terminates, then the following also terminates:
?- solution(Instance, Vs), label(Vs), false.
Of course, in larger tasks, you have no chance to actually witness the termination of the latter query, but a good chance to witness the termination of the first query, because setting up the constraints is often much faster than actually obtaining even a a single solution.
Therefore, test whether your core relation terminates!
This follows up on this previous answer by #mat.
If you have got some more CPU cycles to burn, try shave_zs/1 as defined in this previous answer.
shave_zs/1 kind of works like the auxiliary library predicate clpfd:contracting/1. Unlike contracting/1, however, all values are "up for grabs"—not just the ones at the boundary. YMMV!

Make a predicate reversible

I'm new to prolog; I'm coming from a structured programming background, as will become obvious :)
I am building up a prolog query that involves reversing a number; eg. reverse_num(123,X) results in X = 321. I came up with the following definition, but it only works when I provide a number as the first parameter.
reverse_num(Num, Revnum) :-
number_chars(Num, Atoms),
reverse(Revatoms, Atoms),
number_chars(Reversed, Revatoms),
Reversed = Revnum.
the number_chars/2 predicate doesn't like an unsubstantiated variable if I do: reverse_num(X,123) (where I'm expecting X to be 321).
Am I trying too hard to make reverse_num do something it shouldn't (should it be understood to work only with a number as the first parameter and variable as the second)?
Or is there an easy / straight-forward way to handle a variable as the first parameter?
Relational naming
Before jumping into coding, let's take a step back. After all, the idea in Prolog is to define relations. Your name reverse_num/2 rather suggests some actions, num_reversed/2 might be a better name.
Determine the relation
Your definition is not that bad, let me rewrite it to1:
num_reversed(Num, Reversed) :-
number_chars(Num, Chars),
reverse(Chars, Revchars),
number_chars(Reversed, Revchars).
?- num_reversed(123,X).
X = 321.
?- num_reversed(1230,X).
X = 321.
?- num_reversed(12300,X).
X = 321.
Do you see the pattern? All numbers N*10^I have the same result!
Now, let's ask some more:
?- num_reversed(Num, 321).
error(instantiation_error,number_chars/2).
Hm, what did we expect? Actually, we wanted all 123*10^I to be printed. That's infinitely many solutions. So above query, if correctly answered, would require infinitely many solutions to be printed. If we print them directly, that will take all our universe's lifetime, and more!
It is for this reason, that Prolog produces an instantiation error instead. By this, Prolog essentially states:
This goal is too general that I can make a good answer. Maybe there are infinitely many solutions, maybe not. I know not. But at least I indicate this by issuing an error. To remove this error you need to instantiate the arguments a bit more.
So the answer Prolog produced was not that bad at all! In fact, it is much better to produce a clean error than to, say, fail incorrectly. In general, Prolog's errors are often a very useful hint to what semantic problems you might have. See all error classes how.
Coroutining
As have other answers suggested, coroutining, using when/2 might solve this problem. However, coroutining itself has many semantic problems. Not without reason, systems like XSB do not offer it, due to the many problems related to subsumption checking. An implementation that would be compatible to it would be unexpectedly inefficient.
But for the sake of the point, we could make our definition more versatile by querying it like
?- when(nonvar(Num), num_reversed(Num, Reversed)).
when(nonvar(Num), num_reversed(Num, Reversed)).
Now we get back as an answer exactly the query we entered. This is also known as floundering. So there is a way to represent infinitely may solutions in a compact manner! However, this comes at a rather high price: You no longer know whether a solution exists or not. Think of:
?- when(nonvar(Num), num_reversed(Num, -1)).
when(nonvar(Num), num_reversed(Num, -1)).
Others have suggested to wait also for nonvar(Reversed) which would only be correct if we would produce infinitely many answers - but, as we have seen - this just takes too much time.
Coroutining looked as a very promising road at the beginning of the 1980s. However, it has never really caught on as a general programming methodology. Most of the time you get much too much floundering which is just a pain and even more difficult to handle than, say instantiation errors.
However, a more promising offspring of this development are constraints. There, the mechanisms are much cleaner defined. For practical purposes, programmers will only use existing libraries, like CLPFD, CLPQ, or CHR. Implementing your own library is an extremely non-trivial project in its own right. In fact it might even be possible to provide an implementation of num_reversed/2 using library(clpfd) that is, restricting the relation to the integer case.
Mode dependent conditionals
Traditionally, many such problems are solved by testing for instantiations explicitly. It is good style to perform this exclusively with nonvar/1 and ground/1 like the condition in when/2- other type test predicates lead easily to errors as exemplified by another answer.
num_reversed(Num, Reversed) :-
( nonvar(Num)
-> original_num_reversed(Num, Reversed)
; original_num_reversed(Reversed, Base),
( Base =:= 0
-> Num is 0
; length(_, I),
Num is Base*10^I
)
).
Above code breaks very soon for floats using base 2 and somewhat later for base 10. In fact, with classical base 2 floats, the relation itself does not make much sense.
As for the definition of number_chars/2, ISO/IEC 13211-1:1995 has the following template and mode subclause:
8.16.7.2 Template and modes
number_chars(+number, ?character_list)
number_chars(-number, +character_list)
The first case is when the first argument is instantiated (thus nonvar). The second case, when the first argument is not instantiated. In that case, the second argument has to be instantiated.
Note, however, that due to very similar problems, number_chars/2 is not a relation. As example, Chs = ['0','0'], number_chars(0, Chs) succeeds, whereas number_chars(0, Chs), Chs = ['0','0'] fails.
Very fine print
1 This rewrite is necessary, because in many Prologs reverse/2 only terminates if the first argument is known. And in SWI this rewrite is necessary due to some idiosyncratic inefficiencies.
The number_chars/2 predicate has the signature:
number_chars(?Number, ?CharList)
But although not fully specified by the signature, at least Number or CharList have to be instantiated. That's where the error occurs from.
If you call:
reverse_num(Num,123)
You will call number_chars/2 with both uninstatiated at that time so the predicate will error.
A not very nice solution to the problem is to ask whether Num or RevNum are number/2s. You can do this by writing two versions. It will furthermore filter other calls like reverse_num(f(a),b), etc.:
reverse_num(Num,Revnum) :-
\+ number(Num),
\+ number(Revnum),
throw(error(instantiation_error, _)).
reverse_num(Num, Revnum) :-
ground(Num),
number(Num),
!,
number_chars(Num, Atoms),
reverse(Revatoms, Atoms),
number_chars(Revnum, Revatoms).
reverse_num(Num, Revnum) :-
ground(Revnum),
number(Revnum),
reverse_num(Revnum,Num).
Or you can in case you use two nongrounds (e.g. reverse_num(X,Y).) an instantiation error instead of false as #false says:
reverse_num(Num,Revnum) :-
\+ number(Num),
\+ number(Revnum),
!,
throw(error(instantiation_error, _)).
reverse_num(Num, Revnum) :-
number(Num),
!,
number_chars(Num, Atoms),
reverse(Revatoms, Atoms),
number_chars(Revnum, Revatoms).
reverse_num(Num, Revnum) :-
reverse_num(Revnum,Num).
The cut (!) is not behaviorally necessary, but will increase performance a bit. I'm not really a fan of this implementation, but Prolog cannot always fully make predicates reversible since (a) reversibility is an undecidable property because Prolog is Turing complete; and (b) one of the characteristics of Prolog is that the body atoms are evaluated left-to-right. otherwise it will take ages to evaluate some programs. There are logic engines that can do this in an arbitrary order and thus will succeed for this task.
If the predicate/2 is commutative, a solution that can be generalized is the following pattern:
predicate(X,Y) :-
predicate1(X,A),
predicate2(A,B),
% ...
predicaten(C,Y).
predicate(X,Y) :-
predicate(Y,X).
But you cannot simply add the last clause to the theory, because it can loop infinitely.
Nice to see someone is also worried about define flexible rules with no restrictions in the set of bound arguments.
If using a Prolog system that supports coroutining and the when/2 built-in predicate (e.g. SICStus Prolog, SWI-Prolog, or YAP), try as:
reverse_num(Num, Reversed) :-
when( ( ground(Num); ground(Atoms) ), number_chars(Num, Atoms) ),
when( ( ground(Reversed); ground(Revatoms) ), number_chars(Reversed, Revatoms) ),
reverse(Atoms , Revatoms).
that gives:
?- reverse_num( 123, X ).
X = 321.
?- reverse_num( X, 123 ).
X = 321 .
( thanks to persons who provided theses answers: Prolog: missing feature? )
This SWISH session shows my effort to answer.
Then I've come back here, where I found I was on #PasabaPorAqui' mood (+1), but I didn't get it right.
But, such an interesting topic: notice how regular is the join pattern.
reverse_num(X, Y) :-
when((nonvar(Xs);nonvar(Ys)), reverse(Xs, Ys)),
when((nonvar(X) ;nonvar(Xs)), atomic_chars(X, Xs)),
when((nonvar(Y) ;nonvar(Ys)), atomic_chars(Y, Ys)).
So, we can generalize in a simple way (after accounting for PasabaPorAqui correction, ground/1 it's the key):
% generalized... thanks Pasaba Por Aqui
:- meta_predicate when_2(0).
when_2(P) :-
strip_module(P,_,Q),
Q =.. [_,A0,A1],
when((ground(A0);ground(A1)), P).
reverse_num(X, Y) :-
maplist(when_2, [reverse(Xs, Ys), atomic_chars(X, Xs), atomic_chars(Y, Ys)]).
I think I understand why nonvar/1 was problematic: the list bound for reverse get 'fired' too early, when just the head get bound... too fast !
maplist/2 is not really necessary: by hand we can write
reverse_num(X, Y) :-
when_2(reverse(Xs, Ys)),
when_2(atomic_chars(X, Xs)),
when_2(atomic_chars(Y, Ys)).
this seems an ideal application of term rewriting... what do you think about -:- ? Implementing that we could write bidirectional code like
reverse_num(X, Y) -:-
reverse(Xs, Ys),
atomic_chars(X, Xs),
atomic_chars(Y, Ys).
edit SWISH maybe is not 'term_rewrite' friendly... so here is a lower level approach:
:- op(900, xfy, ++).
A ++ B ++ C :- when_2(A), B ++ C.
A ++ B :- when_2(A), when_2(B).
reverse_num(X, Y) :-
reverse(Xs, Ys) ++ atomic_chars(X, Xs) ++ atomic_chars(Y, Ys).
Setting aside the problem of trailing zeroes turning into leading zeroes, it doesn't seem like it should be much more complicated than something like this (made somewhat more complicated by dealing with negative numbers):
reverse_number(X,Y) :- number(X) , ! , rev(X,Y) .
reverse_number(X,Y) :- number(Y) , ! , rev(Y,X) .
rev(N,R) :-
N < 0 ,
! ,
A is abs(N) ,
rev(A,T) ,
R is - T
.
rev(N,R) :-
number_chars(N,Ns) ,
reverse(Ns,Rs) ,
number_chars(R,Rs)
.
Note that this does require at least one of the arguments to reverse_number/2 to be instantiated.

Resources