{-# LANGUAGE CPP, BangPatterns, ScopedTypeVariables #-}
module Math.Combinat.Partitions.Integer
(
module Math.Combinat.Partitions.Integer.Naive
, Partition
, fromPartition
, mkPartition
, toPartition
, toPartitionUnsafe
, isPartition
, toExponentVector
, fromExponentVector
, dropTailingZeros
, unionOfPartitions
, sumOfPartitions
, partitions
, partitions'
, allPartitions
, allPartitionsGrouped
, allPartitions'
, allPartitionsGrouped'
, countPartitions
, countPartitions'
, countAllPartitions
, countAllPartitions'
, countPartitionsWithKParts
, randomPartition
, randomPartitions
, dominanceCompare
, dominatedPartitions
, dominatingPartitions
, conjugateLexicographicCompare
, ConjLex (..) , fromConjLex
, partitionsWithKParts
, partitionsWithOddParts
, partitionsWithDistinctParts
, subPartitions
, allSubPartitions
, superPartitions
, PartitionConvention(..)
, asciiFerrersDiagram
, asciiFerrersDiagram'
)
where
import Data.List
import Control.Monad ( liftM , replicateM )
import Math.Combinat.Classes
import Math.Combinat.ASCII as ASCII
import Math.Combinat.Numbers (factorial,binomial,multinomial)
import Math.Combinat.Helper
import Data.Array
import System.Random
import Math.Combinat.Partitions.Integer.Naive hiding ()
import Math.Combinat.Partitions.Integer.IntList
import Math.Combinat.Partitions.Integer.Count
fromPartition :: Partition -> [Int]
fromPartition :: Partition -> [Int]
fromPartition (Partition_ [Int]
part) = [Int]
part
mkPartition :: [Int] -> Partition
mkPartition :: [Int] -> Partition
mkPartition [Int]
xs = [Int] -> Partition
toPartitionUnsafe forall a b. (a -> b) -> a -> b
$ forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (forall a. Ord a => a -> a -> Ordering
reverseCompare) forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Ord a => a -> a -> Bool
>Int
0) [Int]
xs
toPartition :: [Int] -> Partition
toPartition :: [Int] -> Partition
toPartition [Int]
xs = if [Int] -> Bool
isPartition [Int]
xs
then [Int] -> Partition
toPartitionUnsafe [Int]
xs
else forall a. HasCallStack => [Char] -> a
error [Char]
"toPartition: not a partition"
toPartitionUnsafe :: [Int] -> Partition
toPartitionUnsafe :: [Int] -> Partition
toPartitionUnsafe = [Int] -> Partition
Partition_
isPartition :: [Int] -> Bool
isPartition :: [Int] -> Bool
isPartition [] = Bool
True
isPartition [Int
x] = Int
x forall a. Ord a => a -> a -> Bool
> Int
0
isPartition (Int
x:xs :: [Int]
xs@(Int
y:[Int]
_)) = (Int
x forall a. Ord a => a -> a -> Bool
>= Int
y) Bool -> Bool -> Bool
&& [Int] -> Bool
isPartition [Int]
xs
toExponentVector :: Partition -> [Int]
toExponentVector :: Partition -> [Int]
toExponentVector Partition
part = Int -> [[Int]] -> [Int]
fun Int
1 forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ forall a. Eq a => [a] -> [[a]]
group (Partition -> [Int]
fromPartition Partition
part) where
fun :: Int -> [[Int]] -> [Int]
fun Int
_ [] = []
fun !Int
k gs :: [[Int]]
gs@(this :: [Int]
this@(Int
i:[Int]
_):[[Int]]
rest)
| Int
k forall a. Ord a => a -> a -> Bool
< Int
i = forall a. Int -> a -> [a]
replicate (Int
iforall a. Num a => a -> a -> a
-Int
k) Int
0 forall a. [a] -> [a] -> [a]
++ Int -> [[Int]] -> [Int]
fun Int
i [[Int]]
gs
| Bool
otherwise = forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
this forall a. a -> [a] -> [a]
: Int -> [[Int]] -> [Int]
fun (Int
kforall a. Num a => a -> a -> a
+Int
1) [[Int]]
rest
fromExponentVector :: [Int] -> Partition
fromExponentVector :: [Int] -> Partition
fromExponentVector [Int]
expos = [Int] -> Partition
Partition forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall {a}. a -> Int -> [a]
f [Int
1..] [Int]
expos where
f :: a -> Int -> [a]
f !a
i !Int
e = forall a. Int -> a -> [a]
replicate Int
e a
i
dropTailingZeros :: [Int] -> [Int]
dropTailingZeros :: [Int] -> [Int]
dropTailingZeros = forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Eq a => a -> a -> Bool
==Int
0) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse
unionOfPartitions :: Partition -> Partition -> Partition
unionOfPartitions :: Partition -> Partition -> Partition
unionOfPartitions (Partition_ [Int]
xs) (Partition_ [Int]
ys) = [Int] -> Partition
mkPartition ([Int]
xs forall a. [a] -> [a] -> [a]
++ [Int]
ys)
sumOfPartitions :: Partition -> Partition -> Partition
sumOfPartitions :: Partition -> Partition -> Partition
sumOfPartitions (Partition_ [Int]
xs) (Partition_ [Int]
ys) = [Int] -> Partition
Partition_ (forall a b c. a -> b -> (a -> b -> c) -> [a] -> [b] -> [c]
longZipWith Int
0 Int
0 forall a. Num a => a -> a -> a
(+) [Int]
xs [Int]
ys)
partitions :: Int -> [Partition]
partitions :: Int -> [Partition]
partitions = forall a b. (a -> b) -> [a] -> [b]
map [Int] -> Partition
toPartitionUnsafe forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [[Int]]
_partitions
partitions'
:: (Int,Int)
-> Int
-> [Partition]
partitions' :: (Int, Int) -> Int -> [Partition]
partitions' (Int, Int)
hw Int
d = forall a b. (a -> b) -> [a] -> [b]
map [Int] -> Partition
toPartitionUnsafe forall a b. (a -> b) -> a -> b
$ (Int, Int) -> Int -> [[Int]]
_partitions' (Int, Int)
hw Int
d
allPartitions :: Int -> [Partition]
allPartitions :: Int -> [Partition]
allPartitions Int
d = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ Int -> [Partition]
partitions Int
i | Int
i <- [Int
0..Int
d] ]
allPartitionsGrouped :: Int -> [[Partition]]
allPartitionsGrouped :: Int -> [[Partition]]
allPartitionsGrouped Int
d = [ Int -> [Partition]
partitions Int
i | Int
i <- [Int
0..Int
d] ]
allPartitions'
:: (Int,Int)
-> [Partition]
allPartitions' :: (Int, Int) -> [Partition]
allPartitions' (Int
h,Int
w) = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ (Int, Int) -> Int -> [Partition]
partitions' (Int
h,Int
w) Int
i | Int
i <- [Int
0..Int
d] ] where d :: Int
d = Int
hforall a. Num a => a -> a -> a
*Int
w
allPartitionsGrouped'
:: (Int,Int)
-> [[Partition]]
allPartitionsGrouped' :: (Int, Int) -> [[Partition]]
allPartitionsGrouped' (Int
h,Int
w) = [ (Int, Int) -> Int -> [Partition]
partitions' (Int
h,Int
w) Int
i | Int
i <- [Int
0..Int
d] ] where d :: Int
d = Int
hforall a. Num a => a -> a -> a
*Int
w
randomPartition :: RandomGen g => Int -> g -> (Partition, g)
randomPartition :: forall g. RandomGen g => Int -> g -> (Partition, g)
randomPartition Int
n g
g = (Partition
p, g
g') where
([Partition
p], g
g') = forall g. RandomGen g => Int -> Int -> g -> ([Partition], g)
randomPartitions Int
1 Int
n g
g
randomPartitions
:: forall g. RandomGen g
=> Int
-> Int
-> g -> ([Partition], g)
randomPartitions :: forall g. RandomGen g => Int -> Int -> g -> ([Partition], g)
randomPartitions Int
howmany Int
n = forall g a. Rand g a -> g -> (a, g)
runRand forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
howmany (Int -> [(Int, Int)] -> Rand g Partition
worker Int
n []) where
cnt :: Int -> Integer
cnt = Int -> Integer
countPartitions
finish :: [(Int,Int)] -> Partition
finish :: [(Int, Int)] -> Partition
finish = [Int] -> Partition
mkPartition forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall {a}. (Int, a) -> [a]
f where f :: (Int, a) -> [a]
f (Int
j,a
d) = forall a. Int -> a -> [a]
replicate Int
j a
d
fi :: Int -> Integer
fi :: Int -> Integer
fi = forall a b. (Integral a, Num b) => a -> b
fromIntegral
find_jd :: Int -> Integer -> (Int,Int)
find_jd :: Int -> Integer -> (Int, Int)
find_jd Int
m Integer
capm = Integer -> [(Int, Int)] -> (Int, Int)
go Integer
0 [ (Int
j,Int
d) | Int
j<-[Int
1..Int
n], Int
d<-[Int
1..forall a. Integral a => a -> a -> a
div Int
m Int
j] ] where
go :: Integer -> [(Int,Int)] -> (Int,Int)
go :: Integer -> [(Int, Int)] -> (Int, Int)
go !Integer
s [] = (Int
1,Int
1)
go !Integer
s [(Int, Int)
jd] = (Int, Int)
jd
go !Integer
s (jd :: (Int, Int)
jd@(Int
j,Int
d):[(Int, Int)]
rest) =
if Integer
s' forall a. Ord a => a -> a -> Bool
> Integer
capm
then (Int, Int)
jd
else Integer -> [(Int, Int)] -> (Int, Int)
go Integer
s' [(Int, Int)]
rest
where
s' :: Integer
s' = Integer
s forall a. Num a => a -> a -> a
+ Int -> Integer
fi Int
d forall a. Num a => a -> a -> a
* Int -> Integer
cnt (Int
m forall a. Num a => a -> a -> a
- Int
jforall a. Num a => a -> a -> a
*Int
d)
worker :: Int -> [(Int,Int)] -> Rand g Partition
worker :: Int -> [(Int, Int)] -> Rand g Partition
worker Int
0 [(Int, Int)]
acc = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [(Int, Int)] -> Partition
finish [(Int, Int)]
acc
worker !Int
m [(Int, Int)]
acc = do
Integer
capm <- forall g a. (RandomGen g, Random a) => (a, a) -> Rand g a
randChoose (Integer
0, (Int -> Integer
fi Int
m) forall a. Num a => a -> a -> a
* Int -> Integer
cnt Int
m forall a. Num a => a -> a -> a
- Integer
1)
let jd :: (Int, Int)
jd@(!Int
j,!Int
d) = Int -> Integer -> (Int, Int)
find_jd Int
m Integer
capm
Int -> [(Int, Int)] -> Rand g Partition
worker (Int
m forall a. Num a => a -> a -> a
- Int
jforall a. Num a => a -> a -> a
*Int
d) ((Int, Int)
jdforall a. a -> [a] -> [a]
:[(Int, Int)]
acc)
dominanceCompare :: Partition -> Partition -> Maybe Ordering
dominanceCompare :: Partition -> Partition -> Maybe Ordering
dominanceCompare Partition
p Partition
q
| Partition
pforall a. Eq a => a -> a -> Bool
==Partition
q = forall a. a -> Maybe a
Just Ordering
EQ
| Partition
p Partition -> Partition -> Bool
`dominates` Partition
q = forall a. a -> Maybe a
Just Ordering
GT
| Partition
q Partition -> Partition -> Bool
`dominates` Partition
p = forall a. a -> Maybe a
Just Ordering
LT
| Bool
otherwise = forall a. Maybe a
Nothing
dominatedPartitions :: Partition -> [Partition]
dominatedPartitions :: Partition -> [Partition]
dominatedPartitions (Partition_ [Int]
lambda) = forall a b. (a -> b) -> [a] -> [b]
map [Int] -> Partition
Partition_ ([Int] -> [[Int]]
_dominatedPartitions [Int]
lambda)
dominatingPartitions :: Partition -> [Partition]
dominatingPartitions :: Partition -> [Partition]
dominatingPartitions (Partition_ [Int]
mu) = forall a b. (a -> b) -> [a] -> [b]
map [Int] -> Partition
Partition_ ([Int] -> [[Int]]
_dominatingPartitions [Int]
mu)
conjugateLexicographicCompare :: Partition -> Partition -> Ordering
conjugateLexicographicCompare :: Partition -> Partition -> Ordering
conjugateLexicographicCompare Partition
p Partition
q = forall a. Ord a => a -> a -> Ordering
compare (Partition -> Partition
dualPartition Partition
q) (Partition -> Partition
dualPartition Partition
p)
newtype ConjLex = ConjLex Partition deriving (ConjLex -> ConjLex -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConjLex -> ConjLex -> Bool
$c/= :: ConjLex -> ConjLex -> Bool
== :: ConjLex -> ConjLex -> Bool
$c== :: ConjLex -> ConjLex -> Bool
Eq,Int -> ConjLex -> ShowS
[ConjLex] -> ShowS
ConjLex -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ConjLex] -> ShowS
$cshowList :: [ConjLex] -> ShowS
show :: ConjLex -> [Char]
$cshow :: ConjLex -> [Char]
showsPrec :: Int -> ConjLex -> ShowS
$cshowsPrec :: Int -> ConjLex -> ShowS
Show)
fromConjLex :: ConjLex -> Partition
fromConjLex :: ConjLex -> Partition
fromConjLex (ConjLex Partition
p) = Partition
p
instance Ord ConjLex where
compare :: ConjLex -> ConjLex -> Ordering
compare (ConjLex Partition
p) (ConjLex Partition
q) = Partition -> Partition -> Ordering
conjugateLexicographicCompare Partition
p Partition
q
partitionsWithKParts
:: Int
-> Int
-> [Partition]
partitionsWithKParts :: Int -> Int -> [Partition]
partitionsWithKParts Int
k Int
n = forall a b. (a -> b) -> [a] -> [b]
map [Int] -> Partition
Partition_ forall a b. (a -> b) -> a -> b
$ forall {t}. (Ord t, Num t, Enum t) => t -> t -> t -> [[t]]
go Int
n Int
k Int
n where
go :: t -> t -> t -> [[t]]
go !t
h !t
k !t
n
| t
k forall a. Ord a => a -> a -> Bool
< t
0 = []
| t
k forall a. Eq a => a -> a -> Bool
== t
0 = if t
hforall a. Ord a => a -> a -> Bool
>=t
0 Bool -> Bool -> Bool
&& t
nforall a. Eq a => a -> a -> Bool
==t
0 then [[] ] else []
| t
k forall a. Eq a => a -> a -> Bool
== t
1 = if t
hforall a. Ord a => a -> a -> Bool
>=t
n Bool -> Bool -> Bool
&& t
nforall a. Ord a => a -> a -> Bool
>=t
1 then [[t
n]] else []
| Bool
otherwise = [ t
aforall a. a -> [a] -> [a]
:[t]
p | t
a <- [t
1..(forall a. Ord a => a -> a -> a
min t
h (t
nforall a. Num a => a -> a -> a
-t
kforall a. Num a => a -> a -> a
+t
1))] , [t]
p <- t -> t -> t -> [[t]]
go t
a (t
kforall a. Num a => a -> a -> a
-t
1) (t
nforall a. Num a => a -> a -> a
-t
a) ]
partitionsWithOddParts :: Int -> [Partition]
partitionsWithOddParts :: Int -> [Partition]
partitionsWithOddParts Int
d = forall a b. (a -> b) -> [a] -> [b]
map [Int] -> Partition
Partition_ (forall {a}. (Num a, Ord a, Enum a) => a -> a -> [[a]]
go Int
d Int
d) where
go :: a -> a -> [[a]]
go a
_ a
0 = [[]]
go !a
h !a
n = [ a
aforall a. a -> [a] -> [a]
:[a]
as | a
a<-[a
1,a
3..forall a. Ord a => a -> a -> a
min a
n a
h], [a]
as <- a -> a -> [[a]]
go a
a (a
nforall a. Num a => a -> a -> a
-a
a) ]
partitionsWithDistinctParts :: Int -> [Partition]
partitionsWithDistinctParts :: Int -> [Partition]
partitionsWithDistinctParts Int
d = forall a b. (a -> b) -> [a] -> [b]
map [Int] -> Partition
Partition_ (forall {a}. (Num a, Ord a, Enum a) => a -> a -> [[a]]
go Int
d Int
d) where
go :: a -> a -> [[a]]
go a
_ a
0 = [[]]
go !a
h !a
n = [ a
aforall a. a -> [a] -> [a]
:[a]
as | a
a<-[a
1..forall a. Ord a => a -> a -> a
min a
n a
h], [a]
as <- a -> a -> [[a]]
go (a
aforall a. Num a => a -> a -> a
-a
1) (a
nforall a. Num a => a -> a -> a
-a
a) ]
subPartitions :: Int -> Partition -> [Partition]
subPartitions :: Int -> Partition -> [Partition]
subPartitions Int
d (Partition_ [Int]
ps) = forall a b. (a -> b) -> [a] -> [b]
map [Int] -> Partition
Partition_ (Int -> [Int] -> [[Int]]
_subPartitions Int
d [Int]
ps)
allSubPartitions :: Partition -> [Partition]
allSubPartitions :: Partition -> [Partition]
allSubPartitions (Partition_ [Int]
ps) = forall a b. (a -> b) -> [a] -> [b]
map [Int] -> Partition
Partition_ ([Int] -> [[Int]]
_allSubPartitions [Int]
ps)
superPartitions :: Int -> Partition -> [Partition]
superPartitions :: Int -> Partition -> [Partition]
superPartitions Int
d (Partition_ [Int]
ps) = forall a b. (a -> b) -> [a] -> [b]
map [Int] -> Partition
toPartitionUnsafe (Int -> [Int] -> [[Int]]
_superPartitions Int
d [Int]
ps)
data PartitionConvention
= EnglishNotation
| EnglishNotationCCW
| FrenchNotation
deriving (PartitionConvention -> PartitionConvention -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PartitionConvention -> PartitionConvention -> Bool
$c/= :: PartitionConvention -> PartitionConvention -> Bool
== :: PartitionConvention -> PartitionConvention -> Bool
$c== :: PartitionConvention -> PartitionConvention -> Bool
Eq,Int -> PartitionConvention -> ShowS
[PartitionConvention] -> ShowS
PartitionConvention -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [PartitionConvention] -> ShowS
$cshowList :: [PartitionConvention] -> ShowS
show :: PartitionConvention -> [Char]
$cshow :: PartitionConvention -> [Char]
showsPrec :: Int -> PartitionConvention -> ShowS
$cshowsPrec :: Int -> PartitionConvention -> ShowS
Show)
asciiFerrersDiagram :: Partition -> ASCII
asciiFerrersDiagram :: Partition -> ASCII
asciiFerrersDiagram = PartitionConvention -> Char -> Partition -> ASCII
asciiFerrersDiagram' PartitionConvention
EnglishNotation Char
'@'
asciiFerrersDiagram' :: PartitionConvention -> Char -> Partition -> ASCII
asciiFerrersDiagram' :: PartitionConvention -> Char -> Partition -> ASCII
asciiFerrersDiagram' PartitionConvention
conv Char
ch Partition
part = [[Char]] -> ASCII
ASCII.asciiFromLines (forall a b. (a -> b) -> [a] -> [b]
map Int -> [Char]
f [Int]
ys) where
f :: Int -> [Char]
f Int
n = forall a. Int -> a -> [a]
replicate Int
n Char
ch
ys :: [Int]
ys = case PartitionConvention
conv of
PartitionConvention
EnglishNotation -> Partition -> [Int]
fromPartition Partition
part
PartitionConvention
EnglishNotationCCW -> forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ Partition -> [Int]
fromPartition forall a b. (a -> b) -> a -> b
$ Partition -> Partition
dualPartition Partition
part
PartitionConvention
FrenchNotation -> forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ Partition -> [Int]
fromPartition forall a b. (a -> b) -> a -> b
$ Partition
part
instance DrawASCII Partition where
ascii :: Partition -> ASCII
ascii = Partition -> ASCII
asciiFerrersDiagram