Prolog+clpfd: simple binary number parser with value - prolog

I'm currently trying to understand DCGs in prolog.
Consider this example.
digit(0) --> "0".
digit(1) --> "1".
binaryNumber(Val) --> digit(Val).
binaryNumber(Next*2 + Cur) -->
%CurVal #= Cur + Next*2,
binaryNumber(Next),
digit(Cur).
That produces:
207 ?- binaryNumber(X, Y, []).
X = 0,
Y = [48] ;
X = 1,
Y = [49] ;
X = 0*2+0,
Y = [48, 48] ;
X = 0*2+1,
Y = [48, 49] ;
X = 1*2+0,
Y = [49, 48] ;
X = 1*2+1,
Y = [49, 49] ;
X = (0*2+0)*2+0,
Which is nice.
However, if I want to "convert" string to value:
:- use_module(library(clpfd)).
digit(0) --> "0".
digit(1) --> "1".
binaryNumber(Val) --> digit(Val).
binaryNumber(CurVal) -->
CurVal #= Cur + Next*2,
binaryNumber(Next),
digit(Cur).
I get:
209 ?- binaryNumber(X, Y, []).
X = 0,
Y = [48] ;
X = 1,
Y = [49] ;
ERROR: binaryNumber/3: Undefined procedure: (#=)/4
ERROR: However, there are definitions for:
ERROR: (#=)/2
Exception: (7) #=(_G4807345, _G4807428+_G4807431*2, _G4807346, _G4807475) ?
...
Two questions:
Why does binaryNumber want #= to have "arity" of 4?
How do I fix this?

You're very close!
Commonly, a dcg foo//n isn't implemented "directly", but by translating a grammar foo//n to a corresponding Prolog predicate foo//(n+2). This translation is done by term_expansion/2, a mechanism analogous to macros in other languages. Usually, you don't have to mind it at all.
For more on dcg read: (1) this DCG primer, and (2) the question
"Is there a way or an algorithm to convert DCG into normal definite clauses in Prolog?" and the answers to that question.
Coming back to the subject, I see two issues in your dcg use:
If used within grammar rules, "ordinary" Prolog goals must be encapsulated with curly braces {}/1,
so they are skipped in aforementioned "grammar to predicate" translation step. In your code, you don't want to use (#=)//2 (a.k.a. (#=)/4), you want (#=)/2!
It is good practise, not to use foo/(n+2) goals directly.
Use phrase/2 or phrase/3 for that!
So let's edit the corresponding code snippet:
binaryNumber(Next*10 + Cur) -->
{ CurVal #= Cur + Next*2 },
binaryNumber(Next),
digit(Cur).
Now let's query!
?- phrase(binaryNumber(X),Ts).
X = 0, Ts = [48] ;
X = 1, Ts = [49] ;
X = 0, Ts = [48,48] ;
X = 1, Ts = [48,49] ;
X = 2, Ts = [49,48] ;
X = 3, Ts = [49,49] ...

Related

How do I fix this triangular sequence (recursion) in prolog Arguments are not sufficiently instantiated?

Trying to calculate the triangular number sequence in Prolog.
This is my solution:
where X is the nth position of the sequence and Y is the result.
triang(1, 1).
triang(X, Y) :-
X>0,
A is X - 1,
triang(A, B),
Y is B + X.
?- triang(5,X).
X = 15
But when i try to do for example triang(X,10) I receive an error
Arguments are not sufficiently instantiated.
I guess this is because X is not defined in the consult.
is there any recommendation how to solve this problem,thank you.
First of all, the result you got is not that bad. It says: sorry, I am unable to come to a conclusion and before producing an incorrect result, I prefer to produce an error.
The actual reason is the following goal
?- X > 0.
error(instantiation_error,(is)/2).
So here we ask for X that are greater than zero. And there are many, in fact infinitely many. There is no direct way to enumerate that set for this built-in and thus it prefers the error.
However, with library(clpz) or clpfd, there is a better way:
:- use_module(library(clpz)). % use clpfd for SWI instead
:- op(150, fx, #).
triang(0, 0).
triang(X, Y) :-
#X #>0,
#Y #>0,
#A #= #X - 1,
#Y #= #B + #X,
triang(A, B).
?- triang(X,15).
X = 5
; false.
?- triang(X,14).
false.
?- triang(X,X).
X = 0
; X = 1
; false.
?- triang(X,Y).
X = 0, Y = 0
; X = 1, Y = 1
; X = 2, Y = 3
; X = 3, Y = 6
; X = 4, Y = 10
; X = 5, Y = 15
; X = 6, Y = 21
; ... .
?- #X #> 0.
clpz:(X in 1..sup).
So now there is an answer to #X #> 0. The answer is often called a constraint. In this case it tells us that X must be in the interval 1 up to (kind of) infinity.

Prolog result not multiplying

I have the following prolog program:
square([H|T], X) :-
squareCompare(T, H, X).
squareCompare([], X, X * X ).
squareCompare([H|T], V, Result) :-
(V * V) < (H * H),
squareCompare(T, V, Result);
(V * V) > (H * H),
squareCompare(T, H, Result).
When I enter:
square([7, 5, 2], Result).
I get Result = 2 * 2, what I want is Result = 4.
This program searches for the smallest square of the element in the list.
Besides the lack of arithmetic evaluation (is/2) as pointed out in the comments there's also an issue with using </2 and >/2: your predicate doesn't work for list with consecutive repetitions, e.g.:
?- square([7,7],X).
false.
where the expected result would be 49. You can remedy that by replacing </2 by =</2 or >/2 by >=/2 in your recursive rule of squareCompare/3:
squareCompare([], X, Y) :-
Y is X*X.
squareCompare([H|T], V, Result) :-
(V * V) < (H * H),
squareCompare(T, V, Result);
(V * V) >= (H * H),
squareCompare(T, H, Result).
Now the predicate yields the desired result:
?- square([7,7],X).
X = 49.
Following another suggestion in the comments, you could opt to use CLP(FD) to make the predicate work both ways. In that case the predicate resembles a true relation so it'd be appropriate to give it a more descriptive name that reflects this fact, say list_minsquare/2. And since you are interested in the smallest square, why not pass around the squares as arguments rather than the numbers? Worst case: the root of the smallest square is the last list element, then there's no difference. Best case: the root of the smallest square is the first list element, then you only calculate it once instead of length-of-list times. Putting all this together:
:- use_module(library(clpfd)).
list_minsquare([H|T],X) :-
S #= H*H,
list_square_minsquare(T,S,X).
list_square_minsquare([],S,S).
list_square_minsquare([H|T],S,Result) :-
S #< (H*H),
list_square_minsquare(T,S,Result).
list_square_minsquare([H|T],S,Result) :-
H2 #= (H*H),
S #>= H2,
list_square_minsquare(T,H2,Result).
Now let's see some action. Your example query yields the desired result:
?- list_minsquare([7,4,2],X).
X = 4.
Consecutive repetitions also don't cause troubles:
?- list_minsquare([7,7],X).
X = 49.
Partially instantiated lists lead to all possible solutions being produced:
?- list_minsquare([7,Y,2],X).
X = 4, % <- 1st answer: X=4 if
Y^2#=_G670,
_G670 in 50..sup ; % Y^2 is between 50 and sup
Y in -1..1, % <- 2nd answer: if Y in -1..1
Y^2#=X, % then X=Y^2
X in 0..1 ;
X = 4, % <- 3rd answer: X=4
Y in -7.. -1\/1..7, % if Y in -7..-1 or 1..7
Y^2#=_G1754,
_G1754 in 4..49. % and Y^2 in 4..49
In the above example there are three possibilities for Y none of which has a unique solution, hence you get residual goals in the answers. If you wish to get concrete solutions you can constrain the range of Y and ask for concrete numbers with label/1:
?- Y in 0..3, list_minsquare([7,Y,2],X), label([Y]).
Y = X, X = 0 ;
Y = X, X = 1 ;
Y = 2,
X = 4 ;
Y = 3,
X = 4.
The most general query works as well. However, it is listing the solutions in an unfair manner:
?- list_minsquare(L,X).
L = [_G97], % <- 1st solution
_G97^2#=X,
X in 0..sup ;
L = [_G266, _G269], % <- 2nd solution
_G266^2#=X,
X in 0..sup,
X+1#=_G309,
_G309 in 1..sup,
_G332#>=_G309,
_G332 in 1..sup,
_G269^2#=_G332 ;
L = [_G494, _G497, _G500], % <- 3rd solution
_G494^2#=X,
X in 0..sup,
X+1#=_G540,
X+1#=_G552,
_G540 in 1..sup,
_G575#>=_G540,
_G575 in 1..sup,
_G500^2#=_G575,
_G552 in 1..sup,
_G620#>=_G552,
_G620 in 1..sup,
_G497^2#=_G620 ;
.
.
.
You only get one solution for every list length before moving on to the next length. You can get a fair ordering by prefixing a goal length/2 in the query. Then you'll get all possibilities for every list length before moving on:
?- length(L,_), list_minsquare(L,X).
L = [_G339], % <- 1st solution: list with one element
_G339^2#=X,
X in 0..sup ;
L = [_G1036, _G1039], % <- 2nd solution: list with two elements
_G1036^2#=X, % X is square of 1st element
X in 0..sup,
X+1#=_G1079,
_G1079 in 1..sup,
_G1102#>=_G1079,
_G1102 in 1..sup,
_G1039^2#=_G1102 ;
L = [_G935, _G938], % <- 3rd solution: list with two elements
_G935^2#=_G954,
_G954 in 0..sup,
_G954#>=X,
X in 0..sup,
_G938^2#=X ; % X is square of 2nd element
.
.
.
Of course you can also constrain and label the numbers in the list for the above query and you'll get concrete numbers in the still infinitely many solutions (since there are infinitely many list lengths).
?- length(L,_), L ins 1..2, list_minsquare(L,X), label(L).
L = [1],
X = 1 ;
L = [2],
X = 4 ;
L = [1, 2],
X = 1 ;
L = [1, 1],
X = 1 ;
L = [2, 1],
X = 1 ;
L = [2, 2],
X = 4 ;
L = [1, 2, 2],
X = 1 ;
L = [1, 2, 1],
X = 1 ;
L = [1, 1, 2],
X = 1 ;
L = [2, 1, 2],
X = 1 ;
.
.
.

Prolog - descending order list

I am trying to write a function - decListRange(X,List) which give a list in range [X-1:1] by descending order. For example -
decListRange(9,List).
Will give -
List = [8,7,6,5,4,3,2,1].
I tried the following but it goes into infinite loop -
decListRange(1,[]) :- !.
decListRange(X,[H|Rest]) :-
H = X-1, NextX = X - 1 ,decListRange(NextX,Rest).
You have two problems. The first real one is that you need to use is instead of =:
H is X-1
This is needed to trigger arithmetic evaluation. Your second problem isn't a real problem but speaks to a bigger misunderstanding, which is that H and NextX are equivalent. Because Prolog only has bindings and not "assignables" as it were, you should never really need to create two "variables" with the same binding. There's no state being kept around for you to modify later.
Cleaning up both you get this:
decListRange(1, []) :- !.
decListRange(X, [H|Rest]) :-
X > 1,
H is X-1,
decListRange(H, Rest).
Edit 2: a clpfd implementation
:- use_module(library(clpfd)).
declist(N, L) :- N == 1, !, L = []. % green cut
declist(1, []).
declist(N, [N1|Ns]) :-
N #> 1,
N1 #= N - 1,
declist(N1, Ns).
This one has the properties #false mentions below in the comments:
?- declist(3, L).
L = [2, 1] ;
false.
?- declist(3, [2,1]).
true ;
false.
?- declist(N, [3,2,1]).
N = 4.
?- declist(N, X).
N = 1,
X = [] ;
N = 2,
X = [1] ;
N = 3,
X = [2, 1] ;
N = 4,
X = [3, 2, 1] ;
N = 5,
X = [4, 3, 2, 1] .
Edit: a short interlude on the difference between = and is.
In procedural languages = is almost always syntax for assigning a particular value to a variable. In Prolog, variables are bindings, and once established they cannot be directly modified by reassigning the variable a different value. Instead they work more like variables in math and logic, where the variable "stands in" for interesting values, but those values are themselves basically immutable. In Prolog, = essentially asks the unification engine to establish bindings. So if you were to do something like this:
?- name(X, Y) = name(bob, tony).
Prolog responds with variable bindings:
X = bob,
Y = tony.
Once those bindings exist, contradictory bindings will fail and affirmative bindings will succeed:
?- name(X, Y) = name(bob, tony), X = bob.
X = bob,
Y = tony.
?- name(X, Y) = name(bob, tony), X = william.
false.
The unification algorithm itself doesn't know anything about arithmetic. This has the pleasant side-effect that you can use any expression raw. For instance:
?- Expr = X + 3, Z + Q = Expr.
Expr = Z+3,
X = Z,
Q = 3.
This is probably really surprising looking. You may expect that somehow Prolog was smart enough to keep the expression around because it noticed X was a variable or something, but that isn't true either:
?- X = 4, Expr = X + 3, Z + Q = Expr.
X = 4,
Expr = 4+3,
Z = 4,
Q = 3.
Another way of looking at this is that Prolog is considering + to be just another operator, so X+3 is a fact just like add(X, 3) that doesn't necessarily have any special meaning. Whichever way you look at it, the is/2 operator exists to apply arithmetic reasoning and produce a value:
?- X = 4, Expr is X + 3.
X = 4,
Expr = 7.
Notice that Expr has the computed value but none of the original structure:
?- X = 4, Expr is X + 3, Z + Q = Expr.
false.
In practice, if you need to do a lot of reasoning with arithmetic, you will want to use a library like clpfd or clpqr depending on whether you're interested in integers or reals. This library enables you to do more interesting things more easily, like specify that an equation holds for values in a certain range and get those values out.

Understanding prolog [lists]

I am to write a program that does this:
?- pLeap(2,5,X,Y).
X = 2,
Y = 3 ;
X = 3,
Y = 4 ;
X = 4,
Y = 5 ;
X = 5,
Y = 5 ;
false.
(gives all pairs X,X+1 between 2 and 5, plus the special case at the end).
This is supposedly the solution. I don't really understand how it works, could anyone guide me through it?
pLeap(X,X,X,X).
pLeap(L,H,X,Y) :-
L<H,
X is L,
Y is X+1.
pLeap(L,H,X,Y) :-
L=<H,
L1 is L+1,
pLeap(L1,H,X,Y).
I'd do it simply like this:
pLeap(L,H,X,Y) :-
X >= L,
X =< H,
Y is X+1.
Why doesn't it work (ignoring the special case at the end)?
You could use library clpfd for you problem.
:- use_module(library(clpfd)).
pLeap(L,H,X,Y) :-
X in L..H,
Y #= min(H, X+1),
label([X]).
Here is the output:
?- pLeap(2,5,X,Y).
X = 2,
Y = 3 ;
X = 3,
Y = 4 ;
X = 4,
Y = 5 ;
X = 5,
Y = 5.
The >= and =< operators don't instantiate their arguments, and you can only use them once the arguments have already been instantiated.
Put another way, in the given solution, X and Y are given values with is, and the < and =< operators are only used on L and H, whose values are given by the user. (On the given solution, try pLeap(L,H,2,3) and you'll get the same problem as you're having.)
In your case, though, you try to use >= and =< on X, which has no value yet, and so the interpreter complains.

How do I find all solutions to a goal in Prolog?

I have predicate P1 that returns values one after the other like this:
-? P1(ARGUMENTS, RETURN).
-? RETURN = 1;
-? RETURN = 2;
-? RETURN = 3;
-? fail.
I also have another predicate called P2:
P2(ARGUMENTS, LIST) :- P1(ARGUMENTS, RETURN),... % SOMEHOW HERE I NEED TO INSERT ALL VALUES OF RETURN TO LIST.
How do find all of the values of RETURN and assign them to LIST?
Use findall to accomplish this:
P2(ARGUMENTS, LIST) :- findall(X, P1(ARGUMENTS, X), LIST).
This is related to the bagof function mentioned in the question linked to by Anders Lindahl. There is a good explanation on the relationship between the two functions (and a third function setof) here:
To illustrate the differences consider
a little example:
listing(p).
p(1,3,5).
p(2,4,1).
p(3,5,2).
p(4,3,1).
p(5,2,4).
Try the following goals. (The answer
displays have been modified to save
space.)
?- bagof(Z,p(X,Y,Z),Bag).
Z = _G182 X = 1 Y = 3 Bag = [5] ;
Z = _G182 X = 2 Y = 4 Bag = [1] ;
Z = _G182 X = 3 Y = 5 Bag = [2] ;
Z = _G182 X = 4 Y = 3 Bag = [1] ;
Z = _G182 X = 5 Y = 2 Bag = [4] ;
No
?- findall(Z,p(X,Y,Z),Bag).
Z = _G182 X = _G180 Y = _G181 Bag = [5, 1, 2, 1, 4] ;
No
?- bagof(Z,X^Y^p(X,Y,Z),Bag).
Z = _G182 X = _G180 Y = _G181 Bag = [5, 1, 2, 1, 4] ;
No
?- setof(Z,X^Y^p(X,Y,Z),Bag).
Z = _G182 X = _G180 Y = _G181 Bag = [1, 2, 4, 5] ;
No
The predicates bagof and setof yield
collections for individual bindings of
the free variables in the goal. setof
yields a sorted version of the
collection without duplicates. To
avoid binding variables, use an
existential quantifier expression. For
example the goal
bagof(Z,X^Y^p(X,Y,Z),Bag) asks for
"the Bag of Z's such that there exists
an X and there exists a Y such that
p(X,Y,Z)". findall acts like bagof
with all free variables automatically
existentially quantified. In addition
findall returns an empty list [] there
is no goal satisfaction, whereas bagof
fails.

Resources