module Math.Combinat.Compositions where
import System.Random
import Math.Combinat.Sets ( randomChoice )
import Math.Combinat.Numbers ( factorial , binomial )
import Math.Combinat.Helper
type Composition = [Int]
compositions'
:: [Int]
-> Int
-> [[Int]]
compositions' :: [Int] -> Int -> [[Int]]
compositions' [] Int
0 = [[]]
compositions' [] Int
_ = []
compositions' shape :: [Int]
shape@(Int
s:[Int]
ss) Int
n =
[ Int
xforall a. a -> [a] -> [a]
:[Int]
xs | Int
x <- [Int
0..forall a. Ord a => a -> a -> a
min Int
s Int
n] , [Int]
xs <- [Int] -> Int -> [[Int]]
compositions' [Int]
ss (Int
nforall a. Num a => a -> a -> a
-Int
x) ]
countCompositions' :: [Int] -> Int -> Integer
countCompositions' :: [Int] -> Int -> Integer
countCompositions' [] Int
0 = Integer
1
countCompositions' [] Int
_ = Integer
0
countCompositions' shape :: [Int]
shape@(Int
s:[Int]
ss) Int
n = forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum
[ [Int] -> Int -> Integer
countCompositions' [Int]
ss (Int
nforall a. Num a => a -> a -> a
-Int
x) | Int
x <- [Int
0..forall a. Ord a => a -> a -> a
min Int
s Int
n] ]
allCompositions1 :: Int -> [[Composition]]
allCompositions1 :: Int -> [[[Int]]]
allCompositions1 Int
n = forall a b. (a -> b) -> [a] -> [b]
map (\Int
d -> forall a. Integral a => a -> a -> [[Int]]
compositions1 Int
d Int
n) [Int
1..Int
n]
allCompositions' :: [Int] -> [[Composition]]
allCompositions' :: [Int] -> [[[Int]]]
allCompositions' [Int]
shape = forall a b. (a -> b) -> [a] -> [b]
map ([Int] -> Int -> [[Int]]
compositions' [Int]
shape) [Int
0..Int
d] where d :: Int
d = forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Int]
shape
compositions
:: Integral a
=> a
-> a
-> [[Int]]
compositions :: forall a. Integral a => a -> a -> [[Int]]
compositions a
len' a
d' = [Int] -> Int -> [[Int]]
compositions' (forall a. Int -> a -> [a]
replicate Int
len Int
d) Int
d where
len :: Int
len = forall a b. (Integral a, Num b) => a -> b
fromIntegral a
len'
d :: Int
d = forall a b. (Integral a, Num b) => a -> b
fromIntegral a
d'
countCompositions :: Integral a => a -> a -> Integer
countCompositions :: forall a. Integral a => a -> a -> Integer
countCompositions a
len a
d = forall a. Integral a => a -> a -> Integer
binomial (a
lenforall a. Num a => a -> a -> a
+a
dforall a. Num a => a -> a -> a
-a
1) (a
lenforall a. Num a => a -> a -> a
-a
1)
compositions1
:: Integral a
=> a
-> a
-> [[Int]]
compositions1 :: forall a. Integral a => a -> a -> [[Int]]
compositions1 a
len a
d
| a
len forall a. Ord a => a -> a -> Bool
> a
d = []
| Bool
otherwise = forall a b. (a -> b) -> [a] -> [b]
map [Int] -> [Int]
plus1 forall a b. (a -> b) -> a -> b
$ forall a. Integral a => a -> a -> [[Int]]
compositions a
len (a
dforall a. Num a => a -> a -> a
-a
len)
where
plus1 :: [Int] -> [Int]
plus1 = forall a b. (a -> b) -> [a] -> [b]
map (forall a. Num a => a -> a -> a
+Int
1)
countCompositions1 :: Integral a => a -> a -> Integer
countCompositions1 :: forall a. Integral a => a -> a -> Integer
countCompositions1 a
len a
d = forall a. Integral a => a -> a -> Integer
countCompositions a
len (a
dforall a. Num a => a -> a -> a
-a
len)
randomComposition :: RandomGen g => Int -> Int -> g -> ([Int],g)
randomComposition :: forall g. RandomGen g => Int -> Int -> g -> ([Int], g)
randomComposition Int
k Int
n g
g0 =
if Int
kforall a. Ord a => a -> a -> Bool
<Int
1 Bool -> Bool -> Bool
|| Int
nforall a. Ord a => a -> a -> Bool
<Int
0
then forall a. HasCallStack => [Char] -> a
error [Char]
"randomComposition: k should be positive, and n should be nonnegative"
else ([Int]
comp, g
g1)
where
([Int]
cs,g
g1) = forall g. RandomGen g => Int -> Int -> g -> ([Int], g)
randomChoice (Int
kforall a. Num a => a -> a -> a
-Int
1) (Int
nforall a. Num a => a -> a -> a
+Int
kforall a. Num a => a -> a -> a
-Int
1) g
g0
comp :: [Int]
comp = forall a b. (a -> a -> b) -> [a] -> [b]
pairsWith (\Int
x Int
y -> Int
yforall a. Num a => a -> a -> a
-Int
xforall a. Num a => a -> a -> a
-Int
1) (Int
0 forall a. a -> [a] -> [a]
: [Int]
cs forall a. [a] -> [a] -> [a]
++ [Int
nforall a. Num a => a -> a -> a
+Int
k])
randomComposition1 :: RandomGen g => Int -> Int -> g -> ([Int],g)
randomComposition1 :: forall g. RandomGen g => Int -> Int -> g -> ([Int], g)
randomComposition1 Int
k Int
n g
g0 =
if Int
kforall a. Ord a => a -> a -> Bool
<Int
1 Bool -> Bool -> Bool
|| Int
nforall a. Ord a => a -> a -> Bool
<Int
k
then forall a. HasCallStack => [Char] -> a
error [Char]
"randomComposition1: we require 0 < k <= n"
else ([Int]
comp, g
g1)
where
([Int]
cs,g
g1) = forall g. RandomGen g => Int -> Int -> g -> ([Int], g)
randomComposition Int
k (Int
nforall a. Num a => a -> a -> a
-Int
k) g
g0
comp :: [Int]
comp = forall a b. (a -> b) -> [a] -> [b]
map (forall a. Num a => a -> a -> a
+Int
1) [Int]
cs