2

I have the following:

:-use_module(library(clpfd)).

list_index_value(List,Index,Value):-
  nth0(Index,List,Value).

length_conindexes_conrandomvector(Length,Conindexs,Randomvector):-
  length(Randomvector,Length),
  same_length(Conindexs,Ones),
  maplist(=(1),Ones),
  maplist(list_index_value(Randomvector),Conindexs,Ones),
  term_variables(Randomvector,Vars),
  maplist(random_between(0,1),Vars).

length_conindexes_notconrandomvector(Length,Conindexes,Randomvector):-
  length(Randomvector,Length),
  length(Conindexes,NumberOfCons),
  same_length(Conindexes,Values),
  sum(Values,#\=,NumberOfCons),
  maplist(list_index_value(Randomvector),Conindexes,Values),
  term_variables(Randomvector,Vars),
  repeat,
  maplist(random_between(0,1),Vars).

length_conindexes_conrandomvector/3 is used to generate a random vector of ones and zeros where the elements in the conindexes positions are 1s.

 ?-length_conindexes_conrandomvector(4,[0,1],R).
 R = [1, 1, 0, 1].

length_conindexes_notconrandomvector/3 is used to generate a random vector where NOT ALL of the conindexes are ones.

?- length_conindexes_notconrandomvector(3,[0,1,2],R).
R = [1, 0, 1] ;
R = [0, 1, 1] ;
R = [1, 1, 0] 

This I feel I have 'hacked' with the repeat command. What is the best way to do this? If I use labelling then the values will not be random? If the constraint is often violated then the search would be very inefficient. What is the best way to do this?

mat
  • 40,498
  • 3
  • 51
  • 78
user27815
  • 4,767
  • 14
  • 28

1 Answers1

3

In SWI-Prolog, I would do all this with CLP(B) constraints.

For example1:

:- use_module(library(clpb)).

length_conindices_notconrandomvector(L, Cs, Rs):-
        L #> 0,
        LMax #= L - 1,
        numlist(0, LMax, Is),
        pairs_keys_values(Pairs, Is, _),
        list_to_assoc(Pairs, A),
        maplist(assoc_index_value(A), Cs, Vs),
        sat(~ *(Vs)),
        assoc_to_values(A, Rs).

assoc_index_value(A, I, V) :- get_assoc(I, A, V).

Notice that I have also taken the liberty to turn the O(N2) method for fetching the needed elements into an O(N×log N) one.

Example query:

?- length_conindices_notconrandomvector(4, [0,1], Rs).
Rs = [X1, X2, X3, X4],
sat(1#X1*X2).

It is always advisable to separate the modeling part into its own predicate which we call the core relation. To obtain concrete solutions, you can for example use random_labeling/2:

?- length_conindices_notconrandomvector(4, [0,1], Rs),
   length(_, Seed),
   random_labeling(Seed, Rs).
Rs = [0, 1, 1, 1],
Seed = 0 ;
Rs = [1, 0, 0, 1],
Seed = 1 ;
Rs = [1, 0, 1, 1],
Seed = 2 ;
Rs = [1, 0, 0, 1],
Seed = 3 .

CLP(B)'s random_labeling/2 is implemented in such a way that each solution is equally likely.


1I am of course assuming that you have :- use_module(library(clpfd)). already in your ~/.swiplrc.
mat
  • 40,498
  • 3
  • 51
  • 78
  • 1
    Thanks once again for a great answer. – user27815 Apr 24 '16 at 08:54
  • 1
    SWI-Prolog's CLP(B) often does not scale very well when many variables are involved, but in this case we are lucky: The formula you need has a quite small BDD, and so this scales quite well. With a bit of practice, you will soon be able to judge when CLP(B) is applicable and when it is better to use CLP(FD) or other methods. In some of the tasks you posted earlier, SAT solvers based on other techniques may fare better than BDD-based CLP(B) systems. The point, as I see it, is to get a good grasp of different techniques that can be applied for different tasks. – mat Apr 24 '16 at 20:43