{- Copyright (C) 2011 Dr. Alistair Ward This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} {- | [@AUTHOR@] Dr. Alistair Ward [@DESCRIPTION@] Defines /QuickCheck/-properties for "Math.Statistics". -} module Factory.Test.QuickCheck.Statistics( -- * Functions quickChecks ) where import qualified Data.List import qualified Data.Numbers.Primes import qualified Factory.Math.Implementations.Factorial as Math.Implementations.Factorial import qualified Factory.Math.Statistics as Math.Statistics import Factory.Test.QuickCheck.Factorial() import qualified Test.QuickCheck import Test.QuickCheck((==>)) -- | Defines invariant properties. quickChecks :: IO () quickChecks = Test.QuickCheck.quickCheck `mapM_` [prop_nC0, prop_nC1, prop_sum] >> Test.QuickCheck.quickCheck `mapM_` [prop_symmetry, prop_prime] >> Test.QuickCheck.quickCheck `mapM_` [prop_nP0, prop_nP1] >> Test.QuickCheck.quickCheck prop_balance where prop_nC0, prop_nC1, prop_sum :: Math.Implementations.Factorial.Algorithm -> Integer -> Test.QuickCheck.Property prop_nC0 algorithm n = Test.QuickCheck.label "prop_nC0" $ Math.Statistics.nCr algorithm (abs n) 0 == 1 prop_nC1 algorithm i = Test.QuickCheck.label "prop_nC1" $ Math.Statistics.nCr algorithm n 1 == n where n = 1 + abs i prop_sum algorithm i = Test.QuickCheck.label "prop_sum" $ sum (Math.Statistics.nCr algorithm n `map` [0 .. n]) == 2 ^ n where n = 1 + abs i prop_symmetry, prop_prime :: Math.Implementations.Factorial.Algorithm -> (Integer, Integer) -> Test.QuickCheck.Property prop_symmetry algorithm (i, j) = Test.QuickCheck.label "prop_symmetry" $ Math.Statistics.nCr algorithm n r == Math.Statistics.nCr algorithm n (n - r) where [r, n] = Data.List.sort $ map abs [i, j] prop_prime algorithm (i, j) = r `notElem` [0, n] ==> Test.QuickCheck.label "prop_prime" $ (Math.Statistics.nCr algorithm n r `mod` n) == 0 where n = Data.Numbers.Primes.primes !! fromIntegral (i `mod` 500000) r = j `mod` n --Ensure r is smaller than n. prop_nP0, prop_nP1 :: Integer -> Test.QuickCheck.Property prop_nP0 n = Test.QuickCheck.label "prop_nP0" $ Math.Statistics.nPr (abs n) 0 == 1 prop_nP1 i = Test.QuickCheck.label "prop_nP1" $ Math.Statistics.nPr n 1 == n where n = 1 + abs i prop_balance :: [Integer] -> Test.QuickCheck.Property prop_balance l = not (null l) ==> Test.QuickCheck.label "prop_balance" . (< 1e-11 {-rounding errors-}) . abs . sum $ map (\i -> fromIntegral i - (Math.Statistics.mean l :: Double)) l