Skip to content

Commit

Permalink
yampa-test: Test FRP.Yampa.Random.noise. Refs #248.
Browse files Browse the repository at this point in the history
This commit introduces a quickcheck-based unit test for the function
FRP.Yampa.Random.noise.

[ci skip]
  • Loading branch information
ivanperez-keera committed Jan 29, 2023
1 parent e0f4e6d commit 878d50c
Showing 1 changed file with 85 additions and 2 deletions.
87 changes: 85 additions & 2 deletions yampa-test/tests/Test/FRP/Yampa/Random.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE ForeignFunctionInterface #-}
-- |
-- Description : Test cases for signal functions working with random values.
-- Copyright : (c) Ivan Perez, 2023
Expand All @@ -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)

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, compliant with the definition of erfcf in
-- ANSI C.
erfc :: Float -> Float
erfc = realToFrac . erfcf . realToFrac

-- | ANSI C function erfcf defined in math.h
foreign import ccall "erfcf" erfcf :: CFloat -> CFloat

-- | Transform Signal Sample streams into streams of differences.
structure :: (a, [(b, a)]) -> (a, [(b, Maybe a)])
structure (x, xs) = (x, map (second Just) xs)

0 comments on commit 878d50c

Please sign in to comment.