How to write this DCG more elegantly? - prolog

Playing around with DCGs and stubled upon the following problem:
I want to parse as well as produce an exact amount of spaces (" "). My trivial approach of simply doing this:
trivial_nat_space(0) --> [].
trivial_nat_space(N) -->
{ N > 0, N is M+1 },
" ",
trivial_nat_space(M).
failed terribly, because of insufficient instantiation of N and M depending on whether i do
?- String=" ", my_string_codes(String,Codes), phrase(trivial_nat_space(Anz_Spaces), Codes, [])
or
?- Anz_Spaces=3,my_string_codes(String,Codes), phrase(trivial_nat_space(Anz_Spaces), Codes, [])
where (for convenience)
my_string_codes(S,C) :-
when((ground(S);ground(C)), string_codes(S,C)).
searching for a nice solution to the problem I made a version that depends on self defined nats:
z.
s(z).
s(s(O)) :-
s(O).
nat_num(S,C) :-
when((ground(S);ground(C)),nat_num_(S,C)).
nat_num_(z,0) :- !.
nat_num_(s(N),X) :-
nonvar(X),
!,
X > 0,
Y is X-1,
nat_num_(N,Y).
nat_num_(s(N),X) :-
var(X),
nat_num_(N,Y),
X is Y+1.
n_space(z) --> [].
n_space(s(N)) -->
" ",
n_space(N).
which I would like to avoid because the additional encoding of the natural number is kind of already present in the builtin numbers.
and this:
nat_space(0) --> [].
nat_space(N) -->
{ var(N) },
" ",
nat_space(M),
{ N is M+1 }.
nat_space(M) -->
{ nonvar(M), M>0 },
" ",
{ N is M-1 },
nat_space(N).
which does work fine:
?- Anz_Spaces=3,my_string_codes(String,Codes), once(phrase(nat_space(Anz_Spaces), Codes, [])).
Anz_Spaces = 3,
String = " ",
Codes = [32, 32, 32].
?- String=" ",my_string_codes(String,Codes), once(phrase(nat_space(Anz_Spaces), Codes, [])).
String = " ",
Codes = [32, 32, 32],
Anz_Spaces = 3.
However the encoding of nat_spaces is (in my opinion) far from nice: it depends on meta-predicates to enforce a specific execution sequence, and (more seriously): if the parser were more complex than just " ", the logic would have to be defined in a seperate DCG predicate/rule resulting in the logic for a single parser/generator to be split into two definitions (the separated one and the one enforcing the correct execution sequence).
Is this the canonical/standard way of solving problems like this or is there a more general, elegant solution that I am missing right now?
Additional Info:
I am using SWI-Prolog version 8.3.9 for x86_64-linux
with :- [library(dcg/basics)] and no additional arguments when starting the runtime. Nor do I set any settings in the file with the definitions.

Frankly, your original definition doesn't fail that terribly. No, it does not fail. For the most general query, it produces one solution,
?- phrase(trivial_nat_space(0), Cs).
Cs = [] % pure perfect logic!
; false.
?- phrase(trivial_nat_space(-1), Cs).
false. % it's right to be false!
?- phrase(trivial_nat_space(1), Cs).
error(instantiation_error,(is)/2). % er...
?- phrase(trivial_nat_space(N), Cs). % most general query
Cs = [], N = 0 % again, pure logic
; error(instantiation_error,(is)/2). % mmh...
... and otherwise an instantiation error. Instantiation errors are not the worst that can happen. They clearly and honestly state that more information (= instantiations) must be provided before we can continue. That is much better than to pretend everything is fine when it is not. Think of a clerk who asks for more information as producing an instantiation error. And then compare this to one that just fills out your IRS forms with some bold default assumptions1.
To localize the reason for an instantiation error, we will use a failure-slice. So I will throw in some false goals and also an additional instantiation to make it even easier:
trivial_nat_space(0) --> [], {false}.
trivial_nat_space(N) --> {N = 1},
{ N > 0, N is M+1, false },
" ",
trivial_nat_space(M).
?- phrase(trivial_nat_space(1), Cs).
error(instantiation_error,(is)/2).
This is a pretty disfunctional program! And still it produces an instantiation error. In order to fix your original program we have to modify something in the remaining visible part. In N is M+1 only the M can cause that error. In fact, it occurs here for the first time. We can replace it by M is N-1 which improves your program:
?- phrase(trivial_nat_space(1), Cs).
Cs = " " % see section double quotes
; false.
?- phrase(trivial_nat_space(2), Cs).
Cs = " "
; false.
?- phrase(trivial_nat_space(N), Cs).
Cs = [], N = 0
; error(instantiation_error,(is)/2). % still ...
?- phrase(trivial_nat_space(N), " ").
error(instantiation_error,(is)/2).
Our program now works at least when the concrete number of spaces is known. Even better, we can also use arithmetic expressions!
?- phrase(trivial_nat_space(4*1), Cs). % let's indent by four spaces
Cs = " "
; false.
?- phrase(trivial_nat_space(4*2), Cs). % ... twice ...
Cs = " "
; false.
?- phrase(trivial_nat_space(4*0), Cs). % ... none?
false.
?- phrase(trivial_nat_space(0), Cs).
Cs = [] % here it works
; false.
So N may be an arithmetic integer expression, and it works as expected, except for 0 which must be stated literally. That is not really a deep problem, no algebraic properties are violated. But elegant it is not. Let's remember that.
Back to the instantiation errors. To handle these cases as well we need some way to deal with this variable N. The easiest way is to use library(clpz) or its predecessor in SWI library(clpfd) as proposed in another answer. And yes, you can do such things manually, but thereby you are duplicating the work that has been invested into that library. It might make sense for performance reasons sometimes, but it will come at a hefty (bug ridden) price.
So let's look at #gusbro's solution and don't forget to add
:- use_module(library(clpz)). % SICStus or Scryer
:- use_module(library(clpfd)). % SWI
?- phrase(trivial_nat_space(N), Cs).
Cs = [], N = 0
; Cs = " ", N = 1 % finally, logic!
; Cs = " ", N = 2
; Cs = " ", N = 3
; ... .
?- phrase(trivial_nat_space(N), " ").
N = 2
; false.
?- N = 1+1, phrase(trivial_nat_space(N), " ").
N = 1+1 % nice like is/2
; false.
?- phrase(trivial_nat_space(N), " "), N = 1+1.
false. % and out, why?
Everything is nice and dandy, up to the last query. So that extension with arithmetic expressions did not work out so nicely. Effectively it boils down to the following problem:
?- N = 1+1, N #= 2.
N = 1+1.
?- N #= 2, N = 1+1.
false.
In the first query, we solve the integer-equation 1+1 #= 2 which succeeds, and in the second query, we solve N #= 2 which succeeds with N = 2 and then we try to solve 2 = 1+1 which fails.
In other words, that extension into general arithmetic expressions did not work so well for constraints. Before, instantiation errors hid the problem. Now we need to draw somehow the line. And violating commutativity as above is not a nice option2.
The solution is to separate expression variables and integer variables explicitly and insist on fully instantiated expressions.
?- N = 1+1, #N #= 2.
error(type_error(integer,1+1),must_be/2)
?- #N #= 2, N = 1+1.
false.
?- assertz(clpz:monotonic).
true.
?- N #= 2, N = 1+1.
error(instantiation_error,instantiation_error(unknown(_102),1)).
So now #gusbro's program gets some slight modification:
trivial_nat_space(0) --> [].
trivial_nat_space(N) -->
{ #N #> 0, #M #= #N-1 },
" ",
trivial_nat_space(M).
double_quotes
Since you want elegant code, consider to use as a single representation for text: lists of characters. In this manner you avoid all this converting code which will never be elegant. In some systems like Tau, Trealla, and Scryer, double quoted items are chars by default. In SWI proceed like so:
?- L = "ab", L = [_,_].
false.
?- phrase("ab","ab").
false.
?- set_prolog_flag(double_quotes, chars).
true.
?- L = "ab", L = [_,_].
L = [a, b].
?- phrase("ab","ab").
true.
And with library(double_quotes)
?- L = "ab", L = [_,_].
L = "ab".
Grammars
Finally, there is something to note about multi-directional grammar rules in general. Think of a predicate text_ast/2. For one Abstract Syntax Tree, there is an infinity of valid program texts which all differ by trivial paraphernalia like layout text. Therefore, this general relation must not terminate when only the AST is given. So you would need an extra parameter indicating whether the text should be canonical or not.
1 And in fact in DEC10 Prolog the default assumption for variables in arithmetic expressions was the value zero. ISO Prolog has defined instantiation errors for those situations.
2 In SICStus' native library clpfd, the same problem appears with ?- N = 1+1, call(N #= 2). instead.

For your specific example, you can use CLP(fd) to be able to use the DCG in both ways:
trivial_nat_space(0) --> [].
trivial_nat_space(N) -->
{ N #> 0, M #= N-1 },
" ",
trivial_nat_space(M).
In the following sample runs I will use backticks (`) to use coded strings:
?- phrase(trivial_nat_space(Anz_Spaces), ` `, []).
Anz_Spaces = 3 ;
false.
?- phrase(trivial_nat_space(3), Spaces, []).
Spaces = [32, 32, 32] ;
false.
?- phrase(trivial_nat_space(N), Spaces, []).
N = 0,
Spaces = [] ;
N = 1,
Spaces = [32] ;
N = 2,
Spaces = [32, 32] ;
N = 3,
Spaces = [32, 32, 32]
...

In this case we can avoid explicit arithmetic altogether, and let unification do the work:
:- set_prolog_flag(double_quotes, chars).
spaces --> "".
spaces --> " ", spaces.
n_spaces(N, Spaces) :-
length(Spaces, N),
phrase(spaces, Spaces).
?- n_spaces(N, S).
N = 0,
S = [] ;
N = 1,
S = [' '] ;
N = 2,
S = [' ', ' ']
?- n_spaces(2, S).
S = [' ', ' '].
?- n_spaces(N, " ").
N = 2.
We need the double_quotes flag here because (at least in SWI-Prolog 8.0.2) it seems that strings have to be either ground or var, unlike lists which can have variable entries/tails, so I don't think it's possible to use this unification technique with SWI-style strings:
?- string_length(String, Length).
ERROR: Arguments are not sufficiently instantiated
ERROR: In:
ERROR: [8] string_length(_10886,_10888)
ERROR: [7] <user>

Related

Find an "infix" of a list in Prolog - order matters

A question from someone who knows Prolog for a week=)
I am writing some prolog command infix(Inf,List)
to check if one list is, as our prof formulated, "an infix" of another list. The order matters+ it shouldn't be right at the beginning or the end of the List.
That means for example:
If we have Inf=[1,2] and List=[1,2,3,4] then is is false.
If we have Inf=[3,4] and List=[1,2,3,4] then is is also false.
If we have Inf=[2,3] and List=[1,2,3,4] then it is true.
If it is Inf=[3,2] and List=[1,2,3,4] then is is false.
If it is Inf=[2,4] and List=[1,2,3,4,5] then is is false.
I wrote some rules already and with them I seem to manage to solve the problem of order and not counting the first element of a List.
infix(Inf,List):- length(Inf,L1),length(List,L2), L1>L2, !, fail.
infix(Inf,List):- length(Inf,L1),length(List,L2), L1=L2, !, fail.
infix(Inf,List):- length(Inf,L1),length(List,L2), L1<L2, delete_first(Inf,List).
delete_first(Inf,[_L|List]):- sublist(Inf,List).
sublist([El|Sub],[El|List]):- checksublist(Sub,List).
sublist([S|Sub],[L|List]):- sublist([S|Sub],List).
checksublist([], L).
checksublist([El|Sub],[El|List]):- checksublist(Sub,List).
However, I can't formulate it in a way, so that the last element is not counted =(. According to my intuitive logic the conditionchecksublist([], L).should be smth like checksublist([], [_|[]]). But it doesn't work this way- I get false for everything.
Does anybody know how to get rid of the last element in this situation? Thanks in advance!
Grammars to the rescue! But I would not call this infix. It's a certain subsequence, actually even a certain substring.
infix(Inf, List) :-
Inf = [_|_],
phrase(([_], ..., seq(Inf), [_], ...), List).
% The following are frequently predefined
... --> [] | [_], ... .
seq([]) --> [].
seq([E|Es]) --> [E], seq(Es).
(Edit) Since you insist that both the prefix and the postfix are non-empty, you probably want this to hold for the infix too. Thus Inf = [_|_] added.
This is the result using Scryer's top level:
?- infix(Inf,"abcdef").
Inf = "b"
; Inf = "bc"
; Inf = "bcd"
; Inf = "bcde"
; Inf = "c"
; Inf = "cd"
; Inf = "cde"
; Inf = "d"
; Inf = "de"
; Inf = "e"
; false.
See this how to print lists of characters as double quoted chars in other systems.
This is too imperative.
You can let Prolog solve it with append/2. It's search-assisted programming, let's use it.
infix(Inf,List) :- append([Prefix,Inf,Suffix],List),Prefix\=[],Suffix\=[].
This is completely declarative, in the sense that
it is formulated as constraint that a solution must fulfill (very mathematical).
Test it using the Unit Test framework:
:- begin_tests(infix).
test(one,[fail]) :- infix([1,2],[1,2,3,4]).
test(two,[fail]) :- infix([3,4],[1,2,3,4]).
test(three) :- infix([2,3],[1,2,3,4]).
test(four,[fail]) :- infix([3,2],[1,2,3,4]).
test(five,[fail]) :- infix([2,4],[1,2,3,4,5]).
:- end_tests(infix).
rt:-run_tests(infix).
Then
?- rt.
% PL-Unit: infix ..
Warning: user://1:12:
PL-Unit: Test three: Test succeeded with choicepoint
.. done
% All 5 tests passed
true.
Sadly, Prolog does not do deep reasoning and theorem proving but employs brute force: it tries possible solutions until one passes or there are no more. Weel, it's sufficient for this case.
For example:
?- append([Prefix,[3,4],Suffix],[1,2,3,4,5,3,4,6]).
Prefix = [1, 2],
Suffix = [5, 3, 4, 6] ;
Prefix = [1, 2, 3, 4, 5],
Suffix = [6] ;
false.

Extracting sequences (Lists) Prolog

Given a list eg [1,2,3,7,2,5,8,9,3,4] how would I extract the sequences within the list?
A sequence is defined as an ordered list (Normally I would say n-tuple but I have been told in prolog a tuple is referred to as a sequence). So we want to cut the list at the point where the next element is smaller than the previous one.
So for the list [1,2,3,7,2,5,8,9,3,4] it should return:
[ [1,2,3,7], [2,5,8,9], [3,4] ] %ie we have cut the list at position 4 & 8.
For this exercise you CANNOT use the construct ; or ->
Many thanks in advance!
EXAMPLE RESULTS:
eg1.
?-function([1,2,3,7,2,5,8,9,3,4],X): %so we cut the list at position 4 & 9
X = [ [1,2,3,7], [2,5,8,9], [3,4] ].
eg2.
?-function([1,2,3,2,2,3,4,3],X): %so we cut the list at position 3,4 & 8
X = [ [1,2,3], [2], [2,3,4], [3] ].
Hopefully that helps clarify the problem. If you need further clarification just let me know! Thanks again in advance for any help you are able to provide.
First, let's break it down conceptually. The predicate list_ascending_rest/3 defines a relation between a list Xs, the left-most ascending sublist of maximum length Ys, and the remaining items Rest. We will use it like in the following query:
?- Xs = [1,2,3,7,2,5,8,9,3,4], list_ascending_rest(Xs,Ys,Rest).
Ys = [1,2,3,7],
Rest = [2,5,8,9,3,4] ;
false.
The straight-forward predicate definition goes like this:
:- use_module(library(clpfd)).
list_ascending_rest([],[],[]).
list_ascending_rest([A],[A],[]).
list_ascending_rest([A1,A2|As], [A1], [A2|As]) :-
A1 #>= A2.
list_ascending_rest([A1,A2|As], [A1|Bs], Cs) :-
A1 #< A2,
list_ascending_rest([A2|As], Bs,Cs).
Then, let's implement predicate list_ascendingParts/2. This predicate repeatedly uses list_ascending_rest/3 for each part until nothing is left.
list_ascendingParts([],[]).
list_ascendingParts([A|As],[Bs|Bss]) :-
list_ascending_rest([A|As],Bs,As0),
list_ascendingParts(As0,Bss).
Example queries:
?- list_ascendingParts([1,2,3,7,2,5,8,9,3,4],Xs).
Xs = [[1,2,3,7], [2,5,8,9], [3,4]] ;
false.
?- list_ascendingParts([1,2,3,2,2,3,4,3],Xs).
Xs = [[1,2,3], [2], [2,3,4], [3]] ;
false.
Edit 2015/04/05
What if the ascending parts are known but the list is unknown? Let's find out:
?- list_ascendingParts(Ls, [[3,4,5],[4],[2,7],[5,6],[6,8],[3]]).
Ls = [3,4,5,4,2,7,5,6,6,8,3] ? ;
no
And let's not forget about the most general query using list_ascendingParts/2:
?- assert(clpfd:full_answer).
yes
?- list_ascendingParts(Ls, Ps).
Ls = [], Ps = [] ? ;
Ls = [_A], Ps = [[_A]] ? ;
Ls = [_A,_B], Ps = [[_A],[_B]], _B#=<_A, _B in inf..sup, _A in inf..sup ? ...
Edit 2015-04-27
Room for improvement? Yes, definitely!
By using the meta-predicate splitlistIfAdj/3 one can "succeed deterministically" and "use non-determinism when required", depending on the situation.
splitlistIfAdj/3 is based on if_/3 as proposed by #false in this answer. So the predicate passed to it has to obey the same convention as (=)/3 and memberd_truth/3.
So let's define (#>)/3 and (#>=)/3:
#>=(X,Y,Truth) :- X #>= Y #<==> B, =(B,1,Truth).
#>( X,Y,Truth) :- X #> Y #<==> B, =(B,1,Truth).
Let's re-ask above queries, using splitlistIfAdj(#>=)
instead of list_ascendingParts:
?- splitlistIfAdj(#>=,[1,2,3,7,2,5,8,9,3,4],Pss).
Pss = [[1,2,3,7],[2,5,8,9],[3,4]]. % succeeds deterministically
?- splitlistIfAdj(#>=,[1,2,3,2,2,3,4,3],Pss).
Pss = [[1,2,3],[2],[2,3,4],[3]]. % succeeds deterministically
?- splitlistIfAdj(#>=,Ls,[[3,4,5],[4],[2,7],[5,6],[6,8],[3]]).
Ls = [3,4,5,4,2,7,5,6,6,8,3] ; % works the other way round, too
false. % universally terminates
Last, the most general query. I wonder what the answers look like:
?- splitlistIfAdj(#>=,Ls,Pss).
Ls = Pss, Pss = [] ;
Ls = [_G28], Pss = [[_G28]] ;
Ls = [_G84,_G87], Pss = [[_G84],[_G87]], _G84#>=_G87 ;
Ls = [_G45,_G48,_G41], Pss = [[_G45],[_G48],[_G41]], _G45#>=_G48, _G48#>=_G41
% and so on...
maplist/3 as suggested in the comment won't help you here because maplist/3 is good at taking a list and mapping each element into a same-size collection of something else, or establishing a relation evenly across all of the individual elements. In this problem, you are trying to gather contiguous sublists that have certain properties.
Here's a DCG solution. The idea here is to examine the list as a series of increasing sequences where, at the boundary between them, the last element of the prior sequence is less than or equal to the first element of the following sequence (as the problem statement basically indicates).
% A set of sequences is an increasing sequence ending in X
% followed by a set of sequences that starts with a value =< X
sequences([S|[[Y|T]|L]]) --> inc_seq(S, X), sequences([[Y|T]|L]), { X >= Y }.
sequences([S]) --> inc_seq(S, _).
sequences([]) --> [].
% An increasing sequence, where M is the maximum value
inc_seq([X,Y|T], M) --> [X], inc_seq([Y|T], M), { X < Y }.
inc_seq([X], X) --> [X].
partition(L, R) :- phrase(sequences(R), L).
| ?- partition([1,2,3,4,2,3,8,7], R).
R = [[1,2,3,4],[2,3,8],[7]] ? ;
(1 ms) no
| ?- partition([1,2,3,2,2,3,4,3],X).
X = [[1,2,3],[2],[2,3,4],[3]] ? ;
(1 ms) no
The only reason for the rule sequences([]) --> []. is if you want partition([], []) to be true. Otherwise, the rule isn't required.

Why do I get duplicate results in my `length/2` implementation in prolog?

I'm working through exercises in Prolog. I've implemented a predicate similar to length/2 (called ue_length here) like this:
%%
% ue_length/2
%%
% not a list predicate
\+(T) :- call(T), !, fail.
\+(_).
% target case
ue_length(List, Length) :- \+(is_list(List)), !, fail.
ue_length(List, Length) :- ue_length(List, 0, Length).
% standard cases
ue_length([], Length, Length).
ue_length([X], Part, Length) :- ue_length([], [Part], Length).
ue_length([X| Rest], Part, Length) :- ue_length(Rest, [Part], Length).
The result is supposed to be a term rather than a number: 0 for [], [0] for a list of length one and [...[0]...] (n brackets) for a list of length n.
When I query Prolog (SWI-Prolog 6) with e.g. [1,2,3,4,5] I get the correct result twice.
?- ue_length([1,2,3,4,5], X).
X = [[[[[0]]]]]
X = [[[[[0]]]]].
I'm new to Prolog. Can someone explain why I get a redundant result?
Minimize the problematic query
As a first step, reduce the size of your query. The same problem (redundant solutions) can be observed already with ue_length([1], X). alone.
But there is something else which is much more problematic:
Is your definition a relation?
?- ue_length(L,N).
false.
So your definition succeeds with a list [1] but fails with a variable in its place? This does not make any sense at all! Even looping would be a better behavior.
Another problematic case is
?- ue_length(L,0).
false.
Here, your definition should give L = [] as answer.
The culprit for this is the test using is_list/1. Simply drop the rule
ue_length(List, Length) :- \+(is_list(List)), !, fail. % incorrect!
Now your definition can also be used to ask the most general query which contains distinct variables in the arguments.
?- ue_length(L,N).
L = [], N = 0
; L = [_A], N = [0]
; L = [_A], N = [0]
; L = [_A, _B], N = [[0]]
...
This is one of the very nice properties of Prolog: You do not need to type in concrete data for your test cases. Just enter the most general query like a pro, and Prolog will do the rest for you.
Localize with false
To localize this redundancy, first think of how that could have happened. One simple possibility is that some clause in your program is redundant and can thus be deleted.
Let's say it's the last one. So I will insert a goal false into the last clause. And I try again the most general query. Alas ...
ue_length(List, Length) :- ue_length(List, 0, Length).
% standard cases
ue_length([], Length, Length).
ue_length([_X], Part, Length) :-
ue_length([], [Part], Length).
ue_length([_X| Rest], Part, Length) :-
false,
ue_length(Rest, [Part], Length).
?- ue_length(L,N).
L = [], N = 0
; L = [_A], N = [0]
; false.
That rule must be quite important, for now we get only answers for lists of length zero and one. So my guess was wrong. But my point is that you can see this very easily by simply using the most general query. The actual redundant clause is the other one. And don't forget to ask the most general query such that you can be sure you get all your answers!

What does this wildcard do in this prolog scenario?

I've come across this code:
connectRow(_,_,0).
connectRow([spot(_,R,_,_)|Spots],R,K) :- K1 is K-1, connectRow(Spots,R,K1).
/*c*/
connectRows([]).
connectRows(Spots) :-
connectRow(Spots,_,9),
skip(Spots,9,Spots1),
connectRows(Spots1).
How does the wildcard in the connectRow(Spots,_,9) work? How does it know which values to check and how does it know that it checked all the possible values?
Edit: I think I understand why this works but I'd like it if someone could verify this for me:
When I "call" the connectRow with the wildcard it matches the wildcard with the "R" in the connectRow predicate. Could this be it?
The _ is just like any other variable, except that each one you see is treated as a different variable and Prolog won't show you what it unifies with. There's no special behavior there; if it confuses you about the behavior, just invent a completely new variable and put it in there to see what it does.
Let's talk about how Prolog deals with variables. Here's an experiment you can follow along with that should undermine unhelpful preconceived notions if you happen to have them.
?- length([2,17,4], X)
X = 3.
A lot of Prolog looks like this and it's easy to fall into the trap of thinking that there are designated "out" variables that work like return values and designated "in" variables that work like parameters. After all:
?- length([2,17,4], 3).
true.
?- length([2,17,4], 5).
false.
Here we begin to see that something interesting is happening. A faulty intuition would be that Prolog is somehow keeping track of the input and output variables and "checking" in this case. That's not what's happening though, because unification is more general than that. Observe:
?- length(X, 3).
X = [_G2184, _G2187, _G2190].
We've now turned the traditional parameter/return value on its head: Prolog knows that X is a list three items long, but doesn't know what the items actually are. Believe it or not, this technique is frequently used to generate variables when you know how many you need but you don't need to have them individually named.
?- length(X, Y).
X = [],
Y = 0 ;
X = [_G2196],
Y = 1 ;
X = [_G2196, _G2199],
Y = 2 ;
X = [_G2196, _G2199, _G2202],
Y = 3
It happens that the definition of length is very general and Prolog can use it to generate lists along with their lengths. This kind of behavior is part of what makes Prolog so good at "generate and test" solutions. You define your problem logically and Prolog should be able to generate logically sound values to test.
All of this variation springs from a pretty simple definition of length:
length([], 0).
length([_|Rest], N1) :-
length(Rest, N0),
succ(N0, N1).
The key is to not read this like a procedure for calculating length but instead to see it as a logical relation between lists and numbers. The definition is inductive, relating the empty list to 0 and a list with some items to 1 + the length of the remainder of the list. The engine that makes this work is called unification.
In the first case, length([2,17,4], X), the value [17,4] is unified with Rest, N0 with 2 and N1 with 3. The process is recursive. In the final case, X is unified with [] and Y with 0, which leads naturally to the next case where we have some item and Y is 1, and the fact that the variable representing the item in the list doesn't have anything in particular to unify with doesn't matter because the value of that variable is never used.
Looking at your problem we see the same sort of recursive structure. The predicates are quite complex, so let's take them in pieces.
connectRow(_, _, 0).
This says connectRow(X, Y, 0) is true, regardless of X and Y. This is the base case.
connectRow([spot(_, R, _, _)|Spots], R, K) :-
This rule is matching a list of spots of a particular structure, presuming the first spot's second value (R) matches the second parameter.
K1 is K-1, connectRow(Spots, R, K1).
The body of this clause is essentially recurring on decrementing K, the third parameter.
It's clear now that this is basically going to generate a list that looks like [spot(_, R, _, _), spot(_, R, _, _), ... spot(_, R, _, _)] with length = K and no particular values in the other three positions for spot. And indeed that's what we see when we test it:
?- connectRow(X, Y, 0).
true ;
(infinite loop)^CAction (h for help) ? abort
% Execution Aborted
?- connectRow(X, Y, 2).
X = [spot(_G906, Y, _G908, _G909), spot(_G914, Y, _G916, _G917)|_G912] ;
(infinite loop)^CAction (h for help) ? abort
So there seem to be a few bugs here; if I were sure these were the whole story I would say:
The base case should use the empty list rather than matching anything
We should stipulate in the inductive case that K > 0
We should use clpfd if we want to be able to generate all possibilities
Making the changes we get slightly different behavior:
:- use_module(library(clpfd)).
connectRow([], _, 0).
connectRow([spot(_, R, _, _)|Spots], R, K) :-
K #> 0, K1 #= K-1, connectRow(Spots, R, K1).
?- connectRow(X, Y, 0).
X = [] ;
false.
?- connectRow(X, Y, 1).
X = [spot(_G906, Y, _G908, _G909)] ;
false.
?- connectRow(X, Y, Z).
X = [],
Z = 0 ;
X = [spot(_G918, Y, _G920, _G921)],
Z = 1 ;
X = [spot(_G918, Y, _G920, _G921), spot(_G1218, Y, _G1220, _G1221)],
Z = 2
You'll note that in the result we have Y standing in our spot structures, but we have weird looking automatically generated variables in the other positions, such as _G918. As it happens, we could use _ instead of Y and see a similar effect:
?- connectRow(X, _, Z).
X = [],
Z = 0 ;
X = [spot(_G1269, _G1184, _G1271, _G1272)],
Z = 1 ;
X = [spot(_G1269, _G1184, _G1271, _G1272), spot(_G1561, _G1184, _G1563, _G1564)],
Z = 2
All of these strange looking variables are there because we used _. Note that all of the spot structures have the exact same generated variable in the second position, because Prolog was told it had to unify the second parameter of connectRow with the second position of spot. It's true everywhere because R is "passed along" to the next call to connectRow, recursively.
Hopefully this helps explain what's going on with the _ in your example, and also Prolog unification in general.
Edit: Unifying something with R
To answer your question below, you can unify R with a value directly, or by binding it to a variable and using the variable. For instance, we can bind it directly:
?- connectRow(X, 'Hello, world!', 2).
X = [spot(_G275, 'Hello, world!', _G277, _G278), spot(_G289, 'Hello, world!', _G291, _G292)]
We can also bind it and then assign it later:
?- connectRow(X, R, 2), R='Neato'.
X = [spot(_G21, 'Neato', _G23, _G24), spot(_G29, 'Neato', _G31, _G32)],
R = 'Neato'
There's nothing special about saying R=<foo>; it unifies both sides of the expression, but both sides can be expressions rather than variables:
?- V = [2,3], [X,Y,Z] = [1|V].
V = [2, 3],
X = 1,
Y = 2,
Z = 3.
So you can use R in another predicate just as well:
?- connectRow(X, R, 2), append([1,2], [3,4], R).
X = [spot(_G33, [1, 2, 3, 4], _G35, _G36), spot(_G41, [1, 2, 3, 4], _G43, _G44)],
R = [1, 2, 3, 4] ;
Note that this creates opportunities for backtracking and generating other solutions. For instance:
?- connectRow(X, R, 2), length(R, _).
X = [spot(_G22, [], _G24, _G25), spot(_G30, [], _G32, _G33)],
R = [] ;
X = [spot(_G22, [_G35], _G24, _G25), spot(_G30, [_G35], _G32, _G33)],
R = [_G35] ;
X = [spot(_G22, [_G35, _G38], _G24, _G25), spot(_G30, [_G35, _G38], _G32, _G33)],
R = [_G35, _G38] ;
Hope this helps!

Counting definite clause grammar recursions in Prolog

I have the following Prolog definite clause grammar:
s-->[a],s,[b].
s-->[].
This will result in words like [a,a,b,b] being accepted in opposite to words like [a,b,a,b]. To put it in a nutshell the grammar is obviously a^n b^n. Now I want to return n to the user. How can I calculate n?
s(X)-->[a],s(Y),[b],{X is Y+1}.
s(0)-->[].
One needs to give parameters to the DCG non terminals. Please take care equality doesn't work exactly like assignment of imperative programming languages so X is Y + 1 was used.
Some sample outputs:
s(X,[a,b,b,b],[]).
false.
s(X,[a,a,a,b,b,b],[]).
X = 3 ;
false.
s(N, M) --> [a], {N1 is N + 1}, s(N1, M), [b].
s(N, N) --> [].
s(N) --> s(0, N).
Usage:
?- phrase(s(N), [a,a,a,b,b,b]).
N = 3
The answers by #thequark and by #LittleBobbyTables work fine when used with ground strings.
But what if they are not bounded in length, like in the following queries?
?- phrase(s(3),_). % expected: success
% observed: no answer(s)
?- phrase(s(-10),_). % expected: failure
% observed: no answer(s)
We surely want queries like the one above to terminate universally!
Let's use clpfd and write:
:- use_module(library(clpfd)).
s(0) --> [].
s(N) --> {N#>0,N#=N0+1},[a],s(N0),[b].
Sample queries:
?- phrase(s(N),[a,a,a,a,b,b,b,b]).
N = 4 ; % works like in the other answers
false.
?- phrase(s(3),Xs).
Xs = [a,a,a,b,b,b] ; % now, this works too!
false. % (terminates universally)
?- phrase(s(-10),_). % fails, like it should
false.

Resources