Why doesn't ord_subset generate subsets?

I’m interested in generating all subsets of an ordered set of a fixed length on backtracking.

What I get:

?- use_module(library(ordsets)).
true.
?- ord_subset(S, [1,2,3]).
S = [] ;
false.

What I hoped for:

?- ord_subset(S, [1,2,3]).
S = [] ;
S = [1] ;
S = [2] ;
S = [3] ;
S = [1, 2] ;
S = [2, 3] ;
S = [1, 3] ;
S = [1, 2, 3].

Has someone built a predicate that does this? Or maybe trying to do this to solve a problem is an anti-pattern that should be avoided?

1 Like

I figured out how to do this with a binary counter implemented in CLP(FD).

The idea is to take any number between 0 and 2^L-1 as a mask. If the mask divisible by 2, we omit the list element at that position, otherwise we include it. Then we divide the mask by 2 and continue to the next element in the list.

Backtracking over all possible masks gives us all possible sublists.

:- catch(use_module(library(clpz)), error(existence_error(_,_),_), use_module(library(clpfd))).
:- use_module(library(reif)).

mask_list_sublist(_, [], []).
mask_list_sublist(Mask, [H|T], Sublist) :-
    length([H|T], L),
    MaxMask #= 2^L - 1,
    Mask in 0..MaxMask,
    Include #= Mask mod 2,
    if_(
        Include = 1,
        Sublist = [H|NextSublist],
        Sublist = NextSublist
    ),
    NextMask #= Mask // 2,
    mask_list_sublist(NextMask, T, NextSublist).

list_sublist(List, Sublist) :-
    mask_list_sublist(_, List, Sublist).

This is perfectly general and works regardless of whether the list is a set or not, and even if no arguments are instantiated:

 ?- list_sublist([a,b,c], S).
S = [a, b, c] ;
S = [a, b] ;
S = [a, c] ;
S = [a] ;
S = [b, c] ;
S = [b] ;
S = [c] ;
S = [].
 ?- list_sublist(L, S).
L = S, S = [] ;
L = S, S = [_49782] ;
L = [_49782],
S = [] ;
L = S, S = [_49782, _49794] ;
L = [_49782, _49794],
S = [_49782] ;
L = [_49782, _49794],
S = [_49794] ;
L = [_49782, _49794],
S = [] ;
L = S, S = [_49782, _49794, _49800] ;
L = [_49782, _49794, _49800],
S = [_49782, _49794] ;
L = [_49782, _49794, _49800],
S = [_49782, _49800] ;
L = [_49782, _49794, _49800],
S = [_49782] ;
L = [_49782, _49794, _49800],
S = [_49794, _49800] ;
L = [_49782, _49794, _49800],
S = [_49794] ;
L = [_49782, _49794, _49800],
S = [_49800] ;
L = [_49782, _49794, _49800],
S = [] ;
...

The number of subsets will grow very fast with the size of the set, even if restricted to a specific length (number of subsets of a set of size N is 2N). So, probably an anti-pattern. :wink:

1 Like

@peter.ludemann I’m trying to solve a (toy) economics problem about a small market with goods and owners and utility functions.

The owners are represented as integers 1…N.
There are M goods, and ownership is represented as a list of length M (since we don’t care what the goods are). For example, [1,2,1] means the first good is owned by owner 1, the second good is owned by owner 2, and the third good is owned by owner 1 again.
The utility function is represented as a list of N lists of length M. It’s a matrix that shows some numeric utility that a particular owner associates with a particular good.


As the simplest possible example, consider Alice (owner 1) and Bob (owner 2). Alice owns an apple (good 1) and Bob owns a banana (good 2).

Ownership list: [1,2]

Alice is allergic to apples and likes bananas, and Bob is allergic to bananas and likes apples.

Utility matrix: [[0,1],[1,0]]

I’d like to write a Prolog program that shows that Alice and Bob will trade their fruits because the trade increases both of their utilities.

My thought of going about it was to split the goods by ownership, generate all possible pairs of owners, then generate all possible subsets of the goods belonging to those owners, sum up the utilities of each subset before and after a potential trade, and then do a trade iff the utility increases for both parties.

Do you have any pointers about how to approach solving this problem, if not with subset generation? Websites, articles, and book suggestions also welcome.

I am not sure if this helps you, but my spontaneous thought was that the representation below is more intuitive than the list of lists pattern (you could then swap out persons and things with integers in your real application, e.g. using between/3).

    precedes(TIME1, TIME2):- between(1, 3, TIME1), TIME2 is TIME1 + 1.

    %owns(PERSON, THING, TIME)
    owns(alice, apple, 1).
    owns(bob, banana, 1).

    %utility(PERSON, THING, UTILITY)
    utility(alice, apple, 0).
    utility(alice, banana, 1).
    utility(bob, apple, 1).
    utility(bob, banana, 0).

    trade(gets(PERSON1, THING1), gets(PERSON2, THING2), TIME2):-
        precedes(TIME1, TIME2),
        owns(PERSON2, THING1, TIME1),
        utility(PERSON2, THING1, 0),
        utility(PERSON1, THING1, 1),
        owns(PERSON1, THING2, TIME1),
        utility(PERSON1, THING2, 0),
        utility(PERSON2, THING2, 1),
        PERSON1 \= PERSON2,
        THING1 \= THING2.
1 Like

Thanks @JCR, your approach makes a lot of sense when you’re trying to solve a concrete problem, but I wanted to also use Prolog to reason about the problem in the abstract forwards and backwards. When a problem can be expressed in terms of lists of integers, elegant general solutions can sometimes be found with CLP. Take the famous N-queens for example.

@j4n_bur53 thanks a lot for the link! It didn’t occur to me to use a weighted maximum to solve the problem, but after looking it up it looks like CLP(FD) can also search for extrema via min(Expr) and max(Expr) options to labeling/2. So there’s lots for me to experiment with!

1 Like

This seems to have resolved in the meantime, but maybe still helpful info that I didn’t find in the thread.

Why doesn’t ord_subset generate subsets?

The technically correct answer is that it is not meant to do that. If you look at the docs, you will see that it says: ord_subset(+Sub, +Super). The plusses there mean that both arguments are “input” arguments. The meaning of those annotations is discussed in the docs as Notation of Predicate Descriptions.

You have a solution that works already. Another idea: since library(ordsets) represents a set as a sorted list without duplicates, a subset is a subsequence of that list. A simple implementation of a list subsequence in Prolog without arithmetic or CLP(FD) could go like this:

list_subseq(L, S) :-
    length(L, N),
    between(0, N, M),
    length(S, M),
    list_subseq_1(S, L).

list_subseq_1([], _).
list_subseq_1([X|Xs], L) :-
    append(_, [X|Rest], L),
    list_subseq_1(Xs, Rest).

This enumerates in order of subsequence length:

?- list_subseq([a,b,c], S).
S = [] ;
S = [a] ;
S = [b] ;
S = [c] ;
S = [a, b] ;
S = [a, c] ;
S = [b, c] ;
S = [a, b, c] ;
false.

?- list_subseq(L, S), numbervars(L-S).
L = S, S = [] ;
L = [A], S = [] ;
L = S, S = [A] ;
L = [A, B], S = [] ;
L = [A, B], S = [A] ;
L = [A, B], S = [B] ;
L = S, S = [A, B] ;
L = [A, B, C], S = [] ;
L = [A, B, C], S = [A] ;
L = [A, B, C], S = [B] ;
L = [A, B, C], S = [C] ;
L = [A, B, C], S = [A, B] ;
L = [A, B, C], S = [A, C] ;
L = [A, B, C], S = [B, C] ;
L = S, S = [A, B, C] ; % and so on

Of course I have no idea how this helps you with your larger problem at hand.

1 Like

That’s an awesome solution, @Boris, much shorter and cleaner than mine!

Thank you again @j4n_bur53, weighted_maximum is a great tool!

I had thought of this also but then realized it doesn’t work.
[1,3,5] is a subset of [1,2,3,4,5] but isn’t a sub-sequence.

The term “subsequence” is probably used differently in different fields. I meant it like this:

Note the difference to “substring”.

I hope I didn’t mess up the predicate definition though…

1 Like

I didn’t expect that CLP(B) and CLP(FD) would work together anyway, but thanks to your pointer, I got a similar demonstration to work in CLP(FD):

?- use_module(library(clpfd)).
true.

?- dif(Person1, Person2),
   tuples_in([[Person1, Weight1],[Person2, Weight2]], [[1,5],[2,-3],[3,7],[4,-9]]),
   TotalWeight #= Weight1 + Weight2,
   TotalWeight #< 10,
   once(labeling([max(TotalWeight)], [TotalWeight])).
TotalWeight = 4,
dif(Person1, Person2),
Person1 in 2..3,
tuples_in([[Person1, Weight1]], [[2, -3], [3, 7]]),
Person2 in 2..3,
tuples_in([[Person2, Weight2]], [[2, -3], [3, 7]]),
Weight2 in -3\/7,
Weight1+Weight2#=4,
Weight1 in -3\/7.