diff --git a/yampa-test/tests/Test/FRP/Yampa/Random.hs b/yampa-test/tests/Test/FRP/Yampa/Random.hs index fb858b11..626a72d1 100644 --- a/yampa-test/tests/Test/FRP/Yampa/Random.hs +++ b/yampa-test/tests/Test/FRP/Yampa/Random.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE ForeignFunctionInterface #-} -- | -- Description : Test cases for signal functions working with random values. -- Copyright : (c) Ivan Perez, 2023 @@ -8,7 +9,89 @@ module Test.FRP.Yampa.Random ) where -import Test.Tasty (TestTree, testGroup) +import Data.Bits (Bits, bitSizeMaybe, popCount) +import Data.Maybe (fromMaybe) +import Data.Word (Word32, Word64) +import Foreign.C (CFloat(..)) +import System.Random (mkStdGen) +import Test.QuickCheck hiding (once, sample) +import Test.Tasty (TestTree, testGroup) +import Test.Tasty.QuickCheck (testProperty) + +import FRP.Yampa (embed, noise, second) +import FRP.Yampa.QuickCheck (Distribution (DistRandom), generateStream) +import FRP.Yampa.Stream (SignalSampleStream) + +foreign import ccall "erfcf" erfcf :: CFloat -> CFloat tests :: TestTree -tests = testGroup "Regression tests for FRP.Yampa.Random" [] +tests = testGroup "Regression tests for FRP.Yampa.Random" + [ testProperty "noise (0, qc)" propNoise ] + +-- * Noise (i.e. random signal generators) and stochastic processes + +propNoise :: Property +propNoise = + forAll genSeed $ \seed -> + forAll myStream $ \stream -> + isRandom (embed (noise (mkStdGen seed)) (structure stream) :: [Word32]) + where + -- Generator: Input stream. + -- + -- We provide a number of samples; otherwise, deviations might not indicate + -- lack of randomness for the signal function. + myStream :: Gen (SignalSampleStream ()) + myStream = + generateStream DistRandom (Nothing, Nothing) (Just (Left numSamples)) + + -- Generator: Random generator seed + genSeed :: Gen Int + genSeed = arbitrary + + -- Constant: Number of samples in the stream used for testing. + -- + -- This number has to be high; numbers 100 or below will likely not work. + numSamples :: Int + numSamples = 400 + +-- * Auxiliary definitions + +-- | Check whether a list of values exhibits randomness. +-- +-- This function implements the Frequence (Monobit) Test, as described in +-- Section 2.1 of "A Statistical Test Suite for Random and Pseudorandom Number +-- Generators for Cryptographic Applications", by Rukhin et al. +isRandom :: Bits a => [a] -> Bool +isRandom ls = pValue >= 0.01 + where + pValue = erfc (sObs / sqrt 2) + sObs = abs sn / sqrt n + n = fromIntegral $ elemSize * length ls + sn = sum $ map numConv ls + + -- Number of bits per element + elemSize :: Int + elemSize = + -- bitSizeMaybe ignores the argument, so it's ok if the list is empty + fromMaybe 0 $ bitSizeMaybe $ head ls + + -- | Substitute each digit e in the binary representation by 2e – 1 and add + -- the results. + numConv :: Bits a => a -> Float + numConv x = fromIntegral $ numOnes - numZeroes + where + numOnes = popCount x + numZeroes = elemSize - popCount x + + -- Number of bits per element + elemSize = fromMaybe 0 $ bitSizeMaybe x + +-- | Complementary Error Function. +-- +-- Defined in the ANSI C function erfc contained in math.h. +erfc :: Float -> Float +erfc = realToFrac . erfcf . realToFrac + +-- | Transform Signal Sample streams into streams of differences. +structure :: (a, [(b, a)]) -> (a, [(b, Maybe a)]) +structure (x, xs) = (x, map (second Just) xs)