{-# LANGUAGE CPP, BangPatterns, ScopedTypeVariables #-}
module Math.Combinat.Partitions.Integer.Count where
import Data.List
import Control.Monad ( liftM , replicateM )
import Math.Combinat.Numbers ( factorial , binomial , multinomial )
import Math.Combinat.Numbers.Integers
import Math.Combinat.Helper
import Data.Array
import System.Random
newtype TableOfIntegers = TableOfIntegers [Array Int Integer]
lookupInteger :: TableOfIntegers -> Int -> Integer
lookupInteger :: TableOfIntegers -> Int -> Integer
lookupInteger (TableOfIntegers [Array Int Integer]
table) !Int
n
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 = ([Array Int Integer]
table [Array Int Integer] -> Int -> Array Int Integer
forall a. [a] -> Int -> a
!! Int
k) Array Int Integer -> Int -> Integer
forall i e. Ix i => Array i e -> i -> e
! Int
r
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = Integer
0
where
(Int
k,Int
r) = Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
divMod Int
n Int
1024
makeTableOfIntegers
:: ((Int -> Integer) -> (Int -> Integer))
-> TableOfIntegers
makeTableOfIntegers :: ((Int -> Integer) -> Int -> Integer) -> TableOfIntegers
makeTableOfIntegers (Int -> Integer) -> Int -> Integer
user = TableOfIntegers
table where
calc :: Int -> Integer
calc = (Int -> Integer) -> Int -> Integer
user Int -> Integer
lkp
lkp :: Int -> Integer
lkp = TableOfIntegers -> Int -> Integer
lookupInteger TableOfIntegers
table
table :: TableOfIntegers
table = [Array Int Integer] -> TableOfIntegers
TableOfIntegers
[ (Int, Int) -> [Integer] -> Array Int Integer
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
1023) ((Int -> Integer) -> [Int] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Integer
calc [Int
a..Int
b])
| Int
k<-[Int
0..]
, let a :: Int
a = Int
1024Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
k
, let b :: Int
b = Int
1024Int -> Int -> Int
forall a. Num a => a -> a -> a
*(Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
]
countPartitions :: Int -> Integer
countPartitions :: Int -> Integer
countPartitions = TableOfIntegers -> Int -> Integer
lookupInteger TableOfIntegers
partitionCountTable
countPartitionsInfiniteProduct :: Int -> Integer
countPartitionsInfiniteProduct :: Int -> Integer
countPartitionsInfiniteProduct Int
k = [Integer]
partitionCountListInfiniteProduct [Integer] -> Int -> Integer
forall a. [a] -> Int -> a
!! Int
k
countPartitionsNaive :: Int -> Integer
countPartitionsNaive :: Int -> Integer
countPartitionsNaive Int
d = (Int, Int) -> Int -> Integer
countPartitions' (Int
d,Int
d) Int
d
partitionCountTable :: TableOfIntegers
partitionCountTable :: TableOfIntegers
partitionCountTable = TableOfIntegers
table where
table :: TableOfIntegers
table = ((Int -> Integer) -> Int -> Integer) -> TableOfIntegers
makeTableOfIntegers (Int -> Integer) -> Int -> Integer
forall p. Num p => (Int -> p) -> Int -> p
fun
fun :: (Int -> p) -> Int -> p
fun Int -> p
lkp !Int
n
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 = (p -> p -> p) -> p -> [p] -> p
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' p -> p -> p
forall a. Num a => a -> a -> a
(+) p
0
[ (if Int -> Bool
forall a. Integral a => a -> Bool
even Int
k then p -> p
forall a. Num a => a -> a
negate else p -> p
forall a. a -> a
id)
( Int -> p
lkp (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int -> Int -> Int
forall a. Integral a => a -> a -> a
div (Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
*(Int
3Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)) Int
2)
p -> p -> p
forall a. Num a => a -> a -> a
+ Int -> p
lkp (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int -> Int -> Int
forall a. Integral a => a -> a -> a
div (Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
*(Int
3Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)) Int
2)
)
| Int
k <- [Int
1..Int -> Int
limit Int
n]
]
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 = p
0
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = p
1
| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = p
1
limit :: Int -> Int
limit :: Int -> Int
limit !Int
n = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer -> Int) -> Integer -> Int
forall a b. (a -> b) -> a -> b
$ Integer -> Integer
ceilingSquareRoot (Integer
1 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
div (Integer
nnInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
nnInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
1) Integer
3) where
nn :: Integer
nn = Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n :: Integer
partitionCountList :: [Integer]
partitionCountList :: [Integer]
partitionCountList = (Int -> Integer) -> [Int] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Integer
countPartitions [Int
0..]
partitionCountListInfiniteProduct :: [Integer]
partitionCountListInfiniteProduct :: [Integer]
partitionCountListInfiniteProduct = [Integer]
final where
final :: [Integer]
final = Int -> [Integer] -> [Integer]
go Int
1 (Integer
1Integer -> [Integer] -> [Integer]
forall a. a -> [a] -> [a]
:Integer -> [Integer]
forall a. a -> [a]
repeat Integer
0)
go :: Int -> [Integer] -> [Integer]
go !Int
k (Integer
x:[Integer]
xs) = Integer
x Integer -> [Integer] -> [Integer]
forall a. a -> [a] -> [a]
: Int -> [Integer] -> [Integer]
go (Int
kInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) [Integer]
ys where
ys :: [Integer]
ys = (Integer -> Integer -> Integer)
-> [Integer] -> [Integer] -> [Integer]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
(+) [Integer]
xs (Int -> [Integer] -> [Integer]
forall a. Int -> [a] -> [a]
take Int
k [Integer]
final [Integer] -> [Integer] -> [Integer]
forall a. [a] -> [a] -> [a]
++ [Integer]
ys)
partitionCountListNaive :: [Integer]
partitionCountListNaive :: [Integer]
partitionCountListNaive = (Int -> Integer) -> [Int] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Integer
countPartitionsNaive [Int
0..]
countAllPartitions :: Int -> Integer
countAllPartitions :: Int -> Integer
countAllPartitions Int
d = [Integer] -> Integer
forall a. Num a => [a] -> a
sum' [ Int -> Integer
countPartitions Int
i | Int
i <- [Int
0..Int
d] ]
countAllPartitions' :: (Int,Int) -> Integer
countAllPartitions' :: (Int, Int) -> Integer
countAllPartitions' (Int
h,Int
w) =
Int -> Int -> Integer
forall a. Integral a => a -> a -> Integer
binomial (Int
hInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
w) (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
h Int
w)
countPartitions' :: (Int,Int) -> Int -> Integer
countPartitions' :: (Int, Int) -> Int -> Integer
countPartitions' (Int, Int)
_ Int
0 = Integer
1
countPartitions' (Int
0,Int
_) Int
d = if Int
dInt -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
0 then Integer
1 else Integer
0
countPartitions' (Int
_,Int
0) Int
d = if Int
dInt -> Int -> Bool
forall a. Eq a => a -> a -> Bool
==Int
0 then Integer
1 else Integer
0
countPartitions' (Int
h,Int
w) Int
d = [Integer] -> Integer
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum
[ (Int, Int) -> Int -> Integer
countPartitions' (Int
i,Int
wInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) (Int
dInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i) | Int
i <- [Int
1..Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
d Int
h] ]
countPartitionsWithKParts
:: Int
-> Int
-> Integer
countPartitionsWithKParts :: Int -> Int -> Integer
countPartitionsWithKParts Int
k Int
n = Int -> Int -> Int -> Integer
forall t p. (Ord t, Num t, Num p, Enum t) => t -> t -> t -> p
go Int
n Int
k Int
n where
go :: t -> t -> t -> p
go !t
h !t
k !t
n
| t
k t -> t -> Bool
forall a. Ord a => a -> a -> Bool
< t
0 = p
0
| t
k t -> t -> Bool
forall a. Eq a => a -> a -> Bool
== t
0 = if t
ht -> t -> Bool
forall a. Ord a => a -> a -> Bool
>=t
0 Bool -> Bool -> Bool
&& t
nt -> t -> Bool
forall a. Eq a => a -> a -> Bool
==t
0 then p
1 else p
0
| t
k t -> t -> Bool
forall a. Eq a => a -> a -> Bool
== t
1 = if t
ht -> t -> Bool
forall a. Ord a => a -> a -> Bool
>=t
n Bool -> Bool -> Bool
&& t
nt -> t -> Bool
forall a. Ord a => a -> a -> Bool
>=t
1 then p
1 else p
0
| Bool
otherwise = [p] -> p
forall a. Num a => [a] -> a
sum' [ t -> t -> t -> p
go t
a (t
kt -> t -> t
forall a. Num a => a -> a -> a
-t
1) (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
a) | t
a<-[t
1..(t -> t -> t
forall a. Ord a => a -> a -> a
min t
h (t
nt -> t -> t
forall a. Num a => a -> a -> a
-t
kt -> t -> t
forall a. Num a => a -> a -> a
+t
1))] ]