module System.Random.Dice.Internal
where
import System.Entropy
import Control.Monad.IO.Class
import Control.Monad
import Control.Exception
import qualified Data.ByteString as B
import Data.Word
import Data.Conduit
import qualified Data.Conduit.List as CL
integralToBits :: (Integral n,Integral m)
=> Int
-> n
-> [m]
integralToBits b x = reverse $ integralToBits' 0 x
where
integralToBits' ns 0 = replicate (bns) 0
integralToBits' ns y =
let (a,res) = quotRem y 2 in
fromIntegral res : integralToBits' (ns+1) a
bitsToIntegral :: (Integral n) =>[n] -> n
bitsToIntegral = extendIntegralWithBits 0
extendIntegralWithBits :: (Integral n) => n -> [n] -> n
extendIntegralWithBits n = foldr (\c r -> 2*r + c) n . reverse
upperBound :: Word64
upperBound = 2^(55 :: Int)
getDiceRolls :: Int
-> Int
-> IO [Int]
getDiceRolls n len =
systemEntropy $$ diceRolls n =$= CL.take len
getRandomRs :: (Int,Int)
-> Int
-> IO [Int]
getRandomRs range len =
systemEntropy $$ randomRs range =$= CL.take len
diceRolls :: Int -> Conduit Word8 IO Int
diceRolls n
| fromIntegral n > upperBound || n <= 0
= throw $ AssertionFailed "diceRolls: n-sided dice are supported, for 1 <= n < 2^55."
| n == 1
= CL.sourceList [0,0..]
| otherwise
= dRoll (fromIntegral n) 1 0 =$= CL.map fst
randomRs :: (Int,Int)
-> Conduit Word8 IO Int
randomRs (low,up) = diceRolls (uplow+1) =$= CL.map (+low)
systemEntropy :: Producer IO Word8
systemEntropy = do
bytes <- B.unpack `liftM` liftIO (getEntropy 8)
forM_ bytes yield
systemEntropy
dRoll :: Word64 -> Word64 -> Word64 -> Conduit Word8 IO (Int,Int)
dRoll n m r = do
let k = ceiling $ (logBase 2 (fromIntegral upperBound) logBase 2 (fromIntegral m :: Double)) / 8
let m' = 2^(8*k) * m
bits <- (concatMap (integralToBits 8) . B.unpack)
`liftM` (if k>0 then liftIO $ getEntropy k else return $ B.pack [])
let w64 = extendIntegralWithBits r bits
let q = m' `div` n
if w64 < n * q
then do
yield (fromIntegral $ w64 `mod` n,k)
dRoll n q (w64 `div` n)
else dRoll n (m' n*q) (w64 n*q)
testPerformance :: Int
-> Int
-> IO ()
testPerformance n len
| fromIntegral n > upperBound
= throw $ AssertionFailed "dice: range must be within Word64 bounds."
| otherwise = do
nbits <- systemEntropy $= dRoll (fromIntegral n) 1 0
$$ CL.take len
>>= return . sum . map snd
putStrLn $ "Generated " ++ show len
++ " random samples in range [0," ++ show (n1) ++ "]"
putStrLn $ "Average number of bits used: "
++ show (8*fromIntegral nbits/ fromIntegral len :: Double)
let lbound = logBase 2 (fromIntegral n) :: Double
putStrLn $ "Entropy lower bound on the number of required bits: "
++ show lbound
putStrLn $ "Performance ratio: " ++ show (((8*fromIntegral nbits
/ fromIntegral len) ::Double) / lbound)