-- | Extraction d’aléa.
--
-- NOTE: Afin de ne produire que des bits qui ont chacun
-- une probabilité d’un sur deux d’être à 'True' ou à 'False',
-- les fonctions de ce module n’extraient que les bits
-- des combinaisons de rang lexicographique strictement inférieur
-- à la plus grande puissance de 2 inférieure ou égale
-- au nombre de combinaisons possibles.
-- Car il n’y a que @2^n@ combinaisons de @n@ bits.
-- Et que parmi ces combinaisons un bit a une probabilité
-- de @2^(n-1)@ sur @2^n@ soit de @1/2@ d’être à 'True', et autant d’être à 'False'.
module Htirage.Random where

import Data.List

import Htirage.Bits
import Htirage.Combin

-- | @equiprobableBits n@ retourne le nombre maximal de bits de 'i'
-- équiprobables quand @i@ parcourt @[0..n-1]@.
--
-- Ce nombre est le plus grand 'b' dans @[0..]@ tel que @2^b-1 <= n@.
--
-- @
-- 'equiprobableBits' '<$>' [0..17] == [0,1,1,2,2,2,2,3,3,3,3,3,3,3,3,4,4,4]
-- @
equiprobableBits :: Integer -> Int
equiprobableBits n | n == 2^b-1 = b
                   | otherwise  = b-1
                   where b = nbBits n

-- | @randomOfCombin n k c@ retourne des bits équiprobables donnés
-- par la combinaison 'c' obtenue par tirage équiprobable
-- d’une combinaison de 'k' entiers parmi @[1..n]@.
--
-- WARNING: aucun bit n’est extrait du tirage 'c'
-- dans le cas où 'c' a un rang lexicographique encodé par
-- un nombre de bits strictement supérieur à @'equiprobableBits' (n`nCk`k)@.
randomOfCombin :: Integer -> Integer -> [Integer] -> [Bool]
randomOfCombin n k xs
 | 0<=n, 0<=k, k<=n
 , all (\x -> 1<=x&&x<=n) xs
 , length (nub xs) == length xs =
	if nbBits rank <= epBits
	then epBits `bitsOfInteger` rank
	else []
	where rank   = rankOfCombin n (sort xs)
	      epBits = equiprobableBits (n`nCk`k)
randomOfCombin _ _ _ = undefined

-- * Aléas publics

-- | @randomOf6aus49 nums numComplementaire@ retourne les bits équiprobables donnés
-- par un tirage du <https://www.lotto.de/de/ergebnisse/lotto-6aus49/archiv.html 6aus49>.
--
-- Il peut produire @26@ bits équiprobables :
-- @'sum' $ 'equiprobableBits' '<$>' [49\`nCk\`6, 10\`nCk\`1]@
--
-- @
-- 'randomOf6aus49' (1,2,3,4,5,6)      1 == 'replicate' (23+3) False
-- 'randomOf6aus49' (7,14,20,30,37,45) 8 == 'replicate' (23+3) True
-- 
-- 'combinOfRank' 49 6 (2 ^ 'equiprobableBits' (49`nCk`6) - 1) == [7,14,20,30,37,45]
-- 'combinOfRank' 49 6 (2 ^ 'equiprobableBits' (49`nCk`6))     == [7,14,20,30,37,46]
-- 'randomOf6aus49' (7,14,20,30,37,45) 1 == 'replicate' 23 True ++ 'replicate' 3 False
-- 'randomOf6aus49' (7,14,20,30,37,46) 1 == [False,False,False]
-- 
-- 'combinOfRank' 10 1 (2 ^ 'equiprobableBits' (10`nCk`1) - 1) == [8]
-- 'combinOfRank' 10 1 (2 ^ 'equiprobableBits' (10`nCk`1))     == [9]
-- 'randomOf6aus49' (7,14,20,30,37,46) 8 == [True,True,True]
-- 'randomOf6aus49' (7,14,20,30,37,46) 9 == []
-- @
randomOf6aus49 :: (Integer,Integer,Integer,Integer,Integer,Integer) -> Integer -> [Bool]
randomOf6aus49 (n1,n2,n3,n4,n5,n6) nc = randomOfCombin 49 6 [n1,n2,n3,n4,n5,n6] ++
                                        randomOfCombin 10 1 [nc]

-- | @randomOfEuroMillions nums numComplementaires@ retourne les bits équiprobables donnés
-- par un tirage de l’<https://www.fdj.fr/jeux/jeux-de-tirage/euromillions/resultats EuroMillions>.
--
-- Il peut produire @26@ bits équiprobables :
-- @'sum' $ 'equiprobableBits' '<$>' [50\`nCk\`5, 11\`nCk\`2]@
--
-- @
-- 'randomOfEuroMillions' (1,2,3,4,5)      (1,2) == 'replicate' (21+5) False
-- 'randomOfEuroMillions' (29,36,38,41,48) (1,9) == 'replicate' (21+5) True
-- 
-- 'combinOfRank' 50 5 (2 ^ 'equiprobableBits' (50`nCk`5) - 1) == [29,36,38,41,48]
-- 'combinOfRank' 50 5 (2 ^ 'equiprobableBits' (50`nCk`5))     == [29,36,38,41,49]
-- 'randomOfEuroMillions' (29,36,38,41,48) (1,2) == 'replicate' 21 True ++ 'replicate' 5 False
-- 'randomOfEuroMillions' (29,36,38,41,49) (1,2) == [False,False,False,False,False]
-- 
-- 'combinOfRank' 11 2 (2 ^ 'equiprobableBits' (11`nCk`2) - 1) == [4,9]
-- 'combinOfRank' 11 2 (2 ^ 'equiprobableBits' (11`nCk`2))     == [4,10]
-- 'randomOfEuroMillions' (29,36,38,41,49) (1,9)  == [True,True,True,True,True]
-- 'randomOfEuroMillions' (29,36,38,41,49) (1,10) == []
-- @
randomOfEuroMillions :: (Integer,Integer,Integer,Integer,Integer) -> (Integer,Integer) -> [Bool]
randomOfEuroMillions (n1,n2,n3,n4,n5) (nc1,nc2) = randomOfCombin 50 5 [n1,n2,n3,n4,n5] ++
                                                  randomOfCombin 11 2 [nc1,nc2]

-- | @randomOfFrenchLoto nums numComplementaire@ retourne les bits équiprobables donnés
-- par un tirage du <https://www.fdj.fr/jeux/jeux-de-tirage/loto/resultats/ Loto Français>.
--
-- Il peut produire @23@ bits équiprobables :
-- @'sum' $ 'equiprobableBits' '<$>' [49\`nCk\`5, 10\`nCk\`1]@
--
-- @
-- 'randomOfFrenchLoto' (1,2,3,4,5)     1 == 'replicate' (20+3) False
-- 'randomOfFrenchLoto' (7,27,36,40,46) 8 == 'replicate' (20+3) True
-- 
-- 'combinOfRank' 49 5 (2 ^ 'equiprobableBits' (49`nCk`5) - 1) == [7,27,36,40,46]
-- 'combinOfRank' 49 5 (2 ^ 'equiprobableBits' (49`nCk`5))     == [7,27,36,40,47]
-- 'randomOfFrenchLoto' (7,27,36,40,46) 1 == 'replicate' 20 True ++ 'replicate' 3 False
-- 'randomOfFrenchLoto' (7,27,36,40,47) 1 == [False,False,False]
-- 
-- 'combinOfRank' 10 1 (2 ^ 'equiprobableBits' (10`nCk`1) - 1) == [8]
-- 'combinOfRank' 10 1 (2 ^ 'equiprobableBits' (10`nCk`1))     == [9]
-- 'randomOfFrenchLoto' (7,27,36,40,47) 8 == [True,True,True]
-- 'randomOfFrenchLoto' (7,27,36,40,47) 9 == []
-- @
randomOfFrenchLoto :: (Integer,Integer,Integer,Integer,Integer) -> Integer -> [Bool]
randomOfFrenchLoto (n1,n2,n3,n4,n5) nc = randomOfCombin 49 5 [n1,n2,n3,n4,n5] ++
                                         randomOfCombin 10 1 [nc]

-- | @randomOfSwissLoto nums numComplementaire@ retourne les bits équiprobables donnés
-- par un tirage du <https://jeux.loro.ch/FR/1/SwissLoto#action=game-history SwissLoto>.
--
-- Il peut produire @24@ bits équiprobables :
-- @'sum' $ 'equiprobableBits' '<$>' [42\`nCk\`6, 6\`nCk\`1]@
--
-- @
-- 'randomOfSwissLoto' (1,2,3,4,5,6)       1 == 'replicate' (22+2) False
-- 'randomOfSwissLoto' (10,12,25,28,33,38) 4 == 'replicate' (22+2) True
-- 
-- 'combinOfRank' 42 6 (2 ^ 'equiprobableBits' (42`nCk`6) - 1) == [10,12,25,28,33,38]
-- 'combinOfRank' 42 6 (2 ^ 'equiprobableBits' (42`nCk`6))     == [10,12,25,28,33,39]
-- 'randomOfSwissLoto' (10,12,25,28,33,38) 1 == 'replicate' 22 True ++ 'replicate' 2 False
-- 'randomOfSwissLoto' (10,12,25,28,33,39) 1 == [False,False]
-- 
-- 'combinOfRank' 6 1 (2 ^ 'equiprobableBits' (6`nCk`1) - 1) == [4]
-- 'combinOfRank' 6 1 (2 ^ 'equiprobableBits' (6`nCk`1))     == [5]
-- 'randomOfSwissLoto' (10,12,25,28,33,39) 4 == [True,True]
-- 'randomOfSwissLoto' (10,12,25,28,33,39) 5 == []
-- @
randomOfSwissLoto :: (Integer,Integer,Integer,Integer,Integer,Integer) -> Integer -> [Bool]
randomOfSwissLoto (n1,n2,n3,n4,n5,n6) nc = randomOfCombin 42 6 [n1,n2,n3,n4,n5,n6] ++
                                           randomOfCombin  6 1 [nc]