module Crypto.Random.Test
( RandomTestState
, RandomTestResult(..)
, randomTestInitialize
, randomTestAppend
, randomTestFinalize
) where
import Data.Word
import Data.Int (Int64)
import qualified Data.ByteString.Lazy as L
import Control.Applicative
import Data.List (foldl')
import qualified Data.Vector.Mutable as M
import qualified Data.Vector as V
data RandomTestResult = RandomTestResult
{ res_totalChars :: Word64
, res_entropy :: Double
, res_chi_square :: Double
, res_mean :: Double
, res_compressionPercent :: Double
, res_probs :: [Double]
} deriving (Show,Eq)
newtype RandomTestState = RandomTestState (M.IOVector Word64)
randomTestInitialize :: IO RandomTestState
randomTestInitialize = RandomTestState <$> M.replicate 256 0
randomTestAppend :: RandomTestState -> L.ByteString -> IO ()
randomTestAppend (RandomTestState buckets) = loop
where loop bs
| L.null bs = return ()
| otherwise = do
let (b1,b2) = L.splitAt monteN bs
mapM_ (addVec 1 . fromIntegral) $ L.unpack b1
loop b2
addVec :: Word64 -> Int -> IO ()
addVec a i = M.read buckets i >>= \d -> M.write buckets i $! d+a
randomTestFinalize :: RandomTestState -> IO RandomTestResult
randomTestFinalize (RandomTestState buckets) = (calculate . V.toList) `fmap` V.freeze buckets
monteN :: Int64
monteN = 6
calculate :: [Word64] -> RandomTestResult
calculate buckets = RandomTestResult
{ res_totalChars = totalChars
, res_entropy = entropy
, res_chi_square = chisq
, res_mean = fromIntegral datasum / fromIntegral totalChars
, res_compressionPercent = 100.0 * (8 entropy) / 8.0
, res_probs = probs
}
where totalChars = sum buckets
probs = map (\v -> fromIntegral v / fromIntegral totalChars :: Double) buckets
entropy = foldl' accEnt 0.0 probs
cexp = fromIntegral totalChars / 256.0 :: Double
(datasum, chisq) = foldl' accMeanChi (0, 0.0) [0..255]
accEnt ent pr
| pr > 0.0 = ent + (pr * xlog (1 / pr))
| otherwise = ent
xlog v = logBase 10 v * (log 10 / log 2)
accMeanChi :: (Word64, Double) -> Int -> (Word64, Double)
accMeanChi (dataSum, chiSq) i =
let ccount = buckets !! i
a = fromIntegral ccount cexp
in (dataSum + fromIntegral i * ccount, chiSq + (a * a / cexp))