{-
	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 <http://www.gnu.org/licenses/>.
-}
{- |
 [@AUTHOR@]	Dr. Alistair Ward

 [@DESCRIPTION@]	Defines /QuickCheck/-properties for "Math.Probability".
-}

module Factory.Test.QuickCheck.Probability(
-- * Functions
	quickChecks
) where

import			Control.Arrow((&&&))
import qualified	Factory.Math.Probability		as Math.Probability
import qualified	Factory.Math.Statistics			as Math.Statistics
import			Factory.Test.QuickCheck.Factorial()
import qualified	ToolShed.Pair				as Pair
import qualified	System.Random
import qualified	Test.QuickCheck
import			Test.QuickCheck((==>))

-- | Defines invariant properties.
quickChecks :: IO ()
quickChecks	= do
	randomGen	<- System.Random.getStdGen

	(
		Test.QuickCheck.quickCheck (prop_normalDistribution randomGen)
		>> Test.QuickCheck.quickCheck (prop_poissonDistribution randomGen)
	 ) where
		prop_normalDistribution :: System.Random.RandomGen g => g -> (Double, Double) -> Test.QuickCheck.Property
		prop_normalDistribution randomGen (mean, variance)	= variance' /= 0	==> Test.QuickCheck.label "prop_normalDistribution" . Pair.both . Pair.mirror (
			(< (0.05 :: Double)) . abs	--Tolerance.
		 ) . (
			Math.Statistics.getMean &&& pred . Math.Statistics.getStandardDeviation
		 ) . map (
			(/ sqrt variance') . (+ negate mean)	--Standardize.
		 ) $ Math.Probability.generateContinuousPopulation 1000 (Math.Probability.NormalDistribution mean variance') randomGen	where
			variance'	= abs variance

		prop_poissonDistribution :: System.Random.RandomGen g => g -> Int -> Test.QuickCheck.Property
		prop_poissonDistribution randomGen lambda	= lambda' /= 0	==> Test.QuickCheck.label "prop_poissonDistribution" . Pair.both . Pair.mirror (
			(< (0.1 :: Double)) . abs	--Tolerance.
		 ) . (
			Math.Statistics.getMean &&& pred . Math.Statistics.getStandardDeviation
		 ) $ map (
			(/ sqrt lambda') . (+ negate lambda') . fromIntegral	--Standardize.
		 ) (
			Math.Probability.generateDiscretePopulation 1000 (Math.Probability.PoissonDistribution lambda') randomGen :: [Int]
		 ) where
			lambda' :: Double
			lambda'	= fromIntegral $ lambda `mod` 1000