{-# LANGUAGE CPP, BangPatterns, ScopedTypeVariables, GeneralizedNewtypeDeriving, FlexibleContexts #-}
module Math.Combinat.Permutations
(
Permutation (..)
, fromPermutation
, lookupPermutation , (!!!)
, permutationArray
, permutationUArray
, uarrayToPermutationUnsafe
, isPermutation
, maybePermutation
, toPermutation
, toPermutationUnsafe
, toPermutationUnsafeN
, permutationSize
, DisjointCycles (..)
, fromDisjointCycles
, disjointCyclesUnsafe
, permutationToDisjointCycles
, disjointCyclesToPermutation
, numberOfCycles
, concatPermutations
, isIdentityPermutation
, isReversePermutation
, isEvenPermutation
, isOddPermutation
, signOfPermutation
, signValueOfPermutation
, module Math.Combinat.Sign
, isCyclicPermutation
, transposition
, transpositions
, adjacentTransposition
, adjacentTranspositions
, cycleLeft
, cycleRight
, reversePermutation
, inversions
, numberOfInversions
, numberOfInversionsNaive
, numberOfInversionsMerge
, bubbleSort2
, bubbleSort
, identityPermutation
, inversePermutation
, multiplyPermutation
, productOfPermutations
, productOfPermutations'
, permuteArray
, permuteList
, permuteArrayLeft , permuteArrayRight
, permuteListLeft , permuteListRight
, sortingPermutationAsc
, sortingPermutationDesc
, asciiPermutation
, asciiDisjointCycles
, twoLineNotation
, inverseTwoLineNotation
, genericTwoLineNotation
, permutations
, _permutations
, permutationsNaive
, _permutationsNaive
, countPermutations
, randomPermutation
, _randomPermutation
, randomCyclicPermutation
, _randomCyclicPermutation
, randomPermutationDurstenfeld
, randomCyclicPermutationSattolo
, permuteMultiset
, countPermuteMultiset
, fasc2B_algorithm_L
)
where
import Control.Monad
import Control.Monad.ST
import Data.List hiding ( permutations )
import Data.Ord ( comparing )
import Data.Array (Array)
import Data.Array.ST
import Data.Array.Unboxed
import Data.Array.IArray
import Data.Array.MArray
import Data.Array.Unsafe
import Data.Vector.Compact.WordVec ( WordVec )
import qualified Data.Vector.Compact.WordVec as V
import Math.Combinat.ASCII
import Math.Combinat.Classes
import Math.Combinat.Helper
import Math.Combinat.Sign
import Math.Combinat.Numbers ( factorial , binomial )
import System.Random
toUArray :: WordVec -> UArray Int Int
toUArray :: WordVec -> UArray Int Int
toUArray WordVec
vec = forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [e] -> a i e
listArray (Int
1,Int
n) (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ WordVec -> [Word]
V.toList WordVec
vec) where n :: Int
n = WordVec -> Int
V.vecLen WordVec
vec
fromUArray :: UArray Int Int -> WordVec
fromUArray :: UArray Int Int -> WordVec
fromUArray UArray Int Int
arr = Int -> [Int] -> WordVec
fromPermListN Int
n (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
elems UArray Int Int
arr) where
(Int
1,Int
n) = forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
bounds UArray Int Int
arr
fromPermListN :: Int -> [Int] -> WordVec
fromPermListN :: Int -> [Int] -> WordVec
fromPermListN Int
n [Int]
perm = Shape -> [Word] -> WordVec
V.fromList' Shape
shape (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (Integral a, Num b) => a -> b
fromIntegral [Int]
perm) where
shape :: Shape
shape = Int -> Int -> Shape
V.Shape Int
n Int
bits
bits :: Int
bits = Word -> Int
V.bitsNeededFor (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n :: Word)
fromPermList :: [Int] -> WordVec
fromPermList :: [Int] -> WordVec
fromPermList [Int]
perm = [Word] -> WordVec
V.fromList (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (Integral a, Num b) => a -> b
fromIntegral [Int]
perm)
(.!) :: WordVec -> Int -> Int
.! :: WordVec -> Int -> Int
(.!) WordVec
vec Int
idx = forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> WordVec -> Word
V.unsafeIndex (Int
idxforall a. Num a => a -> a -> a
-Int
1) WordVec
vec)
_elems :: WordVec -> [Int]
_elems :: WordVec -> [Int]
_elems = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. WordVec -> [Word]
V.toList
_assocs :: WordVec -> [(Int,Int)]
_assocs :: WordVec -> [(Int, Int)]
_assocs WordVec
vec = forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] (WordVec -> [Int]
_elems WordVec
vec)
_bound :: WordVec -> Int
_bound :: WordVec -> Int
_bound = WordVec -> Int
V.vecLen
toPermN :: Int -> [Int] -> Permutation
toPermN :: Int -> [Int] -> Permutation
toPermN Int
n [Int]
xs = WordVec -> Permutation
Permutation (Int -> [Int] -> WordVec
fromPermListN Int
n [Int]
xs)
newtype Permutation = Permutation WordVec deriving (Permutation -> Permutation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Permutation -> Permutation -> Bool
$c/= :: Permutation -> Permutation -> Bool
== :: Permutation -> Permutation -> Bool
$c== :: Permutation -> Permutation -> Bool
Eq,Eq Permutation
Permutation -> Permutation -> Bool
Permutation -> Permutation -> Ordering
Permutation -> Permutation -> Permutation
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Permutation -> Permutation -> Permutation
$cmin :: Permutation -> Permutation -> Permutation
max :: Permutation -> Permutation -> Permutation
$cmax :: Permutation -> Permutation -> Permutation
>= :: Permutation -> Permutation -> Bool
$c>= :: Permutation -> Permutation -> Bool
> :: Permutation -> Permutation -> Bool
$c> :: Permutation -> Permutation -> Bool
<= :: Permutation -> Permutation -> Bool
$c<= :: Permutation -> Permutation -> Bool
< :: Permutation -> Permutation -> Bool
$c< :: Permutation -> Permutation -> Bool
compare :: Permutation -> Permutation -> Ordering
$ccompare :: Permutation -> Permutation -> Ordering
Ord)
instance Show Permutation where
showsPrec :: Int -> Permutation -> ShowS
showsPrec Int
d (Permutation WordVec
arr)
= Bool -> ShowS -> ShowS
showParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
10)
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"toPermutation " forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 (WordVec -> [Int]
_elems WordVec
arr)
instance Read Permutation where
readsPrec :: Int -> ReadS Permutation
readsPrec Int
d String
r = forall a. Bool -> ReadS a -> ReadS a
readParen (Int
d forall a. Ord a => a -> a -> Bool
> Int
10) ReadS Permutation
fun String
r where
fun :: ReadS Permutation
fun String
r = [ ([Int] -> Permutation
toPermutation [Int]
p,String
t)
| (String
"toPermutation",String
s) <- ReadS String
lex String
r
, ([Int]
p,String
t) <- forall a. Read a => Int -> ReadS a
readsPrec Int
11 String
s
]
instance DrawASCII Permutation where
ascii :: Permutation -> ASCII
ascii = Permutation -> ASCII
asciiPermutation
newtype DisjointCycles = DisjointCycles [[Int]] deriving (DisjointCycles -> DisjointCycles -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisjointCycles -> DisjointCycles -> Bool
$c/= :: DisjointCycles -> DisjointCycles -> Bool
== :: DisjointCycles -> DisjointCycles -> Bool
$c== :: DisjointCycles -> DisjointCycles -> Bool
Eq,Eq DisjointCycles
DisjointCycles -> DisjointCycles -> Bool
DisjointCycles -> DisjointCycles -> Ordering
DisjointCycles -> DisjointCycles -> DisjointCycles
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DisjointCycles -> DisjointCycles -> DisjointCycles
$cmin :: DisjointCycles -> DisjointCycles -> DisjointCycles
max :: DisjointCycles -> DisjointCycles -> DisjointCycles
$cmax :: DisjointCycles -> DisjointCycles -> DisjointCycles
>= :: DisjointCycles -> DisjointCycles -> Bool
$c>= :: DisjointCycles -> DisjointCycles -> Bool
> :: DisjointCycles -> DisjointCycles -> Bool
$c> :: DisjointCycles -> DisjointCycles -> Bool
<= :: DisjointCycles -> DisjointCycles -> Bool
$c<= :: DisjointCycles -> DisjointCycles -> Bool
< :: DisjointCycles -> DisjointCycles -> Bool
$c< :: DisjointCycles -> DisjointCycles -> Bool
compare :: DisjointCycles -> DisjointCycles -> Ordering
$ccompare :: DisjointCycles -> DisjointCycles -> Ordering
Ord,Int -> DisjointCycles -> ShowS
[DisjointCycles] -> ShowS
DisjointCycles -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisjointCycles] -> ShowS
$cshowList :: [DisjointCycles] -> ShowS
show :: DisjointCycles -> String
$cshow :: DisjointCycles -> String
showsPrec :: Int -> DisjointCycles -> ShowS
$cshowsPrec :: Int -> DisjointCycles -> ShowS
Show,ReadPrec [DisjointCycles]
ReadPrec DisjointCycles
Int -> ReadS DisjointCycles
ReadS [DisjointCycles]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisjointCycles]
$creadListPrec :: ReadPrec [DisjointCycles]
readPrec :: ReadPrec DisjointCycles
$creadPrec :: ReadPrec DisjointCycles
readList :: ReadS [DisjointCycles]
$creadList :: ReadS [DisjointCycles]
readsPrec :: Int -> ReadS DisjointCycles
$creadsPrec :: Int -> ReadS DisjointCycles
Read)
fromPermutation :: Permutation -> [Int]
fromPermutation :: Permutation -> [Int]
fromPermutation (Permutation WordVec
ar) = WordVec -> [Int]
_elems WordVec
ar
permutationUArray :: Permutation -> UArray Int Int
permutationUArray :: Permutation -> UArray Int Int
permutationUArray (Permutation WordVec
ar) = WordVec -> UArray Int Int
toUArray WordVec
ar
permutationArray :: Permutation -> Array Int Int
permutationArray :: Permutation -> Array Int Int
permutationArray (Permutation WordVec
ar) = forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [e] -> a i e
listArray (Int
1,Int
n) (WordVec -> [Int]
_elems WordVec
ar) where
n :: Int
n = WordVec -> Int
_bound WordVec
ar
toPermutationUnsafe :: [Int] -> Permutation
toPermutationUnsafe :: [Int] -> Permutation
toPermutationUnsafe [Int]
xs = WordVec -> Permutation
Permutation ([Int] -> WordVec
fromPermList [Int]
xs)
toPermutationUnsafeN :: Int -> [Int] -> Permutation
toPermutationUnsafeN :: Int -> [Int] -> Permutation
toPermutationUnsafeN Int
n [Int]
xs = WordVec -> Permutation
Permutation (Int -> [Int] -> WordVec
fromPermListN Int
n [Int]
xs)
uarrayToPermutationUnsafe :: UArray Int Int -> Permutation
uarrayToPermutationUnsafe :: UArray Int Int -> Permutation
uarrayToPermutationUnsafe = WordVec -> Permutation
Permutation forall b c a. (b -> c) -> (a -> b) -> a -> c
. UArray Int Int -> WordVec
fromUArray
isPermutation :: [Int] -> Bool
isPermutation :: [Int] -> Bool
isPermutation [Int]
xs = (UArray Int Int
arforall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!Int
0 forall a. Eq a => a -> a -> Bool
== Int
0) Bool -> Bool -> Bool
&& forall (t :: * -> *). Foldable t => t Bool -> Bool
and [ UArray Int Int
arforall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!Int
j forall a. Eq a => a -> a -> Bool
== Int
1 | Int
j<-[Int
1..Int
n] ] where
n :: Int
n = forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
xs
ar :: UArray Int Int
ar = (forall (a :: * -> * -> *) e i e'.
(IArray a e, Ix i) =>
(e -> e' -> e) -> e -> (i, i) -> [(i, e')] -> a i e
accumArray forall a. Num a => a -> a -> a
(+) Int
0 (Int
0,Int
n) forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map Int -> (Int, Int)
f [Int]
xs) :: UArray Int Int
f :: Int -> (Int,Int)
f :: Int -> (Int, Int)
f !Int
j = if Int
jforall a. Ord a => a -> a -> Bool
<Int
1 Bool -> Bool -> Bool
|| Int
jforall a. Ord a => a -> a -> Bool
>Int
n then (Int
0,Int
1) else (Int
j,Int
1)
maybePermutation :: [Int] -> Maybe Permutation
maybePermutation :: [Int] -> Maybe Permutation
maybePermutation [Int]
input = forall a. (forall s. ST s a) -> a
runST forall s. ST s (Maybe Permutation)
action where
n :: Int
n = forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
input
action :: forall s. ST s (Maybe Permutation)
action :: forall s. ST s (Maybe Permutation)
action = do
STUArray s Int Int
ar <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
newArray (Int
1,Int
n) Int
0 :: ST s (STUArray s Int Int)
let go :: [Int] -> m (Maybe Permutation)
go [] = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just ([Int] -> Permutation
toPermutationUnsafe [Int]
input)
go (Int
j:[Int]
js) = if Int
jforall a. Ord a => a -> a -> Bool
<Int
1 Bool -> Bool -> Bool
|| Int
jforall a. Ord a => a -> a -> Bool
>Int
n
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else do
Int
z <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Int
ar Int
j
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
ar Int
j (Int
zforall a. Num a => a -> a -> a
+Int
1)
if Int
zforall a. Eq a => a -> a -> Bool
==Int
0 then [Int] -> m (Maybe Permutation)
go [Int]
js
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
forall {m :: * -> *}.
MArray (STUArray s) Int m =>
[Int] -> m (Maybe Permutation)
go [Int]
input
toPermutation :: [Int] -> Permutation
toPermutation :: [Int] -> Permutation
toPermutation [Int]
xs = case [Int] -> Maybe Permutation
maybePermutation [Int]
xs of
Just Permutation
p -> Permutation
p
Maybe Permutation
Nothing -> forall a. HasCallStack => String -> a
error String
"toPermutation: not a permutation"
permutationSize :: Permutation -> Int
permutationSize :: Permutation -> Int
permutationSize (Permutation WordVec
ar) = WordVec -> Int
_bound WordVec
ar
lookupPermutation :: Permutation -> Int -> Int
lookupPermutation :: Permutation -> Int -> Int
lookupPermutation (Permutation WordVec
ar) Int
idx = WordVec
ar WordVec -> Int -> Int
.! Int
idx
(!!!) :: Permutation -> Int -> Int
!!! :: Permutation -> Int -> Int
(!!!) (Permutation WordVec
ar) Int
idx = WordVec
ar WordVec -> Int -> Int
.! Int
idx
instance HasWidth Permutation where
width :: Permutation -> Int
width = Permutation -> Int
permutationSize
isIdentityPermutation :: Permutation -> Bool
isIdentityPermutation :: Permutation -> Bool
isIdentityPermutation (Permutation WordVec
ar) = (WordVec -> [Int]
_elems WordVec
ar forall a. Eq a => a -> a -> Bool
== [Int
1..Int
n]) where
n :: Int
n = WordVec -> Int
_bound WordVec
ar
concatPermutations :: Permutation -> Permutation -> Permutation
concatPermutations :: Permutation -> Permutation -> Permutation
concatPermutations Permutation
perm1 Permutation
perm2 = [Int] -> Permutation
toPermutationUnsafe [Int]
list where
n :: Int
n = Permutation -> Int
permutationSize Permutation
perm1
list :: [Int]
list = Permutation -> [Int]
fromPermutation Permutation
perm1 forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map (forall a. Num a => a -> a -> a
+Int
n) (Permutation -> [Int]
fromPermutation Permutation
perm2)
asciiPermutation :: Permutation -> ASCII
asciiPermutation :: Permutation -> ASCII
asciiPermutation = Permutation -> ASCII
twoLineNotation
asciiDisjointCycles :: DisjointCycles -> ASCII
asciiDisjointCycles :: DisjointCycles -> ASCII
asciiDisjointCycles (DisjointCycles [[Int]]
cycles) = ASCII
final where
final :: ASCII
final = VAlign -> HSep -> [ASCII] -> ASCII
hCatWith VAlign
VTop (Int -> HSep
HSepSpaces Int
1) [ASCII]
boxes
boxes :: [ASCII]
boxes = [ [(Int, Int)] -> ASCII
genericTwoLineNotation (forall {a}. [a] -> [(a, a)]
f [Int]
cyc) | [Int]
cyc <- [[Int]]
cycles ]
f :: [a] -> [(a, a)]
f [a]
cyc = forall {a}. [a] -> [(a, a)]
pairs ([a]
cyc forall a. [a] -> [a] -> [a]
++ [forall a. [a] -> a
head [a]
cyc])
twoLineNotation :: Permutation -> ASCII
twoLineNotation :: Permutation -> ASCII
twoLineNotation (Permutation WordVec
arr) = [(Int, Int)] -> ASCII
genericTwoLineNotation forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] (WordVec -> [Int]
_elems WordVec
arr)
inverseTwoLineNotation :: Permutation -> ASCII
inverseTwoLineNotation :: Permutation -> ASCII
inverseTwoLineNotation (Permutation WordVec
arr) =
[(Int, Int)] -> ASCII
genericTwoLineNotation forall a b. (a -> b) -> a -> b
$ forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing forall a b. (a, b) -> b
snd) forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] (WordVec -> [Int]
_elems WordVec
arr)
genericTwoLineNotation :: [(Int,Int)] -> ASCII
genericTwoLineNotation :: [(Int, Int)] -> ASCII
genericTwoLineNotation [(Int, Int)]
xys = [String] -> ASCII
asciiFromLines [ String
topLine, String
botLine ] where
topLine :: String
topLine = String
"( " forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [[a]] -> [a]
intercalate String
" " [String]
us forall a. [a] -> [a] -> [a]
++ String
" )"
botLine :: String
botLine = String
"( " forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [[a]] -> [a]
intercalate String
" " [String]
vs forall a. [a] -> [a] -> [a]
++ String
" )"
pairs :: [(String, String)]
pairs = [ (forall a. Show a => a -> String
show Int
x, forall a. Show a => a -> String
show Int
y) | (Int
x,Int
y) <- [(Int, Int)]
xys ]
([String]
us,[String]
vs) = forall a b. [(a, b)] -> ([a], [b])
unzip (forall a b. (a -> b) -> [a] -> [b]
map (String, String) -> (String, String)
f [(String, String)]
pairs)
f :: (String, String) -> (String, String)
f (String
s,String
t) = (String
s',String
t') where
a :: Int
a = forall (t :: * -> *) a. Foldable t => t a -> Int
length String
s
b :: Int
b = forall (t :: * -> *) a. Foldable t => t a -> Int
length String
t
c :: Int
c = forall a. Ord a => a -> a -> a
max Int
a Int
b
s' :: String
s' = forall a. Int -> a -> [a]
replicate (Int
cforall a. Num a => a -> a -> a
-Int
a) Char
' ' forall a. [a] -> [a] -> [a]
++ String
s
t' :: String
t' = forall a. Int -> a -> [a]
replicate (Int
cforall a. Num a => a -> a -> a
-Int
b) Char
' ' forall a. [a] -> [a] -> [a]
++ String
t
fromDisjointCycles :: DisjointCycles -> [[Int]]
fromDisjointCycles :: DisjointCycles -> [[Int]]
fromDisjointCycles (DisjointCycles [[Int]]
cycles) = [[Int]]
cycles
disjointCyclesUnsafe :: [[Int]] -> DisjointCycles
disjointCyclesUnsafe :: [[Int]] -> DisjointCycles
disjointCyclesUnsafe = [[Int]] -> DisjointCycles
DisjointCycles
instance DrawASCII DisjointCycles where
ascii :: DisjointCycles -> ASCII
ascii = DisjointCycles -> ASCII
asciiDisjointCycles
instance HasNumberOfCycles DisjointCycles where
numberOfCycles :: DisjointCycles -> Int
numberOfCycles (DisjointCycles [[Int]]
cycles) = forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Int]]
cycles
instance HasNumberOfCycles Permutation where
numberOfCycles :: Permutation -> Int
numberOfCycles = forall p. HasNumberOfCycles p => p -> Int
numberOfCycles forall b c a. (b -> c) -> (a -> b) -> a -> c
. Permutation -> DisjointCycles
permutationToDisjointCycles
disjointCyclesToPermutation :: Int -> DisjointCycles -> Permutation
disjointCyclesToPermutation :: Int -> DisjointCycles -> Permutation
disjointCyclesToPermutation Int
n (DisjointCycles [[Int]]
cycles) = WordVec -> Permutation
Permutation forall a b. (a -> b) -> a -> b
$ UArray Int Int -> WordVec
fromUArray UArray Int Int
perm where
pairs :: [Int] -> [(Int,Int)]
pairs :: [Int] -> [(Int, Int)]
pairs xs :: [Int]
xs@(Int
x:[Int]
_) = forall {a}. [a] -> [(a, a)]
worker ([Int]
xsforall a. [a] -> [a] -> [a]
++[Int
x]) where
worker :: [b] -> [(b, b)]
worker (b
x:xs :: [b]
xs@(b
y:[b]
_)) = (b
x,b
y)forall a. a -> [a] -> [a]
:[b] -> [(b, b)]
worker [b]
xs
worker [b]
_ = []
pairs [] = forall a. HasCallStack => String -> a
error String
"disjointCyclesToPermutation: empty cycle"
perm :: UArray Int Int
perm = forall i e. (forall s. ST s (STUArray s i e)) -> UArray i e
runSTUArray forall a b. (a -> b) -> a -> b
$ do
STUArray s Int Int
ar <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
newArray_ (Int
1,Int
n) :: ST s (STUArray s Int Int)
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int
1..Int
n] forall a b. (a -> b) -> a -> b
$ \Int
i -> forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
ar Int
i Int
i
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [[Int]]
cycles forall a b. (a -> b) -> a -> b
$ \[Int]
cyc -> forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ ([Int] -> [(Int, Int)]
pairs [Int]
cyc) forall a b. (a -> b) -> a -> b
$ \(Int
i,Int
j) -> forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
ar Int
i Int
j
forall (m :: * -> *) a. Monad m => a -> m a
return STUArray s Int Int
ar
permutationToDisjointCycles :: Permutation -> DisjointCycles
permutationToDisjointCycles :: Permutation -> DisjointCycles
permutationToDisjointCycles (Permutation WordVec
perm) = DisjointCycles
res where
n :: Int
n = WordVec -> Int
_bound WordVec
perm
f :: [Int] -> Bool
f :: [Int] -> Bool
f [Int
_] = Bool
False
f [Int]
_ = Bool
True
res :: DisjointCycles
res = forall a. (forall s. ST s a) -> a
runST forall a b. (a -> b) -> a -> b
$ do
STUArray s Int Bool
tag <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
newArray (Int
1,Int
n) Bool
False
[[Int]]
cycles <- forall (m :: * -> *) b a.
Monad m =>
(b -> m (a, Maybe b)) -> b -> m [a]
unfoldM (forall s. STUArray s Int Bool -> Int -> ST s ([Int], Maybe Int)
step STUArray s Int Bool
tag) Int
1
forall (m :: * -> *) a. Monad m => a -> m a
return ([[Int]] -> DisjointCycles
DisjointCycles forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter [Int] -> Bool
f [[Int]]
cycles)
step :: STUArray s Int Bool -> Int -> ST s ([Int],Maybe Int)
step :: forall s. STUArray s Int Bool -> Int -> ST s ([Int], Maybe Int)
step STUArray s Int Bool
tag Int
k = do
[Int]
cyc <- forall s. STUArray s Int Bool -> Int -> Int -> [Int] -> ST s [Int]
worker STUArray s Int Bool
tag Int
k Int
k [Int
k]
Maybe Int
m <- forall s. STUArray s Int Bool -> Int -> ST s (Maybe Int)
next STUArray s Int Bool
tag (Int
kforall a. Num a => a -> a -> a
+Int
1)
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. [a] -> [a]
reverse [Int]
cyc, Maybe Int
m)
next :: STUArray s Int Bool -> Int -> ST s (Maybe Int)
next :: forall s. STUArray s Int Bool -> Int -> ST s (Maybe Int)
next STUArray s Int Bool
tag Int
k = if Int
k forall a. Ord a => a -> a -> Bool
> Int
n
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Bool
tag Int
k forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
b -> if Bool
b
then forall s. STUArray s Int Bool -> Int -> ST s (Maybe Int)
next STUArray s Int Bool
tag (Int
kforall a. Num a => a -> a -> a
+Int
1)
else forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just Int
k)
worker :: STUArray s Int Bool -> Int -> Int -> [Int] -> ST s [Int]
worker :: forall s. STUArray s Int Bool -> Int -> Int -> [Int] -> ST s [Int]
worker STUArray s Int Bool
tag Int
k Int
l [Int]
cyc = do
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Bool
tag Int
l Bool
True
let m :: Int
m = WordVec
perm WordVec -> Int -> Int
.! Int
l
if Int
m forall a. Eq a => a -> a -> Bool
== Int
k
then forall (m :: * -> *) a. Monad m => a -> m a
return [Int]
cyc
else forall s. STUArray s Int Bool -> Int -> Int -> [Int] -> ST s [Int]
worker STUArray s Int Bool
tag Int
k Int
m (Int
mforall a. a -> [a] -> [a]
:[Int]
cyc)
isEvenPermutation :: Permutation -> Bool
isEvenPermutation :: Permutation -> Bool
isEvenPermutation (Permutation WordVec
perm) = Bool
res where
n :: Int
n = WordVec -> Int
_bound WordVec
perm
res :: Bool
res = forall a. (forall s. ST s a) -> a
runST forall a b. (a -> b) -> a -> b
$ do
STUArray s Int Bool
tag <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
newArray (Int
1,Int
n) Bool
False
[Int]
cycles <- forall (m :: * -> *) b a.
Monad m =>
(b -> m (a, Maybe b)) -> b -> m [a]
unfoldM (forall s. STUArray s Int Bool -> Int -> ST s (Int, Maybe Int)
step STUArray s Int Bool
tag) Int
1
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Integral a => a -> Bool
even (forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Int]
cycles)
step :: STUArray s Int Bool -> Int -> ST s (Int,Maybe Int)
step :: forall s. STUArray s Int Bool -> Int -> ST s (Int, Maybe Int)
step STUArray s Int Bool
tag Int
k = do
Int
cyclen <- forall s. STUArray s Int Bool -> Int -> Int -> Int -> ST s Int
worker STUArray s Int Bool
tag Int
k Int
k Int
0
Maybe Int
m <- forall s. STUArray s Int Bool -> Int -> ST s (Maybe Int)
next STUArray s Int Bool
tag (Int
kforall a. Num a => a -> a -> a
+Int
1)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
cyclen,Maybe Int
m)
next :: STUArray s Int Bool -> Int -> ST s (Maybe Int)
next :: forall s. STUArray s Int Bool -> Int -> ST s (Maybe Int)
next STUArray s Int Bool
tag Int
k = if Int
k forall a. Ord a => a -> a -> Bool
> Int
n
then forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Bool
tag Int
k forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
b -> if Bool
b
then forall s. STUArray s Int Bool -> Int -> ST s (Maybe Int)
next STUArray s Int Bool
tag (Int
kforall a. Num a => a -> a -> a
+Int
1)
else forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just Int
k)
worker :: STUArray s Int Bool -> Int -> Int -> Int -> ST s Int
worker :: forall s. STUArray s Int Bool -> Int -> Int -> Int -> ST s Int
worker STUArray s Int Bool
tag Int
k Int
l Int
cyclen = do
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Bool
tag Int
l Bool
True
let m :: Int
m = WordVec
perm WordVec -> Int -> Int
.! Int
l
if Int
m forall a. Eq a => a -> a -> Bool
== Int
k
then forall (m :: * -> *) a. Monad m => a -> m a
return Int
cyclen
else forall s. STUArray s Int Bool -> Int -> Int -> Int -> ST s Int
worker STUArray s Int Bool
tag Int
k Int
m (Int
1forall a. Num a => a -> a -> a
+Int
cyclen)
isOddPermutation :: Permutation -> Bool
isOddPermutation :: Permutation -> Bool
isOddPermutation = Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Permutation -> Bool
isEvenPermutation
signOfPermutation :: Permutation -> Sign
signOfPermutation :: Permutation -> Sign
signOfPermutation Permutation
perm = case Permutation -> Bool
isEvenPermutation Permutation
perm of
Bool
True -> Sign
Plus
Bool
False -> Sign
Minus
{-# SPECIALIZE signValueOfPermutation :: Permutation -> Int #-}
{-# SPECIALIZE signValueOfPermutation :: Permutation -> Integer #-}
signValueOfPermutation :: Num a => Permutation -> a
signValueOfPermutation :: forall a. Num a => Permutation -> a
signValueOfPermutation = forall a. Num a => Sign -> a
signValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. Permutation -> Sign
signOfPermutation
isCyclicPermutation :: Permutation -> Bool
isCyclicPermutation :: Permutation -> Bool
isCyclicPermutation Permutation
perm =
case [[Int]]
cycles of
[] -> Bool
True
[[Int]
cyc] -> (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
cyc forall a. Eq a => a -> a -> Bool
== Int
n)
[[Int]]
_ -> Bool
False
where
n :: Int
n = Permutation -> Int
permutationSize Permutation
perm
DisjointCycles [[Int]]
cycles = Permutation -> DisjointCycles
permutationToDisjointCycles Permutation
perm
inversions :: Permutation -> [(Int,Int)]
inversions :: Permutation -> [(Int, Int)]
inversions (Permutation WordVec
arr) = [(Int, Int)]
list where
n :: Int
n = WordVec -> Int
_bound WordVec
arr
list :: [(Int, Int)]
list = [ (Int
i,Int
j) | Int
i<-[Int
1..Int
nforall a. Num a => a -> a -> a
-Int
1], Int
j<-[Int
iforall a. Num a => a -> a -> a
+Int
1..Int
n], WordVec
arrWordVec -> Int -> Int
.!Int
i forall a. Ord a => a -> a -> Bool
> WordVec
arrWordVec -> Int -> Int
.!Int
j ]
numberOfInversions :: Permutation -> Int
numberOfInversions :: Permutation -> Int
numberOfInversions = Permutation -> Int
numberOfInversionsMerge
numberOfInversionsMerge :: Permutation -> Int
numberOfInversionsMerge :: Permutation -> Int
numberOfInversionsMerge (Permutation WordVec
arr) = forall a b. (a, b) -> a
fst (Int -> [Int] -> (Int, [Int])
sortCnt Int
n forall a b. (a -> b) -> a -> b
$ WordVec -> [Int]
_elems WordVec
arr) where
n :: Int
n = WordVec -> Int
_bound WordVec
arr
sortCnt :: Int -> [Int] -> (Int,[Int])
sortCnt :: Int -> [Int] -> (Int, [Int])
sortCnt Int
0 [Int]
_ = (Int
0,[] )
sortCnt Int
1 [Int
x] = (Int
0,[Int
x])
sortCnt Int
2 [Int
x,Int
y] = if Int
xforall a. Ord a => a -> a -> Bool
>Int
y then (Int
1,[Int
y,Int
x]) else (Int
0,[Int
x,Int
y])
sortCnt Int
n [Int]
xs = (Int, [Int]) -> (Int, [Int]) -> (Int, [Int])
mergeCnt (Int -> [Int] -> (Int, [Int])
sortCnt Int
k [Int]
us) (Int -> [Int] -> (Int, [Int])
sortCnt Int
l [Int]
vs) where
k :: Int
k = forall a. Integral a => a -> a -> a
div Int
n Int
2
l :: Int
l = Int
n forall a. Num a => a -> a -> a
- Int
k
([Int]
us,[Int]
vs) = forall a. Int -> [a] -> ([a], [a])
splitAt Int
k [Int]
xs
mergeCnt :: (Int,[Int]) -> (Int,[Int]) -> (Int,[Int])
mergeCnt :: (Int, [Int]) -> (Int, [Int]) -> (Int, [Int])
mergeCnt (!Int
c,[Int]
us) (!Int
d,[Int]
vs) = (Int
cforall a. Num a => a -> a -> a
+Int
dforall a. Num a => a -> a -> a
+Int
e,[Int]
ws) where
(Int
e,[Int]
ws) = forall {a}. Ord a => Int -> [a] -> [a] -> (Int, [a])
go Int
0 [Int]
us [Int]
vs
go :: Int -> [a] -> [a] -> (Int, [a])
go !Int
k [a]
xs [] = ( Int
kforall a. Num a => a -> a -> a
*forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
xs , [a]
xs )
go Int
_ [] [a]
ys = ( Int
0 , [a]
ys)
go !Int
k xxs :: [a]
xxs@(a
x:[a]
xs) yys :: [a]
yys@(a
y:[a]
ys) = if a
x forall a. Ord a => a -> a -> Bool
< a
y
then let (Int
a,[a]
zs) = Int -> [a] -> [a] -> (Int, [a])
go Int
k [a]
xs [a]
yys in (Int
aforall a. Num a => a -> a -> a
+Int
k, a
xforall a. a -> [a] -> [a]
:[a]
zs)
else let (Int
a,[a]
zs) = Int -> [a] -> [a] -> (Int, [a])
go (Int
kforall a. Num a => a -> a -> a
+Int
1) [a]
xxs [a]
ys in (Int
a , a
yforall a. a -> [a] -> [a]
:[a]
zs)
numberOfInversionsNaive :: Permutation -> Int
numberOfInversionsNaive :: Permutation -> Int
numberOfInversionsNaive (Permutation WordVec
arr) = forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
list where
n :: Int
n = WordVec -> Int
_bound WordVec
arr
list :: [Int]
list = [ (Int
0::Int) | Int
i<-[Int
1..Int
nforall a. Num a => a -> a -> a
-Int
1], Int
j<-[Int
iforall a. Num a => a -> a -> a
+Int
1..Int
n], WordVec
arrWordVec -> Int -> Int
.!Int
i forall a. Ord a => a -> a -> Bool
> WordVec
arrWordVec -> Int -> Int
.!Int
j ]
bubbleSort2 :: Permutation -> [(Int,Int)]
bubbleSort2 :: Permutation -> [(Int, Int)]
bubbleSort2 = forall a b. (a -> b) -> [a] -> [b]
map forall {b}. Num b => b -> (b, b)
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. Permutation -> [Int]
bubbleSort where f :: b -> (b, b)
f b
i = (b
i,b
iforall a. Num a => a -> a -> a
+b
1)
bubbleSort :: Permutation -> [Int]
bubbleSort :: Permutation -> [Int]
bubbleSort perm :: Permutation
perm@(Permutation WordVec
tgt) = forall a. (forall s. ST s a) -> a
runST forall s. ST s [Int]
action where
n :: Int
n = WordVec -> Int
_bound WordVec
tgt
action :: forall s. ST s [Int]
action :: forall s. ST s [Int]
action = do
STUArray s Int Int
fwd <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
newArray_ (Int
1,Int
n) :: ST s (STUArray s Int Int)
STUArray s Int Int
inv <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
newArray_ (Int
1,Int
n) :: ST s (STUArray s Int Int)
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int
1..Int
n] forall a b. (a -> b) -> a -> b
$ \Int
i -> forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
fwd Int
i Int
i
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int
1..Int
n] forall a b. (a -> b) -> a -> b
$ \Int
i -> forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
inv Int
i Int
i
[[Int]]
list <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Int
1..Int
n] forall a b. (a -> b) -> a -> b
$ \Int
x -> do
let k :: Int
k = WordVec
tgt WordVec -> Int -> Int
.! Int
x
Int
i <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Int
inv Int
k
let j :: Int
j = Int
x
let swaps :: [Int]
swaps = Int -> Int -> [Int]
move Int
i Int
j
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int]
swaps forall a b. (a -> b) -> a -> b
$ \Int
y -> do
Int
a <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Int
fwd Int
y
Int
b <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Int
fwd (Int
yforall a. Num a => a -> a -> a
+Int
1)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
fwd (Int
yforall a. Num a => a -> a -> a
+Int
1) Int
a
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
fwd Int
y Int
b
Int
u <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Int
inv Int
a
Int
v <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Int
inv Int
b
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
inv Int
b Int
u
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
inv Int
a Int
v
forall (m :: * -> *) a. Monad m => a -> m a
return [Int]
swaps
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Int]]
list)
move :: Int -> Int -> [Int]
move :: Int -> Int -> [Int]
move !Int
i !Int
j
| Int
j forall a. Eq a => a -> a -> Bool
== Int
i = []
| Int
j forall a. Ord a => a -> a -> Bool
> Int
i = [Int
i..Int
jforall a. Num a => a -> a -> a
-Int
1]
| Int
j forall a. Ord a => a -> a -> Bool
< Int
i = [Int
iforall a. Num a => a -> a -> a
-Int
1,Int
iforall a. Num a => a -> a -> a
-Int
2..Int
j]
reversePermutation :: Int -> Permutation
reversePermutation :: Int -> Permutation
reversePermutation Int
n = WordVec -> Permutation
Permutation forall a b. (a -> b) -> a -> b
$ Int -> [Int] -> WordVec
fromPermListN Int
n [Int
n,Int
nforall a. Num a => a -> a -> a
-Int
1..Int
1]
isReversePermutation :: Permutation -> Bool
isReversePermutation :: Permutation -> Bool
isReversePermutation (Permutation WordVec
arr) = WordVec -> [Int]
_elems WordVec
arr forall a. Eq a => a -> a -> Bool
== [Int
n,Int
nforall a. Num a => a -> a -> a
-Int
1..Int
1] where n :: Int
n = WordVec -> Int
_bound WordVec
arr
transposition :: Int -> (Int,Int) -> Permutation
transposition :: Int -> (Int, Int) -> Permutation
transposition Int
n (Int
i,Int
j) =
if Int
iforall a. Ord a => a -> a -> Bool
>=Int
1 Bool -> Bool -> Bool
&& Int
jforall a. Ord a => a -> a -> Bool
>=Int
1 Bool -> Bool -> Bool
&& Int
iforall a. Ord a => a -> a -> Bool
<=Int
n Bool -> Bool -> Bool
&& Int
jforall a. Ord a => a -> a -> Bool
<=Int
n
then WordVec -> Permutation
Permutation forall a b. (a -> b) -> a -> b
$ Int -> [Int] -> WordVec
fromPermListN Int
n [ Int -> Int
f Int
k | Int
k<-[Int
1..Int
n] ]
else forall a. HasCallStack => String -> a
error String
"transposition: index out of range"
where
f :: Int -> Int
f Int
k | Int
k forall a. Eq a => a -> a -> Bool
== Int
i = Int
j
| Int
k forall a. Eq a => a -> a -> Bool
== Int
j = Int
i
| Bool
otherwise = Int
k
transpositions :: Int -> [(Int,Int)] -> Permutation
transpositions :: Int -> [(Int, Int)] -> Permutation
transpositions Int
n [(Int, Int)]
list = WordVec -> Permutation
Permutation (UArray Int Int -> WordVec
fromUArray forall a b. (a -> b) -> a -> b
$ forall i e. (forall s. ST s (STUArray s i e)) -> UArray i e
runSTUArray forall s. ST s (STUArray s Int Int)
action) where
action :: ST s (STUArray s Int Int)
action :: forall s. ST s (STUArray s Int Int)
action = do
STUArray s Int Int
arr <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
newArray_ (Int
1,Int
n)
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int
1..Int
n] forall a b. (a -> b) -> a -> b
$ \Int
i -> forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
arr Int
i Int
i
let doSwap :: (Int, Int) -> m ()
doSwap (Int
i,Int
j) = do
Int
u <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Int
arr Int
i
Int
v <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Int
arr Int
j
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
arr Int
i Int
v
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
arr Int
j Int
u
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ forall {m :: * -> *}.
MArray (STUArray s) Int m =>
(Int, Int) -> m ()
doSwap [(Int, Int)]
list
forall (m :: * -> *) a. Monad m => a -> m a
return STUArray s Int Int
arr
adjacentTransposition :: Int -> Int -> Permutation
adjacentTransposition :: Int -> Int -> Permutation
adjacentTransposition Int
n Int
k
| Int
kforall a. Ord a => a -> a -> Bool
>Int
0 Bool -> Bool -> Bool
&& Int
kforall a. Ord a => a -> a -> Bool
<Int
n = Int -> (Int, Int) -> Permutation
transposition Int
n (Int
k,Int
kforall a. Num a => a -> a -> a
+Int
1)
| Bool
otherwise = forall a. HasCallStack => String -> a
error String
"adjacentTransposition: index out of range"
adjacentTranspositions :: Int -> [Int] -> Permutation
adjacentTranspositions :: Int -> [Int] -> Permutation
adjacentTranspositions Int
n [Int]
list = WordVec -> Permutation
Permutation (UArray Int Int -> WordVec
fromUArray forall a b. (a -> b) -> a -> b
$ forall i e. (forall s. ST s (STUArray s i e)) -> UArray i e
runSTUArray forall s. ST s (STUArray s Int Int)
action) where
action :: ST s (STUArray s Int Int)
action :: forall s. ST s (STUArray s Int Int)
action = do
STUArray s Int Int
arr <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
newArray_ (Int
1,Int
n)
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int
1..Int
n] forall a b. (a -> b) -> a -> b
$ \Int
i -> forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
arr Int
i Int
i
let doSwap :: Int -> m ()
doSwap Int
i
| Int
iforall a. Ord a => a -> a -> Bool
<Int
0 Bool -> Bool -> Bool
|| Int
iforall a. Ord a => a -> a -> Bool
>=Int
n = forall a. HasCallStack => String -> a
error String
"adjacentTranspositions: index out of range"
| Bool
otherwise = do
Int
u <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Int
arr Int
i
Int
v <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Int
arr (Int
iforall a. Num a => a -> a -> a
+Int
1)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
arr Int
i Int
v
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
arr (Int
iforall a. Num a => a -> a -> a
+Int
1) Int
u
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ forall {m :: * -> *}. MArray (STUArray s) Int m => Int -> m ()
doSwap [Int]
list
forall (m :: * -> *) a. Monad m => a -> m a
return STUArray s Int Int
arr
cycleLeft :: Int -> Permutation
cycleLeft :: Int -> Permutation
cycleLeft Int
n = WordVec -> Permutation
Permutation forall a b. (a -> b) -> a -> b
$ Int -> [Int] -> WordVec
fromPermListN Int
n ([Int
2..Int
n] forall a. [a] -> [a] -> [a]
++ [Int
1])
cycleRight :: Int -> Permutation
cycleRight :: Int -> Permutation
cycleRight Int
n = WordVec -> Permutation
Permutation forall a b. (a -> b) -> a -> b
$ Int -> [Int] -> WordVec
fromPermListN Int
n (Int
n forall a. a -> [a] -> [a]
: [Int
1..Int
nforall a. Num a => a -> a -> a
-Int
1])
multiplyPermutation :: Permutation -> Permutation -> Permutation
multiplyPermutation :: Permutation -> Permutation -> Permutation
multiplyPermutation pi1 :: Permutation
pi1@(Permutation WordVec
perm1) pi2 :: Permutation
pi2@(Permutation WordVec
perm2) =
if (Int
nforall a. Eq a => a -> a -> Bool
==Int
m)
then WordVec -> Permutation
Permutation forall a b. (a -> b) -> a -> b
$ UArray Int Int -> WordVec
fromUArray UArray Int Int
result
else forall a. HasCallStack => String -> a
error String
"multiplyPermutation: permutations of different sets"
where
n :: Int
n = WordVec -> Int
_bound WordVec
perm1
m :: Int
m = WordVec -> Int
_bound WordVec
perm2
result :: UArray Int Int
result = forall (arr :: * -> * -> *) b.
IArray arr b =>
Permutation -> arr Int b -> arr Int b
permuteArray Permutation
pi2 (WordVec -> UArray Int Int
toUArray WordVec
perm1)
infixr 7 `multiplyPermutation`
inversePermutation :: Permutation -> Permutation
inversePermutation :: Permutation -> Permutation
inversePermutation (Permutation WordVec
perm1) = WordVec -> Permutation
Permutation forall a b. (a -> b) -> a -> b
$ UArray Int Int -> WordVec
fromUArray UArray Int Int
result
where
result :: UArray Int Int
result = forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(i, e)] -> a i e
array (Int
1,Int
n) forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> (b, a)
swap forall a b. (a -> b) -> a -> b
$ WordVec -> [(Int, Int)]
_assocs WordVec
perm1
n :: Int
n = WordVec -> Int
_bound WordVec
perm1
identityPermutation :: Int -> Permutation
identityPermutation :: Int -> Permutation
identityPermutation Int
n = WordVec -> Permutation
Permutation forall a b. (a -> b) -> a -> b
$ Int -> [Int] -> WordVec
fromPermListN Int
n [Int
1..Int
n]
productOfPermutations :: [Permutation] -> Permutation
productOfPermutations :: [Permutation] -> Permutation
productOfPermutations [] = forall a. HasCallStack => String -> a
error String
"productOfPermutations: empty list, we don't know size of the result"
productOfPermutations [Permutation]
ps = forall a. (a -> a -> a) -> [a] -> a
foldl1' Permutation -> Permutation -> Permutation
multiplyPermutation [Permutation]
ps
productOfPermutations' :: Int -> [Permutation] -> Permutation
productOfPermutations' :: Int -> [Permutation] -> Permutation
productOfPermutations' Int
n [] = Int -> Permutation
identityPermutation Int
n
productOfPermutations' Int
n ps :: [Permutation]
ps@(Permutation
p:[Permutation]
_) = if Int
n forall a. Eq a => a -> a -> Bool
== Permutation -> Int
permutationSize Permutation
p
then forall a. (a -> a -> a) -> [a] -> a
foldl1' Permutation -> Permutation -> Permutation
multiplyPermutation [Permutation]
ps
else forall a. HasCallStack => String -> a
error String
"productOfPermutations': incompatible permutation size(s)"
{-# SPECIALIZE permuteArray :: Permutation -> Array Int b -> Array Int b #-}
{-# SPECIALIZE permuteArray :: Permutation -> UArray Int Int -> UArray Int Int #-}
permuteArray :: IArray arr b => Permutation -> arr Int b -> arr Int b
permuteArray :: forall (arr :: * -> * -> *) b.
IArray arr b =>
Permutation -> arr Int b -> arr Int b
permuteArray = forall (arr :: * -> * -> *) b.
IArray arr b =>
Permutation -> arr Int b -> arr Int b
permuteArrayRight
permuteList :: Permutation -> [a] -> [a]
permuteList :: forall a. Permutation -> [a] -> [a]
permuteList = forall a. Permutation -> [a] -> [a]
permuteListRight
{-# SPECIALIZE permuteArrayRight :: Permutation -> Array Int b -> Array Int b #-}
{-# SPECIALIZE permuteArrayRight :: Permutation -> UArray Int Int -> UArray Int Int #-}
permuteArrayRight :: IArray arr b => Permutation -> arr Int b -> arr Int b
permuteArrayRight :: forall (arr :: * -> * -> *) b.
IArray arr b =>
Permutation -> arr Int b -> arr Int b
permuteArrayRight pi :: Permutation
pi@(Permutation WordVec
perm) arr Int b
ar =
if (Int
aforall a. Eq a => a -> a -> Bool
==Int
1) Bool -> Bool -> Bool
&& (Int
bforall a. Eq a => a -> a -> Bool
==Int
n)
then forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [e] -> a i e
listArray (Int
1,Int
n) [ arr Int b
arforall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!(WordVec
permWordVec -> Int -> Int
.!Int
i) | Int
i <- [Int
1..Int
n] ]
else forall a. HasCallStack => String -> a
error String
"permuteArrayRight: array bounds do not match"
where
n :: Int
n = WordVec -> Int
_bound WordVec
perm
(Int
a,Int
b) = forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
bounds arr Int b
ar
permuteListRight :: forall a . Permutation -> [a] -> [a]
permuteListRight :: forall a. Permutation -> [a] -> [a]
permuteListRight Permutation
perm [a]
xs = forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
elems forall a b. (a -> b) -> a -> b
$ forall (arr :: * -> * -> *) b.
IArray arr b =>
Permutation -> arr Int b -> arr Int b
permuteArrayRight Permutation
perm forall a b. (a -> b) -> a -> b
$ Array Int a
arr where
arr :: Array Int a
arr = forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [e] -> a i e
listArray (Int
1,Int
n) [a]
xs :: Array Int a
n :: Int
n = Permutation -> Int
permutationSize Permutation
perm
{-# SPECIALIZE permuteArrayLeft :: Permutation -> Array Int b -> Array Int b #-}
{-# SPECIALIZE permuteArrayLeft :: Permutation -> UArray Int Int -> UArray Int Int #-}
permuteArrayLeft :: IArray arr b => Permutation -> arr Int b -> arr Int b
permuteArrayLeft :: forall (arr :: * -> * -> *) b.
IArray arr b =>
Permutation -> arr Int b -> arr Int b
permuteArrayLeft pi :: Permutation
pi@(Permutation WordVec
perm) arr Int b
ar =
if (Int
aforall a. Eq a => a -> a -> Bool
==Int
1) Bool -> Bool -> Bool
&& (Int
bforall a. Eq a => a -> a -> Bool
==Int
n)
then forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [(i, e)] -> a i e
array (Int
1,Int
n) [ ( WordVec
permWordVec -> Int -> Int
.!Int
i , arr Int b
arforall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!Int
i ) | Int
i <- [Int
1..Int
n] ]
else forall a. HasCallStack => String -> a
error String
"permuteArrayLeft: array bounds do not match"
where
n :: Int
n = WordVec -> Int
_bound WordVec
perm
(Int
a,Int
b) = forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> (i, i)
bounds arr Int b
ar
permuteListLeft :: forall a. Permutation -> [a] -> [a]
permuteListLeft :: forall a. Permutation -> [a] -> [a]
permuteListLeft Permutation
perm [a]
xs = forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
elems forall a b. (a -> b) -> a -> b
$ forall (arr :: * -> * -> *) b.
IArray arr b =>
Permutation -> arr Int b -> arr Int b
permuteArrayLeft Permutation
perm forall a b. (a -> b) -> a -> b
$ Array Int a
arr where
arr :: Array Int a
arr = forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
(i, i) -> [e] -> a i e
listArray (Int
1,Int
n) [a]
xs :: Array Int a
n :: Int
n = Permutation -> Int
permutationSize Permutation
perm
sortingPermutationAsc :: Ord a => [a] -> Permutation
sortingPermutationAsc :: forall a. Ord a => [a] -> Permutation
sortingPermutationAsc [a]
xs = [Int] -> Permutation
toPermutation (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [(Int, a)]
sorted) where
sorted :: [(Int, a)]
sorted = forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing forall a b. (a, b) -> b
snd) forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] [a]
xs
sortingPermutationDesc :: Ord a => [a] -> Permutation
sortingPermutationDesc :: forall a. Ord a => [a] -> Permutation
sortingPermutationDesc [a]
xs = [Int] -> Permutation
toPermutation (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [(Int, a)]
sorted) where
sorted :: [(Int, a)]
sorted = forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (forall a b. Ord a => (b -> a) -> b -> b -> Ordering
reverseComparing forall a b. (a, b) -> b
snd) forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] [a]
xs
permutations :: Int -> [Permutation]
permutations :: Int -> [Permutation]
permutations = Int -> [Permutation]
permutationsNaive
_permutations :: Int -> [[Int]]
_permutations :: Int -> [[Int]]
_permutations = Int -> [[Int]]
_permutationsNaive
permutationsNaive :: Int -> [Permutation]
permutationsNaive :: Int -> [Permutation]
permutationsNaive Int
n = forall a b. (a -> b) -> [a] -> [b]
map [Int] -> Permutation
toPermutationUnsafe forall a b. (a -> b) -> a -> b
$ Int -> [[Int]]
_permutations Int
n
_permutationsNaive :: Int -> [[Int]]
_permutationsNaive :: Int -> [[Int]]
_permutationsNaive Int
0 = [[]]
_permutationsNaive Int
1 = [[Int
1]]
_permutationsNaive Int
n = forall {a}. Ord a => [a] -> [[a]]
helper [Int
1..Int
n] where
helper :: [a] -> [[a]]
helper [] = [[]]
helper [a]
xs = [ a
i forall a. a -> [a] -> [a]
: [a]
ys | a
i <- [a]
xs , [a]
ys <- [a] -> [[a]]
helper ([a]
xs forall {t}. Ord t => [t] -> t -> [t]
`minus` a
i) ]
minus :: [t] -> t -> [t]
minus [] t
_ = []
minus (t
x:[t]
xs) t
i = if t
x forall a. Ord a => a -> a -> Bool
< t
i then t
x forall a. a -> [a] -> [a]
: [t] -> t -> [t]
minus [t]
xs t
i else [t]
xs
countPermutations :: Int -> Integer
countPermutations :: Int -> Integer
countPermutations = forall a. Integral a => a -> Integer
factorial
randomPermutation :: RandomGen g => Int -> g -> (Permutation,g)
randomPermutation :: forall g. RandomGen g => Int -> g -> (Permutation, g)
randomPermutation = forall g. RandomGen g => Int -> g -> (Permutation, g)
randomPermutationDurstenfeld
_randomPermutation :: RandomGen g => Int -> g -> ([Int],g)
_randomPermutation :: forall g. RandomGen g => Int -> g -> ([Int], g)
_randomPermutation Int
n g
rndgen = (Permutation -> [Int]
fromPermutation Permutation
perm, g
rndgen') where
(Permutation
perm, g
rndgen') = forall g. RandomGen g => Int -> g -> (Permutation, g)
randomPermutationDurstenfeld Int
n g
rndgen
randomCyclicPermutation :: RandomGen g => Int -> g -> (Permutation,g)
randomCyclicPermutation :: forall g. RandomGen g => Int -> g -> (Permutation, g)
randomCyclicPermutation = forall g. RandomGen g => Int -> g -> (Permutation, g)
randomCyclicPermutationSattolo
_randomCyclicPermutation :: RandomGen g => Int -> g -> ([Int],g)
_randomCyclicPermutation :: forall g. RandomGen g => Int -> g -> ([Int], g)
_randomCyclicPermutation Int
n g
rndgen = (Permutation -> [Int]
fromPermutation Permutation
perm, g
rndgen') where
(Permutation
perm, g
rndgen') = forall g. RandomGen g => Int -> g -> (Permutation, g)
randomCyclicPermutationSattolo Int
n g
rndgen
randomPermutationDurstenfeld :: RandomGen g => Int -> g -> (Permutation,g)
randomPermutationDurstenfeld :: forall g. RandomGen g => Int -> g -> (Permutation, g)
randomPermutationDurstenfeld = forall g. RandomGen g => Bool -> Int -> g -> (Permutation, g)
randomPermutationDurstenfeldSattolo Bool
False
randomCyclicPermutationSattolo :: RandomGen g => Int -> g -> (Permutation,g)
randomCyclicPermutationSattolo :: forall g. RandomGen g => Int -> g -> (Permutation, g)
randomCyclicPermutationSattolo = forall g. RandomGen g => Bool -> Int -> g -> (Permutation, g)
randomPermutationDurstenfeldSattolo Bool
True
randomPermutationDurstenfeldSattolo :: RandomGen g => Bool -> Int -> g -> (Permutation,g)
randomPermutationDurstenfeldSattolo :: forall g. RandomGen g => Bool -> Int -> g -> (Permutation, g)
randomPermutationDurstenfeldSattolo Bool
isSattolo Int
n g
rnd = (Permutation, g)
res where
res :: (Permutation, g)
res = forall a. (forall s. ST s a) -> a
runST forall a b. (a -> b) -> a -> b
$ do
STUArray s Int Int
ar <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
newArray_ (Int
1,Int
n)
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Int
1..Int
n] forall a b. (a -> b) -> a -> b
$ \Int
i -> forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
ar Int
i Int
i
g
rnd' <- forall g s.
RandomGen g =>
Int -> Int -> g -> STUArray s Int Int -> ST s g
worker Int
n (if Bool
isSattolo then Int
nforall a. Num a => a -> a -> a
-Int
1 else Int
n) g
rnd STUArray s Int Int
ar
UArray Int Int
perm <- forall i (a :: * -> * -> *) e (m :: * -> *) (b :: * -> * -> *).
(Ix i, MArray a e m, IArray b e) =>
a i e -> m (b i e)
Data.Array.Unsafe.unsafeFreeze STUArray s Int Int
ar
forall (m :: * -> *) a. Monad m => a -> m a
return (WordVec -> Permutation
Permutation (UArray Int Int -> WordVec
fromUArray UArray Int Int
perm), g
rnd')
worker :: RandomGen g => Int -> Int -> g -> STUArray s Int Int -> ST s g
worker :: forall g s.
RandomGen g =>
Int -> Int -> g -> STUArray s Int Int -> ST s g
worker Int
n Int
m g
rnd STUArray s Int Int
ar =
if Int
nforall a. Eq a => a -> a -> Bool
==Int
1
then forall (m :: * -> *) a. Monad m => a -> m a
return g
rnd
else do
let (Int
k,g
rnd') = forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
randomR (Int
1,Int
m) g
rnd
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
k forall a. Eq a => a -> a -> Bool
/= Int
n) forall a b. (a -> b) -> a -> b
$ do
Int
y <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Int
ar Int
k
Int
z <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Int
ar Int
n
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
ar Int
n Int
y
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Int
ar Int
k Int
z
forall g s.
RandomGen g =>
Int -> Int -> g -> STUArray s Int Int -> ST s g
worker (Int
nforall a. Num a => a -> a -> a
-Int
1) (Int
mforall a. Num a => a -> a -> a
-Int
1) g
rnd' STUArray s Int Int
ar
permuteMultiset :: (Eq a, Ord a) => [a] -> [[a]]
permuteMultiset :: forall a. (Eq a, Ord a) => [a] -> [[a]]
permuteMultiset = forall a. (Eq a, Ord a) => [a] -> [[a]]
fasc2B_algorithm_L
countPermuteMultiset :: (Eq a, Ord a) => [a] -> Integer
countPermuteMultiset :: forall a. (Eq a, Ord a) => [a] -> Integer
countPermuteMultiset [a]
xs = forall a. Integral a => a -> Integer
factorial Int
n forall a. Integral a => a -> a -> a
`div` forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
product [ forall a. Integral a => a -> Integer
factorial (forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
z) | [a]
z <- forall a. Eq a => [a] -> [[a]]
group [a]
ys ]
where
ys :: [a]
ys = forall a. Ord a => [a] -> [a]
sort [a]
xs
n :: Int
n = forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
xs
fasc2B_algorithm_L :: (Eq a, Ord a) => [a] -> [[a]]
fasc2B_algorithm_L :: forall a. (Eq a, Ord a) => [a] -> [[a]]
fasc2B_algorithm_L [a]
xs = forall a. (a -> Maybe a) -> a -> [a]
unfold1 forall {a}. Ord a => [a] -> Maybe [a]
next (forall a. Ord a => [a] -> [a]
sort [a]
xs) where
next :: [a] -> Maybe [a]
next [a]
xs = case forall {a}. Ord a => ([a], [a]) -> Maybe ([a], [a])
findj (forall a. [a] -> [a]
reverse [a]
xs,[]) of
Maybe ([a], [a])
Nothing -> forall a. Maybe a
Nothing
Just ( (a
l:[a]
ls) , [a]
rs) -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall {a}. Ord a => a -> [a] -> ([a], [a]) -> [a]
inc a
l [a]
ls (forall a. [a] -> [a]
reverse [a]
rs,[])
Just ( [] , [a]
_ ) -> forall a. HasCallStack => String -> a
error String
"permute: should not happen"
findj :: ([a], [a]) -> Maybe ([a], [a])
findj ( xxs :: [a]
xxs@(a
x:[a]
xs) , yys :: [a]
yys@(a
y:[a]
_) ) = if a
x forall a. Ord a => a -> a -> Bool
>= a
y
then ([a], [a]) -> Maybe ([a], [a])
findj ( [a]
xs , a
x forall a. a -> [a] -> [a]
: [a]
yys )
else forall a. a -> Maybe a
Just ( [a]
xxs , [a]
yys )
findj ( a
x:[a]
xs , [] ) = ([a], [a]) -> Maybe ([a], [a])
findj ( [a]
xs , [a
x] )
findj ( [] , [a]
_ ) = forall a. Maybe a
Nothing
inc :: a -> [a] -> ([a], [a]) -> [a]
inc !a
u [a]
us ( (a
x:[a]
xs) , [a]
yys ) = if a
u forall a. Ord a => a -> a -> Bool
>= a
x
then a -> [a] -> ([a], [a]) -> [a]
inc a
u [a]
us ( [a]
xs , a
x forall a. a -> [a] -> [a]
: [a]
yys )
else forall a. [a] -> [a]
reverse (a
xforall a. a -> [a] -> [a]
:[a]
us) forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [a]
reverse (a
uforall a. a -> [a] -> [a]
:[a]
yys) forall a. [a] -> [a] -> [a]
++ [a]
xs
inc a
_ [a]
_ ( [] , [a]
_ ) = forall a. HasCallStack => String -> a
error String
"permute: should not happen"