{-
	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@]	Miscellaneous statistical functions.
-}

module Factory.Math.Statistics(
-- * Functions
	mean,
	nCr,
	nPr
) where

import			Control.Arrow((***))
import			Control.Parallel(par, pseq)
import qualified	Data.List
--import qualified	Factory.Data.PrimeFactors		as Data.PrimeFactors
--import		Factory.Data.PrimeFactors((>/<), (>*<))
import qualified	Factory.Math.Factorial			as Math.Factorial
import qualified	Factory.Math.Implementations.Factorial	as Math.Implementations.Factorial

-- | Determines the <http://en.wikipedia.org/wiki/Mean> of the supplied numbers.
mean :: (Real r, Fractional f) => [r] -> f
mean []	= error "Factory.Math.Statistics.mean:\tundefined result for specified null-list"
mean l	= uncurry (/) . (realToFrac *** fromIntegral) $ foldr (\s -> (+ s) *** succ) (0, 0 :: Int) l

-- | The number of unordered combinations of /r/ objects taken from /n/; <http://en.wikipedia.org/wiki/Combination>.
nCr :: (Math.Factorial.Algorithm factorialAlgorithm, Integral i)
	=> factorialAlgorithm
	-> i	-- ^ The total number of items from which to select.
	-> i	-- ^ The number of iterms in a sample.
	-> i	-- ^ The number of combinations.
nCr _ 0 _	= 1
nCr _ _ 0	= 1
nCr factorialAlgorithm n r
	| n < 0		= error $ "Factory.Math.Statistics.nCr:\tinvalid n; " ++ show n
	| r < 0		= error $ "Factory.Math.Statistics.nCr:\tinvalid r; " ++ show r
	| n < r		= 0
{-
	| otherwise	= uncurry div $ product' *** product' $ Math.Implementations.Factorial.primeFactors n >/< (
		Math.Implementations.Factorial.primeFactors r >*< Math.Implementations.Factorial.primeFactors (n - r)
	) where
		product'	= Data.PrimeFactors.product' (recip 2) 10
-}
	| otherwise	= numerator `par` (denominator `pseq` numerator `div` denominator)
	where
		[smaller, bigger]	= Data.List.sort [r, n - r]
		numerator		= Math.Implementations.Factorial.risingFactorial (bigger + 1) (n - bigger)
		denominator		= Math.Factorial.factorial factorialAlgorithm smaller

-- | The number of permutations of /r/ objects taken from /n/; <http://en.wikipedia.org/wiki/Permutations>.
nPr :: Integral i
	=> i	-- ^ The total number of items from which to select.
	-> i	-- ^ The number of items in a sample.
	-> i	-- ^ The number of permutations.
nPr 0 _	= 1
nPr _ 0	= 1
nPr n r
	| n < 0		= error $ "Factory.Math.Statistics.nPr:\tinvalid n; " ++ show n
	| r < 0		= error $ "Factory.Math.Statistics.nPr:\tinvalid r; " ++ show r
	| n < r		= 0
	| otherwise	= Math.Implementations.Factorial.fallingFactorial n r