2

As someone who's new to Prolog, I'm looking to find out what a good way to count the number of inversions in a list.

I know how to flatten a matrix using flatten(Matrix, FlatMatrix), thus creating a variable that contains a single set of elements in the matrix. However, I'm unsure as to how to go about finding the number of inversions in that list.

From my understanding, the number of inversions in a matrix of numbers from 0...n is the total number of elements that are less than the number being compared (please correct me if I'm wrong on this).

I have a tiny bit of understanding of how setof/3 works in Prolog but I'd love to know a more efficient way to tackle the figuring out of the number of inversions in a flattened matrix. Variables in Prolog are strange to me so simple explanations would be best.

Thank you in advance!

repeat
  • 18,496
  • 4
  • 54
  • 166
Mitch
  • 53
  • 6

3 Answers3

2

First, I didn't quite get the meaning of what you were calling "inversion", so I'll stick to the quasi-canonical interpretation that @CapelliC used in his answer to this question.

Let's assume that all list items are integers, so we can use .

:- use_module(library(clpfd)).

z_z_order(X,Y,Op) :-
   zcompare(Op,X,Y).

To count the number of inversions (up-down direction changes), we do the following four steps:

  1. compare adjacent items (using mapadj/3, as defined at the very end of this answer)

    ?- Zs = [1,2,4,3,2,3,3,4,5,6,7,6,6,6,5,8], mapadj(z_z_order,Zs,Cs0).
    Zs  = [1,2,4,3,2,3,3,4,5,6,7,6,6,6,5,8],
    Cs0 = [ <,<,>,>,<,=,<,<,<,<,>,=,=,>,< ].
    
  2. eliminate all occurrences of = in Cs0 (using tfilter/3 and dif/3)

    ?- Cs0 = [<,<,>,>,<,=,<,<,<,<,>,=,=,>,<,<], tfilter(dif(=),Cs0,Cs1).
    Cs0 = [<,<,>,>,<,=,<,<,<,<,>,=,=,>,<,<],
    Cs1 = [<,<,>,>,<,  <,<,<,<,>,    >,<,<].
    
  3. get runs of equal items in Cs1 (using splitlistIfAdj/3 and dif/3)

    ?- Cs1 = [<,<,>,>,<,<,<,<,<,>,>,<,<], splitlistIfAdj(dif,Cs1,Cs).
    Cs1 = [ <,< , >,> , <,<,<,<,< , >,> , <,< ],
    Cs  = [[<,<],[>,>],[<,<,<,<,<],[>,>],[<,<]].
    
  4. the number of inversions is one less than the number of runs (using length/2 and (#=)/2)

    ?- Cs = [[<,<],[>,>],[<,<,<,<,<],[>,>],[<,<]], length(Cs,L), N #= max(0,L-1).
    Cs = [[<,<],[>,>],[<,<,<,<,<],[>,>],[<,<]], L = 5, N = 4.
    

That's it. Let's put it all together!

zs_invcount(Zs,N) :-
   mapadj(z_z_order,Zs,Cs0),
   tfilter(dif(=),Cs0,Cs1),
   splitlistIfAdj(dif,Cs1,Cs),
   length(Cs,L),
   N #= max(0,L-1).

Sample uses:

?- zs_invcount([1,2,3],0),    
   zs_invcount([1,2,3,2],1),    
   zs_invcount([1,2,3,3,2],1),               % works with duplicate items, too
   zs_invcount([1,2,3,3,2,1,1,1],1),
   zs_invcount([1,2,3,3,2,1,1,1,4,6],2),
   zs_invcount([1,2,3,3,2,1,1,1,4,6,9,1],3),
   zs_invcount([1,2,3,3,2,1,1,1,4,6,9,1,1],3).
true.

Implementation of mapadj/3

:- meta_predicate mapadj(3,?,?), list_prev_mapadj_list(?,?,3,?).
mapadj(P_3,[A|As],Bs) :-
   list_prev_mapadj_list(As,A,P_3,Bs).

list_prev_mapadj_list([]     ,_ , _ ,[]).
list_prev_mapadj_list([A1|As],A0,P_3,[B|Bs]) :-
   call(P_3,A0,A1,B),
   list_prev_mapadj_list(As,A1,P_3,Bs).
Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166
  • 1
    Nice solution! Also check out `automaton/8`: It lets you associate counters with state transitions of an automaton that describes a sequence. In this example, the sequence would consist of `>`, `<` and `=`, mapped to integers, for example `0`, `1` and `2`, related via CLP(FD) constraints to a sequence of integers for which these relations fit at the corresponding positions. – mat Aug 12 '15 at 21:20
  • 1
    @mat. Good idea! MyFirstAutomaton® (in clpfd). – repeat Aug 12 '15 at 21:24
1

Here's an alternative to my previous answer. It is based on and mapadj/3:

:- use_module(library(clpfd)).

Using tfilter/3, bool01_t/2, and sum/3 we define:

z_z_momsign(Z0,Z1,X) :-
   X #= max(-1,min(1,Z1-Z0)).

z_z_absmomsign(Z0,Z1,X) :-
   X #= min(1,abs(Z1-Z0)).

#\=(X,Y,Truth) :-
   X #\= Y #<==> B,
   bool01_t(B,Truth).

Finally, we define zs_invcount/2 like so:

zs_invcount(Zs,N) :-
   mapadj(z_z_momsign,Zs,Ms0),
   tfilter(#\=(0),Ms0,Ms),
   mapadj(z_z_absmomsign,Ms,Ds),
   sum(Ds,#=,N).

Sample use:

?- zs_invcount([1,2,3],0),    
   zs_invcount([1,2,3,2],1),    
   zs_invcount([1,2,3,3,2],1),               % works with duplicate items, too
   zs_invcount([1,2,3,3,2,1,1,1],1),
   zs_invcount([1,2,3,3,2,1,1,1,4,6],2),
   zs_invcount([1,2,3,3,2,1,1,1,4,6,9,1],3),
   zs_invcount([1,2,3,3,2,1,1,1,4,6,9,1,1],3).
true.

Edit

Consider the execution of following sample query in more detail:

?- zs_invcount([1,2,4,3,2,3,3,4,5,6,7,6,6,6,5,8],N).

Let's proceed step-by-step!

  1. For all adjacent list items, calculate the sign of their "momentum":

    ?- Zs = [1,2,4,3,2,3,3,4,5,6,7,6,6,6,5,8], mapadj(z_z_momsign,Zs,Ms0).
    Zs  = [1,2, 4,3, 2,3,3,4,5,6,7, 6,6,6, 5,8],
    Ms0 = [ 1,1,-1,-1,1,0,1,1,1,1,-1,0,0,-1,1 ].
    
  2. Eliminate all sign values of 0:

    ?- Ms0 = [1,1,-1,-1,1,0,1,1,1,1,-1,0,0,-1,1], tfilter(#\=(0),Ms0,Ms).
    Ms0 = [1,1,-1,-1,1,0,1,1,1,1,-1,0,0,-1,1],
    Ms  = [1,1,-1,-1,1,  1,1,1,1,-1,    -1,1].
    
  3. Get the "momentum inversions", i.e., absolute signs of the momentum of momentums.

    ?- Ms = [1,1,-1,-1,1,1,1,1,1,-1,-1,1], mapadj(z_z_absmomsign,Ms,Ds).
    Ms = [1,1,-1,-1,1,1,1,1,1,-1,-1,1],
    Ds = [ 0,1, 0, 1,0,0,0,0,1, 0, 1 ].
    
  4. Finally, sum up the number of "momentum inversions" using sum/3:

    ?- Ds = [0,1,0,1,0,0,0,0,1,0,1], sum(Ds,#=,N).
    N = 4, Ds = [0,1,0,1,0,0,0,0,1,0,1].
    

Or, alternatively, all steps at once:

:- Zs  = [1,2,4, 3, 2,3,3,4,5,6,7, 6,6,6, 5,8], mapadj(z_z_momsign,Zs,Ms0),
   Ms0 = [ 1,1,-1,-1,1,0,1,1,1,1,-1,0,0,-1,1 ], tfilter(#\=(0),Ms0,Ms),
   Ms  = [ 1,1,-1,-1,1,  1,1,1,1,-1,    -1,1 ], mapadj(z_z_absmomsign,Ms,Ds),
   Ds  = [  0,1, 0, 1, 0, 0,0,0,1,   0,   1  ], sum(Ds,#=,N),
   N   = 4.
Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166
0

a possible definition, attempting to keep it as simple as possible:

count_inversions(L, N) :-
    direction(L, D, L1),
    count_inversions(L1, D, 0, N).

direction([A,B|L], D, [B|L]) :-
    A > B -> D = down ; D = up.

count_inversions([_], _, N, N).
count_inversions(L, D, M, N) :-
    direction(L, D, L1),
    !, count_inversions(L1, D, M, N).
count_inversions(L, _, M, N) :-
    direction(L, D1, L1),
    M1 is M+1, count_inversions(L1, D1, M1, N).

The direction/3 predicate compares a pair of elements, determining if they are in ascending/descending order. Such information is passed down visiting the list, and if it cannot be matched, a counter is incremented (an accumulator, starting from 0). When the visit stops (the list has only 1 elements, then no direction can be determined), the accumulated counter is 'passed up' to be returned at the top level call.

I opted for a cut, instead of 'if/then/else' construct, so you can try to rewrite by yourself count_inversions/4 using it (you can see it used in direction/3). Beware of operators precedence!

note: direction/3 ignores the ambiguity inherent when A =:= B, and assigns 'up' to this case.

HTH

Salomon Zhang
  • 1,553
  • 3
  • 23
  • 41
CapelliC
  • 59,646
  • 5
  • 47
  • 90
  • Can you describe what the various elements are doing in these predicates? I understand the empty set base case, but the meaning behind the letters in the predicates is a little confusing. – Mitch Apr 17 '15 at 18:55
  • 1
    s(X): crafty, but somewhat brittle for lists containing adjacent duplicates (depending on the direction of the current run). e.g., `count_inversions([1,2,3,3,4,3],1)` succeeds, but `count_inversions([1,2,3,3,4,3,3],1)` fails. – repeat Aug 12 '15 at 21:07
  • The result for both of `count_inversions([8,2],N).` and `count_inversions([8,2],N).` is `N = 0`. – OmG May 21 '19 at 06:10
  • the number of inversion for both `[8,2]` and `[2,8]` is zero. For the former case should be `1`. Am I right? – OmG May 21 '19 at 06:47
  • @OmG: which *inversion* do you see in [8,2]? There is nothing in OP's question about ascending/descending sequences preferred reading – CapelliC May 21 '19 at 08:10
  • OK. good. I think a reasonable solution should work just for one of the ascending or descending in the meanwhile. So, one of `[8,2]` and `[2,8]` should have an inversion! Anyhow, I've just written my comment and nothing more. – OmG May 21 '19 at 17:51