Search code examples
prologdcg

Two DCG rules for `(ab)*`. Can it be one?


I want to generate or test strings obeying the Perl Regex (ab)*

The code below works perfectly well:

Generate

?- phrase_acceptable(Text,6).
Text = abababababab ;
false.

Test (or compress?)

?- phrase_acceptable("ababab",N).
[97,98,97,98,97,98]
N = 3 

Enumerate possibilities

?- phrase_acceptable(T,N).
T = '',
N = 0 ;
T = ab,
N = 1 ;
T = abab,
N = 2 ;
T = ababab,
N = 3 
...

However, this demands two clauses for acceptable//1 which are selected based on whether N is fresh or not. Can that be avoided? Using CLP(FD) doesn't help, as one has to check that N>=0 in any case to avoid infinite descent.

ff(X) :- var(X).    % "freshvar(X)" using 2 letters, which is less annoying
bb(X) :- nonvar(X). % "notfreshvar(X)" using 2 letters, which is less annoying

acceptable(0) --> [].
acceptable(N) --> { bb(N), N>0, succ(Nm,N) }, `ab`, acceptable(Nm).  
acceptable(N) --> { ff(N) }, `ab`, acceptable(Nm), { succ(Nm,N) }. 

phrase_acceptable(Text,N) :-
   bb(Text),!,
   atom_codes(Text,Codes), 
   writeln(Codes),
   phrase(acceptable(N),Codes,[]).
   
phrase_acceptable(Text,N) :- 
   ff(Text),!,
   phrase(acceptable(N),Codes,[]),
   atom_codes(Text,Codes).

Solution

  • How about this:

    :- use_module(library(clpfd)).
    
    acceptable(0) --> [].
    acceptable(N1) -->  `ab`, { N #= N1-1, N #>= 0 }, acceptable(N).
    
    phrase_acceptable(Text, N):-
      (nonvar(Text) -> atom_codes(Text, Codes) ; true),
      N #>= 0,
      phrase(acceptable(N), Codes, []),
      (var(Text) -> atom_codes(Text, Codes) ; true).
    

    Test cases:

    ?- phrase_acceptable(ababab,N).
    N = 3 ;
    false.
    
    ?- phrase_acceptable(Text,3).
    Text = ababab ;
    false.
    
    ?- phrase_acceptable(Text,N).
    Text = '',
    N = 0 ;
    Text = ab,
    N = 1 ;
    Text = abab,
    N = 2 ;
    Text = ababab,
    N = 3 .