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' [] 0 = [[]]
compositions' [] _ = []
compositions' shape@(s:ss) n = 
  [ x:xs | x <- [0..min s n] , xs <- compositions' ss (nx) ] 
countCompositions' :: [Int] -> Int -> Integer
countCompositions' [] 0 = 1
countCompositions' [] _ = 0
countCompositions' shape@(s:ss) n = sum 
  [ countCompositions' ss (nx) | x <- [0..min s n] ] 
allCompositions1 :: Int -> [[Composition]]
allCompositions1 n = map (\d -> compositions1 d n) [1..n] 
allCompositions' :: [Int] -> [[Composition]]
allCompositions' shape = map (compositions' shape) [0..d] where d = sum shape
compositions 
  :: Integral a 
  => a       
  -> a       
  -> [[Int]]
compositions len' d' = compositions' (replicate len d) d where
  len = fromIntegral len'
  d   = fromIntegral d'
countCompositions :: Integral a => a -> a -> Integer
countCompositions len d = binomial (len+d1) (len1)
compositions1  
  :: Integral a 
  => a       
  -> a       
  -> [[Int]]
compositions1 len d 
  | len > d   = []
  | otherwise = map plus1 $ compositions len (dlen)
  where
    plus1 = map (+1)
    
    
countCompositions1 :: Integral a => a -> a -> Integer
countCompositions1 len d = countCompositions len (dlen)
randomComposition :: RandomGen g => Int -> Int -> g -> ([Int],g)
randomComposition k n g0 = 
  if k<1 || n<0 
    then error "randomComposition: k should be positive, and n should be nonnegative" 
    else (comp, g1) 
  where
    (cs,g1) = randomChoice (k1) (n+k1) g0
    comp = pairsWith (\x y -> yx1) (0 : cs ++ [n+k])
  
randomComposition1 :: RandomGen g => Int -> Int -> g -> ([Int],g)
randomComposition1 k n g0 = 
  if k<1 || n<k 
    then error "randomComposition1: we require 0 < k <= n" 
    else (comp, g1) 
  where
    (cs,g1) = randomComposition k (nk) g0 
    comp = map (+1) cs