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

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).

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 .

Related

Filter list in prolog

I'm trying to rewrite code from Haskell to Prolog.
count :: Eq a => a -> [a] -> Int
count x = length . filter (x==)
f :: [Integer] -> [Integer]
f [] = []
f list = filter (\x -> count x list == 1) list
This code return list that contains elements that appears only once in the list.
So if I have list [1,1,2,2,3,4,4,5] this function returns [3,5]
I tried to find filter construction in Prolog but seems there no such thing. How can I make similar function in Prolog ?
To the existing answers, I would like to add an answer that is quite general in the sense that you can use it in multiple directions.
Building block: list_element_number/3
I start with the following predicate, defining a relation between:
a list Ls0
an element E
the number N of occurrences of E in Ls0
Here it is:
list_element_number(Ls0, E, N) :-
tfilter(=(E), Ls0, Ls),
length(Ls, N).
This solution uses tfilter/3 from library(reif). The predicate subsumes the function count you have posted. The main benefit of this predicate over the function is that the predicate can be used not only in those cases that even Haskell can do easily, such as:
?- list_element_number([a,b,c], a, N).
N = 1.
No, we can use it also in other directions, such as:
?- list_element_number([a,b,c], X, 1).
X = a ;
X = b ;
X = c ;
false.
Or even:
?- list_element_number([a,b,E], X, 2).
E = X, X = a ;
E = X, X = b ;
false.
Or even:
?- list_element_number([A,B,C], X, 3).
A = B, B = C, C = X ;
false.
And even in the most general case, in which all arguments are fresh variables:
?- list_element_number(Ls, E, N).
Ls = [],
N = 0 ;
Ls = [E],
N = 1 ;
Ls = [E, E],
N = 2 ;
Ls = [E, E, E],
N = 3 .
We can fairly enumerate all answers like this:
?- length(Ls, _), list_element_number(Ls, E, N).
Ls = [],
N = 0 ;
Ls = [E],
N = 1 ;
Ls = [_160],
N = 0,
dif(E, _160) ;
Ls = [E, E],
N = 2 .
Main predicate: list_singletons/2
Using this building block, we can define list_singletons/2 as follows:
list_singletons(Ls, Singles) :-
tfilter(count_one(Ls), Ls, Singles).
count_one(Ls, E, T) :-
list_element_number(Ls, E, Num),
cond_t(Num=1, true, T).
This uses cond_t/3 and (again) tfilter/3 from library(reif).
Sample queries
Here are a few sample queries. First, the test case you have posted:
?- list_singletons([1,1,2,2,3,4,4,5], Singles).
Singles = [3, 5].
It works as desired.
Now a case involving variables:
?- list_singletons([A,B], Singles).
A = B,
Singles = [] ;
Singles = [A, B],
dif(A, B).
On backtracking, all possibilities are generated: Either A = B holds, and in that case, there is no element that occurs only once. Or A is different from B, and in that case both A and B occur exactly once.
As a special case of the above query, we can post:
?- list_singletons([A,A], Singles).
Singles = [].
And as a generalization, we can post:
?- length(Ls, _), list_singletons(Ls, Singles).
Ls = Singles, Singles = [] ;
Ls = Singles, Singles = [_7216] ;
Ls = [_7216, _7216],
Singles = [] ;
Ls = Singles, Singles = [_7828, _7834],
dif(_7828, _7834) ;
Ls = [_7216, _7216, _7216],
Singles = [] ;
Ls = [_7910, _7910, _7922],
Singles = [_7922],
dif(_7910, _7922) .
Enjoy the generality of this relation, obtained via logical-purity.
A more simple version :
filter_list(L,OutList):-findall(X, (select(X,L, L1),\+member(X, L1)) , OutList).
?- filter_list([1,1,2,2,3,4,4,5],L).
L = [3, 5].
Without findall, you can try
filter_list(In, Out) :- filter_list(In, _, Out).
filter_list([], [], []).
filter_list([H|T], L1, L2) :-
filter_list(T, LL1, LL2),
( member(H, LL1)
-> L1 = LL1, L2 = LL2
; (select(H, LL2, L2)
-> L1 = [H|LL1]
; L1 = LL1, L2 = [H|LL2])).
without counting...
filter_uniques([],[]).
filter_uniques([H|T],F) :-
delete(T,H,D),
( D=T -> F=[H|R],S=T ; F=R,S=D ),
filter_uniques(S,R).
a more direct rewrite of your code, with library(yall) support for inlining of the filter predicate (the first argument to include/3)
filt_uniq(L,F) :-
include({L}/[E]>>aggregate(count,member(E,L),1),L,F).
A simple version:
(see the comment by #false below, the version with findall/3 has some inconsistency problems in more complex queries but second version looks ok however it is definitely not so efficient ).
filter_list(L,OutList):-findall(X, (member(X,L),count(X,L,N),N=:=1) , OutList).
count(_,[],0).
count(X,[X|T],N):-count(X,T,N1),N is N1+1.
count(X,[X1|T],N):-dif(X,X1),count(X,T,N).
The predicate filter_list/2 uses findall/3 and simply states find all X that belong to the list L and count returns 1 and store them in OutList.
Example:
?- filter_list([1,1,2,2,3,4,4,5],L).
L = [3, 5].
You could write filter_list/2 without using findall/3 like:
filter_list(L,OutList):- filter_list(L,OutList,L).
filter_list([],[],_).
filter_list([H|T],[H|T1],L):-count(H,L,N), N=:=1, filter_list(T,T1,L).
filter_list([H|T],T1,L):-count(H,L,N), N > 1, filter_list(T,T1,L).

Checking if a string is contained in a language (Prolog)

This is the CFG:
S -> T | V
T -> UU
U -> aUb | ab
V -> aVb | aWb
W -> bWa | ba
so this will accept some form of:
{a^n b^n a^m b^m | n,m >= 1} U {a^n b^m a^m b^n | n,m >= 1}
And here is the code I'm working with:
in_lang([]).
in_lang(L) :-
mapS(L), !.
mapS(L) :-
mapT(L) ; mapV(L),!.
mapT(L) :-
append(L1, mapU(L), L), mapU(L1), !.
mapU([a|T]) :-
((append(L1,[b],T), mapU(L1)) ; (T = b)),!.
mapV([a|T]) :-
((append(L1,[b],T), mapV(L1)) ;
(append(L1,[b],T), mapW(L1))),
!.
mapW([b|T]) :-
((append(L1,[a],T), mapW(L1)) ;
(T = a)),
!.
As of right now, this is returning false for the following three strings:
[a,a,b,b,a,b] // this should be true
[a,a,a,b,b,a,a,b,b,b] // this should be true as well
[a,a,a,b,b,a,b,b,b] // this one IS false
Any help or insight would be greatly appreciated, I'm not too comfortable with Prolog so debugging this by myself has been a challenge.
Simply use a dcg! And library(double_quotes).
:- set_prolog_flag(double_quotes, chars).
s --> t | v.
t --> u, u.
u --> "a",u,"b" | "ab".
v --> "a",v,"b" | "a",w,"b".
w --> "b",w,"a" | "ba".
?- use_module(library(double_quotes)).
?- length(L,N), phrase(s, L).
L = "abab", N = 4
; L = "abab", N = 4
; L = "aabbab", N = 6
; L = "abaabb", N = 6
; L = "aababb", N = 6
; L = "abbaab", N = 6
; L = "aaabbbab", N = 8
; L = "aabbaabb", N = 8
; L = "abaaabbb", N = 8
; L = "aaababbb", N = 8
; ... .
First, note that this code doesn't make sense:
... append(L1, mapU(L), L) ...
In Prolog there are predicates, not functions...
A CFG production rule (a non terminal) should 'eat' a number of tokens, and in Prolog this means you need at least 2 arguments: the input token list, and what remains after a production has successfully matched the relevant part of input.
That is, append/3 is not required: just pattern matching, performed by unification operator (=)/2
mapS(L1, L) :- mapT(L1,L) ; mapV(L1,L).
mapT(L1, L) :- mapU(L1,L2), mapU(L2,L).
mapU(L1, L) :- L1=[a|L2], mapU(L2,L3), L3=[b|L] ; L1=[a,b|L].
... complete the translation
and then call it:
?- mapS([a,a,b,b,a,b],R).
R = [] ;
false.
R = [] means the entire sequence has been matched...
In the definition of mapT, you are trying to use the "return value" of mapU as an argument to append. But mapU is a predicate, and predicates don't have return values.
Instead one typically writes a predicate with an unbound variable which the predicate binds to the desired "return value"; after the predciate has been proven, the now bound variable can be used in subsequent predicates.

Defining Prolog DCG with extra arguments

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.
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]
...
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] ;
...

Prolog, split list into two lists

I got a problem with lists. What I need to do is to split one list [1,-2,3,-4], into two lists [1,3] and [-2,-4]. My code looks like the following:
lists([],_,_).
lists([X|Xs],Y,Z):- lists(Xs,Y,Z), X>0 -> append([X],Y,Y) ; append([X],Z,Z).
and I'm getting
Y = [1|Y],
Z = [-2|Z].
What am I doing wrong?
If your Prolog system offers clpfd you could preserve logical-purity. Want to know how? Read on!
We take the second definition of lists/3 that #CapelliC wrote in
his answer as a starting point, and replace partition/4 by tpartition/4 and (<)/2 by (#<)/3:
lists(A,B,C) :- tpartition(#<(0),A,B,C).
Let's run a sample query!
?- As = [0,1,2,-2,3,4,-4,5,6,7,0], lists(As,Bs,Cs).
As = [0,1,2,-2,3,4,-4,5,6,7,0],
Bs = [ 1,2, 3,4, 5,6,7 ],
Cs = [0, -2, -4, 0].
As we use monotone code, we get logically sound answers for more general queries:
?- As = [X,Y], lists(As,Bs,Cs).
As = [X,Y], Bs = [X,Y], Cs = [ ], X in 1..sup, Y in 1..sup ;
As = [X,Y], Bs = [X ], Cs = [ Y], X in 1..sup, Y in inf..0 ;
As = [X,Y], Bs = [ Y], Cs = [X ], X in inf..0 , Y in 1..sup ;
As = [X,Y], Bs = [ ], Cs = [X,Y], X in inf..0 , Y in inf..0 .
Here you have. It splits a list, and does not matter if have odd or even items number.
div(L, A, B) :-
append(A, B, L),
length(A, N),
length(B, N).
div(L, A, B) :-
append(A, B, L),
length(A, N),
N1 is N + 1,
length(B, N1).
div(L, A, B) :-
append(A, B, L),
length(A, N),
N1 is N - 1,
length(B, N1).
Refer this:
domains
list=integer*
predicates
split(list,list,list)
clauses
split([],[],[]).
split([X|L],[X|L1],L2):-
X>= 0,
!,
split(L,L1,L2).
split([X|L],L1,[X|L2]):-
split(L,L1,L2).
Output :
Goal: split([1,2,-3,4,-5,2],X,Y)
Solution: X=[1,2,4,2], Y=[-3,-5]
See, if that helps.
Just for variety, this can also be done with a DCG, which is easy to read for a problem like this:
split([], []) --> [].
split([X|T], N) --> [X], { X >= 0 }, split(T, N).
split(P, [X|T]) --> [X], { X < 0 }, split(P, T).
split(L, A, B) :-
phrase(split(A, B), L).
As in:
| ?- split([1,2,-4,3,-5], A, B).
A = [1,2,3]
B = [-4,-5] ? ;
no
It also provides all the possible solutions in reverse:
| ?- split(L, [1,2,3], [-4,-5]).
L = [1,2,3,-4,-5] ? ;
L = [1,2,-4,3,-5] ? ;
L = [1,2,-4,-5,3] ? ;
L = [1,-4,2,3,-5] ? ;
L = [1,-4,2,-5,3] ? ;
L = [1,-4,-5,2,3] ? ;
L = [-4,1,2,3,-5] ? ;
L = [-4,1,2,-5,3] ? ;
L = [-4,1,-5,2,3] ? ;
L = [-4,-5,1,2,3] ? ;
(2 ms) no
Gaurav's solution will also do this if the cut is removed and an explicit X < 0 check placed in the third clause of the split/3 predicate.
There are several corrections to be done in your code.
If you enjoy compact (as readable) code, a possibility is
lists([],[],[]).
lists([X|Xs],Y,Z) :-
( X>0 -> (Y,Z)=([X|Ys],Zs) ; (Y,Z)=(Ys,[X|Zs]) ), lists(Xs,Ys,Zs).
But since (SWI)Prolog offers libraries to handle common list processing tasks, could be as easy as
lists(A,B,C) :- partition(<(0),A,B,C).

Prolog - How to find the maximum set of elements that their sum is equal to N

my game is about picking the max set of elements from a given list that their sum is N
example : L=[1,1,2,2,3,2,4,5,6], N = 6 , Sub List would be equal to [1,1,2,2]
I need a hint using constraint logic programming.
There is a library for Constrained Logic Programming in SWI-Prolog. It's called clpfd.
:-use_module(library(clpfd)).
Let's say that you'll have a variable for the length of the subsequence. Its domain goes from zero (corresponding to the empty subsequence) to the length of the list. In order to get the longest sequence first, values should be tried starting with the highest.
...
length(List, M),
L in 0..M,
labeling([max(L)],[L]),
...
Next, L can be used to build a list of L variables that would correspond to indices of elements from List. As these indices must be in ascending order, chain/2 can be used to create #</2 constraints between any two consecutive indices.
...
length(Indices, L),
Indices ins 1..M,
chain(Indices, #<),
...
Using these indices, a list with elements from List can be constructed. nth1/3 is useful here, but with a minor trick.
...
nth1a(List, N, E):-
nth1(N, List, E).
...
maplist(nth1a(List), Indices, SubSequence),
...
And the sum of that list must be N:
...
sum(SubSequence, #=, N)
...
As only the longest sequence is needed, once/1 can be used to stop after first solution is found.
Some example queries:
?- longest_subsequence([1,1,4,4,6], 9, S).
S = [1, 4, 4].
?- longest_subsequence([1,1,4,4,6], 11, S).
S = [1, 4, 6].
?- longest_subsequence([1,1,4,4,6], 21, S).
false.
As I am not sure if that's a homework or not, I won't post the full code here.
In this answer we use clpfd and a little lambda:
:- use_module([library(clpfd),
library(lambda)]).
Based on meta-predicate maplist/4 and the constraints (ins)/2 and sum/3 we define:
zs_selection_len_sum(Zs, Bs, L, S) :-
same_length(Zs, Bs),
Bs ins 0..1,
maplist(\Z^B^X^(X #= Z*B), Zs, Bs, Xs),
sum(Bs, #=, L),
sum(Xs, #=, S).
Sample queries using labeling/2 with option max/1:
?- zs_selection_len_sum([1,1,4,4,6],Bs,L,8), labeling([max(L)],Bs).
Bs = [1,1,0,0,1], L = 3
; Bs = [0,0,1,1,0], L = 2
; false.
?- zs_selection_len_sum([1,1,3,4,5],Bs,L,7), labeling([max(L)],Bs).
Bs = [1,1,0,0,1], L = 3
; Bs = [0,0,1,1,0], L = 2
; false.
?- zs_selection_len_sum([1,1,2,2,3,2,4,5,6],Bs,L,6), labeling([max(L)],Bs).
Bs = [1,1,0,1,0,1,0,0,0], L = 4
; Bs = [1,1,1,0,0,1,0,0,0], L = 4
; Bs = [1,1,1,1,0,0,0,0,0], L = 4
; Bs = [0,0,1,1,0,1,0,0,0], L = 3
; Bs = [0,1,0,0,1,1,0,0,0], L = 3
; Bs = [0,1,0,1,1,0,0,0,0], L = 3
; Bs = [0,1,1,0,1,0,0,0,0], L = 3
; Bs = [1,0,0,0,1,1,0,0,0], L = 3
; Bs = [1,0,0,1,1,0,0,0,0], L = 3
; Bs = [1,0,1,0,1,0,0,0,0], L = 3
; Bs = [1,1,0,0,0,0,1,0,0], L = 3
; Bs = [0,0,0,0,0,1,1,0,0], L = 2
; Bs = [0,0,0,1,0,0,1,0,0], L = 2
; Bs = [0,0,1,0,0,0,1,0,0], L = 2
; Bs = [0,1,0,0,0,0,0,1,0], L = 2
; Bs = [1,0,0,0,0,0,0,1,0], L = 2
; Bs = [0,0,0,0,0,0,0,0,1], L = 1
; false.

Resources