{-# LANGUAGE CPP, BangPatterns, ScopedTypeVariables, PatternSynonyms, ViewPatterns #-}
module Math.Combinat.Partitions.Integer.Naive 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.IntList
import Math.Combinat.Partitions.Integer.Count ( countPartitions )
newtype Partition = Partition [Int] deriving (Partition -> Partition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Partition -> Partition -> Bool
$c/= :: Partition -> Partition -> Bool
== :: Partition -> Partition -> Bool
$c== :: Partition -> Partition -> Bool
Eq,Eq Partition
Partition -> Partition -> Bool
Partition -> Partition -> Ordering
Partition -> Partition -> Partition
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 :: Partition -> Partition -> Partition
$cmin :: Partition -> Partition -> Partition
max :: Partition -> Partition -> Partition
$cmax :: Partition -> Partition -> Partition
>= :: Partition -> Partition -> Bool
$c>= :: Partition -> Partition -> Bool
> :: Partition -> Partition -> Bool
$c> :: Partition -> Partition -> Bool
<= :: Partition -> Partition -> Bool
$c<= :: Partition -> Partition -> Bool
< :: Partition -> Partition -> Bool
$c< :: Partition -> Partition -> Bool
compare :: Partition -> Partition -> Ordering
$ccompare :: Partition -> Partition -> Ordering
Ord,Int -> Partition -> ShowS
[Partition] -> ShowS
Partition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Partition] -> ShowS
$cshowList :: [Partition] -> ShowS
show :: Partition -> String
$cshow :: Partition -> String
showsPrec :: Int -> Partition -> ShowS
$cshowsPrec :: Int -> Partition -> ShowS
Show,ReadPrec [Partition]
ReadPrec Partition
Int -> ReadS Partition
ReadS [Partition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Partition]
$creadListPrec :: ReadPrec [Partition]
readPrec :: ReadPrec Partition
$creadPrec :: ReadPrec Partition
readList :: ReadS [Partition]
$creadList :: ReadS [Partition]
readsPrec :: Int -> ReadS Partition
$creadsPrec :: Int -> ReadS Partition
Read)
instance HasNumberOfParts Partition where
numberOfParts :: Partition -> Int
numberOfParts (Partition [Int]
p) = forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
p
toList :: Partition -> [Int]
toList :: Partition -> [Int]
toList (Partition [Int]
xs) = [Int]
xs
fromList :: [Int] -> Partition
fromList :: [Int] -> Partition
fromList = [Int] -> Partition
mkPartition where
mkPartition :: [Int] -> Partition
mkPartition [Int]
xs = [Int] -> Partition
Partition 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
fromListUnsafe :: [Int] -> Partition
fromListUnsafe :: [Int] -> Partition
fromListUnsafe = [Int] -> Partition
Partition
isEmptyPartition :: Partition -> Bool
isEmptyPartition :: Partition -> Bool
isEmptyPartition (Partition [Int]
p) = forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Int]
p
emptyPartition :: Partition
emptyPartition :: Partition
emptyPartition = [Int] -> Partition
Partition []
instance CanBeEmpty Partition where
empty :: Partition
empty = Partition
emptyPartition
isEmpty :: Partition -> Bool
isEmpty = Partition -> Bool
isEmptyPartition
partitionHeight :: Partition -> Int
partitionHeight :: Partition -> Int
partitionHeight (Partition [Int]
part) = case [Int]
part of
(Int
p:[Int]
_) -> Int
p
[] -> Int
0
partitionWidth :: Partition -> Int
partitionWidth :: Partition -> Int
partitionWidth (Partition [Int]
part) = forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
part
instance HasHeight Partition where
height :: Partition -> Int
height = Partition -> Int
partitionHeight
instance HasWidth Partition where
width :: Partition -> Int
width = Partition -> Int
partitionWidth
heightWidth :: Partition -> (Int,Int)
heightWidth :: Partition -> (Int, Int)
heightWidth Partition
part = (forall a. HasHeight a => a -> Int
height Partition
part, forall a. HasWidth a => a -> Int
width Partition
part)
partitionWeight :: Partition -> Int
partitionWeight :: Partition -> Int
partitionWeight (Partition [Int]
part) = forall a. Num a => [a] -> a
sum' [Int]
part
instance HasWeight Partition where
weight :: Partition -> Int
weight = Partition -> Int
partitionWeight
dualPartition :: Partition -> Partition
dualPartition :: Partition -> Partition
dualPartition (Partition [Int]
part) = [Int] -> Partition
Partition ([Int] -> [Int]
_dualPartition [Int]
part)
instance HasDuality Partition where
dual :: Partition -> Partition
dual = Partition -> Partition
dualPartition
elements :: Partition -> [(Int,Int)]
elements :: Partition -> [(Int, Int)]
elements (Partition [Int]
part) = [Int] -> [(Int, Int)]
_elements [Int]
part
pattern Nil :: Partition
pattern $bNil :: Partition
$mNil :: forall {r}. Partition -> ((# #) -> r) -> ((# #) -> r) -> r
Nil <- (isEmpty -> True) where
Nil = forall a. CanBeEmpty a => a
empty
pattern Cons :: Int -> Partition -> Partition
pattern $bCons :: Int -> Partition -> Partition
$mCons :: forall {r}.
Partition -> (Int -> Partition -> r) -> ((# #) -> r) -> r
Cons x xs <- (unconsPartition -> Just (x,xs)) where
Cons Int
x (Partition [Int]
xs) = [Int] -> Partition
Partition (Int
xforall a. a -> [a] -> [a]
:[Int]
xs)
pattern Partition_ :: [Int] -> Partition
pattern $bPartition_ :: [Int] -> Partition
$mPartition_ :: forall {r}. Partition -> ([Int] -> r) -> ((# #) -> r) -> r
Partition_ xs = Partition xs
pattern Head :: Int -> Partition
pattern $mHead :: forall {r}. Partition -> (Int -> r) -> ((# #) -> r) -> r
Head h <- (head . toDescList -> h)
pattern Tail :: Partition -> Partition
pattern $mTail :: forall {r}. Partition -> (Partition -> r) -> ((# #) -> r) -> r
Tail xs <- (Partition . tail . toDescList -> xs)
pattern Length :: Int -> Partition
pattern $mLength :: forall {r}. Partition -> (Int -> r) -> ((# #) -> r) -> r
Length n <- (partitionWidth -> n)
toExponentialForm :: Partition -> [(Int,Int)]
toExponentialForm :: Partition -> [(Int, Int)]
toExponentialForm = [Int] -> [(Int, Int)]
_toExponentialForm forall b c a. (b -> c) -> (a -> b) -> a -> c
. Partition -> [Int]
toDescList
fromExponentialForm :: [(Int,Int)] -> Partition
fromExponentialForm :: [(Int, Int)] -> Partition
fromExponentialForm = [Int] -> Partition
Partition forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Int, Int)] -> [Int]
_fromExponentialForm where
diffSequence :: Partition -> [Int]
diffSequence :: Partition -> [Int]
diffSequence = forall {a}. Num a => [a] -> [a]
go forall b c a. (b -> c) -> (a -> b) -> a -> c
. Partition -> [Int]
toDescList where
go :: [a] -> [a]
go (a
x:ys :: [a]
ys@(a
y:[a]
_)) = (a
xforall a. Num a => a -> a -> a
-a
y) forall a. a -> [a] -> [a]
: [a] -> [a]
go [a]
ys
go [a
x] = [a
x]
go [] = []
unconsPartition :: Partition -> Maybe (Int,Partition)
unconsPartition :: Partition -> Maybe (Int, Partition)
unconsPartition (Partition [Int]
xs) = case [Int]
xs of
(Int
y:[Int]
ys) -> forall a. a -> Maybe a
Just (Int
y, [Int] -> Partition
Partition [Int]
ys)
[] -> forall a. Maybe a
Nothing
toDescList :: Partition -> [Int]
toDescList :: Partition -> [Int]
toDescList (Partition [Int]
xs) = [Int]
xs
dominates :: Partition -> Partition -> Bool
dominates :: Partition -> Partition -> Bool
dominates (Partition [Int]
qs) (Partition [Int]
ps)
= forall (t :: * -> *). Foldable t => t Bool -> Bool
and forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall a. Ord a => a -> a -> Bool
(>=) ([Int] -> [Int]
sums ([Int]
qs forall a. [a] -> [a] -> [a]
++ forall a. a -> [a]
repeat Int
0)) ([Int] -> [Int]
sums [Int]
ps)
where
sums :: [Int] -> [Int]
sums = forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl forall a. Num a => a -> a -> a
(+) Int
0
isSubPartitionOf :: Partition -> Partition -> Bool
isSubPartitionOf :: Partition -> Partition -> Bool
isSubPartitionOf (Partition [Int]
ps) (Partition [Int]
qs) = forall (t :: * -> *). Foldable t => t Bool -> Bool
and forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall a. Ord a => a -> a -> Bool
(<=) [Int]
ps ([Int]
qs forall a. [a] -> [a] -> [a]
++ forall a. a -> [a]
repeat Int
0)
isSuperPartitionOf :: Partition -> Partition -> Bool
isSuperPartitionOf :: Partition -> Partition -> Bool
isSuperPartitionOf (Partition [Int]
qs) (Partition [Int]
ps) = forall (t :: * -> *). Foldable t => t Bool -> Bool
and forall a b. (a -> b) -> a -> b
$ forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall a. Ord a => a -> a -> Bool
(<=) [Int]
ps ([Int]
qs forall a. [a] -> [a] -> [a]
++ forall a. a -> [a]
repeat Int
0)
pieriRule :: Partition -> Int -> [Partition]
pieriRule :: Partition -> Int -> [Partition]
pieriRule (Partition [Int]
lambda) Int
n = forall a b. (a -> b) -> [a] -> [b]
map [Int] -> Partition
Partition ([Int] -> Int -> [[Int]]
_pieriRule [Int]
lambda Int
n) where
dualPieriRule :: Partition -> Int -> [Partition]
dualPieriRule :: Partition -> Int -> [Partition]
dualPieriRule Partition
lam Int
n = forall a b. (a -> b) -> [a] -> [b]
map Partition -> Partition
dualPartition forall a b. (a -> b) -> a -> b
$ Partition -> Int -> [Partition]
pieriRule (Partition -> Partition
dualPartition Partition
lam) Int
n