Parity of the number of inversions of a permutation

I think it is a quite popular problem. I have a permutation and I want to count how often a big number is left from a smaller one. More precisely I'm interested in whether this number is even or odd. That's for instance the criterion to decide whether Lloyd's shuffle puzzle is solvable or not. Example: 1 4 3 2 I can choose six pairs (respecting the order) of numbers out of it, namely (1,4) (1,3) (1,2) (4,3) (4,2) (3,2), where in the last three pairs the first member is greater than the second one. Thus I have 3 inversions and an odd parity. I' searching for a function which sorts the numbers and determines the parity of the number of inversions. I assume that there are elegant and fast algorithms for this problem (n * log n time steps), e.g. a merge sort algorithm. A brute force solution with quadratic time consumption is countInversions :: (Ord a) => [a] -> Int countInversions = sum . map (\(x:xs) -> length (filter (x>) xs)) . init . tails

On Wed, Mar 09, 2005 at 12:42:09PM +0100, Henning Thielemann wrote:
I think it is a quite popular problem. I have a permutation and I want to count how often a big number is left from a smaller one. More precisely I'm interested in whether this number is even or odd. That's for instance the criterion to decide whether Lloyd's shuffle puzzle is solvable or not. Example: 1 4 3 2 I can choose six pairs (respecting the order) of numbers out of it, namely (1,4) (1,3) (1,2) (4,3) (4,2) (3,2), where in the last three pairs the first member is greater than the second one. Thus I have 3 inversions and an odd parity. I'm searching for a function which sorts the numbers and determines the parity of the number of inversions. I assume that there are elegant and fast algorithms for this problem (n * log n time steps), e.g. a merge sort algorithm. A brute force solution with quadratic time consumption is countInversions :: (Ord a) => [a] -> Int countInversions = sum . map (\(x:xs) -> length (filter (x>) xs)) . init . tails
That's not a permutation, that's a cycle. Permutations are sets of disjoint cycles (which commute). -- wli

On Fri, 11 Mar 2005, William Lee Irwin III wrote:
On Wed, Mar 09, 2005 at 12:42:09PM +0100, Henning Thielemann wrote:
I'm searching for a function which sorts the numbers and determines the parity of the number of inversions. I assume that there are elegant and fast algorithms for this problem (n * log n time steps), e.g. a merge sort algorithm. A brute force solution with quadratic time consumption is countInversions :: (Ord a) => [a] -> Int countInversions = sum . map (\(x:xs) -> length (filter (x>) xs)) . init . tails
That's not a permutation, that's a cycle. Permutations are sets of disjoint cycles (which commute).
??? A permutation is a bijective function (here on a finite set), isn't it? Ok, the list representation is not immediately a permutation. But why a cycle?

Henning Thielemann wrote:
I' searching for a function which sorts the numbers and determines the parity of the number of inversions. I assume that there are elegant and fast algorithms for this problem (n * log n time steps), e.g. a merge sort algorithm.
This is a rather nice little problem. I think this works: countInversions :: (Ord a) => [a] -> Int countInversions [] = 0 countInversions xs = snd $ foldb merge [([x],0) | x <- xs] merge :: (Ord a) => ([a],Int) -> ([a],Int) -> ([a],Int) merge (xs,a) (ys,b) = case merge' (length xs) xs ys of (zs,c) -> (zs,a+b+c) merge' 0 [] ys = (ys,0) merge' n xs [] = (xs,0) merge' n (x:xs) (y:ys) = case compare x y of LT -> case merge' (n-1) xs (y:ys) of (zs,c) -> (x:zs,c) GT -> case merge' n (x:xs) ys of (zs,c) -> (y:zs,c+n) EQ -> undefined foldb :: (a -> a -> a) -> [a] -> a foldb f [] = undefined foldb f [x] = x foldb f xs = foldb f (foldb' f xs) foldb' f (x1:x2:xs) = f x1 x2 : foldb' f xs foldb' f xs = xs -- Ben

On Tue, 15 Mar 2005, Ben Rudiak-Gould wrote:
Henning Thielemann wrote:
I' searching for a function which sorts the numbers and determines the parity of the number of inversions. I assume that there are elegant and fast algorithms for this problem (n * log n time steps), e.g. a merge sort algorithm.
This is a rather nice little problem. I think this works:
countInversions :: (Ord a) => [a] -> Int
countInversions [] = 0 countInversions xs = snd $ foldb merge [([x],0) | x <- xs]
Yes, zipping together one-node lists is a nice idea to prevent dividing as in the classic divide&conquere scheme.
participants (3)
-
Ben Rudiak-Gould
-
Henning Thielemann
-
William Lee Irwin III