3
votes

I am trying to define a Prolog DCG for the set of strings 0^N 1^M 2^N+M of length 2N + 2M for N, M >= 0 using extra arguments. An example of a correct string would be "011222" but not "012".

I have used the following code to create this DCG.

s --> a(N), b(M), c(N), c(M).

a(0) --> [].
a(succ(X)) --> [0], a(X).

b(0) --> [].
b(succ(X)) --> [1], b(X).

c(0) --> [].
c(succ(X)) --> [2], c(X).

When I run the query

s([0,1,1,2,2,2], []).

Prolog returns true as expected.

However when I run

s(X, []).

Prolog returns the following:

X = []
X = [1,2]
X = [1,1,2,2]
X = [1,1,1,2,2,2]

These are not valid strings. I think this may be because N and M are being decremented by the c predicate before prolog runs the a and b predicates. Is this the case? How could this be resolved?

Edit: I've tried modifying the s production to this:

s --> a(N), b(M), c(NplusM), {NplusM is N + M}.

but that gives an error when running queries.

2
The productions are valid, you didn't exclude N=0.Mostowski Collapse

2 Answers

1
votes

You're misusing succ/2, maybe because you expect Prolog evaluates functions in head patterns. It doesn't. Then, try to replace your rules with

a(0) --> [].
a(Y) --> {succ(X,Y)}, [0], a(X).

etc etc

edit since succ/2 needs at least one argument instantiated to an integer, we could supply N,M to the DCG entry, or, using CLP(FD):

:- use_module(library(clpfd)).

s --> a(N), b(M), c(N), c(M).

a(0) --> [].
a(Y) --> {Y #= X-1}, [0], a(X).

b(0) --> [].
b(Y) --> {Y #= X-1}, [1], b(X).

c(0) --> [].
c(Y) --> {Y #= X-1}, [2], c(X).

but still, list' length must be provided. For example

?- length(L,_),phrase(s,L).
L = [] ;
L = [1, 2] ;
L = [0, 2] ;
L = [1, 1, 2, 2] ;
L = [0, 1, 2, 2] ;
L = [0, 0, 2, 2] ;
...
1
votes

IMO the answers you are getting are correct!

I renamed your grammar from s to aN_bM_cNM and added two additional arguments, one for N, the other for M. Also, I renamed succ to s:

aN_bM_cNM(N, M) --> n_reps(N, 0), n_reps(M, 1), n_reps(N, 2), n_reps(M, 2).

n_reps(  0 , _) --> [].
n_reps(s(N), E) --> [E], n_reps(N, E).

Now let's run the query that @CapelliC gave. The goal length(Xs, _) ensures fair enumeration of the infinite solution set of aN_bM_cNM//2:

?- length(Xs, _), phrase(aN_bM_cNM(N,M), Xs).
(  Xs = []               , N =       0   , M =         0
;  Xs = [1,2]            , N =       0   , M =       s(0)
;  Xs = [0,2]            , N =     s(0)  , M =         0
;  Xs = [1,1,2,2]        , N =       0   , M =     s(s(0))
;  Xs = [0,1,2,2]        , N =     s(0)  , M =       s(0)
;  Xs = [0,0,2,2]        , N =   s(s(0)) , M =         0
;  Xs = [1,1,1,2,2,2]    , N =       0   , M =   s(s(s(0)))
;  Xs = [0,1,1,2,2,2]    , N =     s(0)  , M =     s(s(0))
;  Xs = [0,0,1,2,2,2]    , N =   s(s(0)) , M =       s(0)
;  Xs = [0,0,0,2,2,2]    , N = s(s(s(0))), M =         0
;  Xs = [1,1,1,1,2,2,2,2], N =       0   , M = s(s(s(s(0))))
...

To raise the lower bound of N or M, just state an additional goal of the form X = s(s(_)) (for a minimum value of 2). In the following query both N and M are to be greater than 0:

?- N =   s(_) , M =     s(_)  , length(Xs, _), phrase(aN_bM_cNM(N,M), Xs).
(  N =   s(0) , M =     s(0)  , Xs = [0,1,2,2]
;  N =   s(0) , M =   s(s(0)) , Xs = [0,1,1,2,2,2]
;  N = s(s(0)), M =     s(0)  , Xs = [0,0,1,2,2,2]
;  N =   s(0) , M = s(s(s(0))), Xs = [0,1,1,1,2,2,2,2]
...