{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
module Statistics.Distribution.Hypergeometric
(
HypergeometricDistribution
, hypergeometric
, hypergeometricE
, hdM
, hdL
, hdK
) where
import Control.Applicative
import Data.Aeson (FromJSON(..), ToJSON, Value(..), (.:))
import Data.Binary (Binary(..))
import Data.Data (Data, Typeable)
import GHC.Generics (Generic)
import Numeric.MathFunctions.Constants (m_epsilon,m_neg_inf)
import Numeric.SpecFunctions (choose,logChoose)
import qualified Statistics.Distribution as D
import Statistics.Internal
data HypergeometricDistribution = HD {
HypergeometricDistribution -> Int
hdM :: {-# UNPACK #-} !Int
, HypergeometricDistribution -> Int
hdL :: {-# UNPACK #-} !Int
, HypergeometricDistribution -> Int
hdK :: {-# UNPACK #-} !Int
} deriving (HypergeometricDistribution -> HypergeometricDistribution -> Bool
(HypergeometricDistribution -> HypergeometricDistribution -> Bool)
-> (HypergeometricDistribution
-> HypergeometricDistribution -> Bool)
-> Eq HypergeometricDistribution
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HypergeometricDistribution -> HypergeometricDistribution -> Bool
$c/= :: HypergeometricDistribution -> HypergeometricDistribution -> Bool
== :: HypergeometricDistribution -> HypergeometricDistribution -> Bool
$c== :: HypergeometricDistribution -> HypergeometricDistribution -> Bool
Eq, Typeable, Typeable HypergeometricDistribution
DataType
Constr
Typeable HypergeometricDistribution
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> HypergeometricDistribution
-> c HypergeometricDistribution)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HypergeometricDistribution)
-> (HypergeometricDistribution -> Constr)
-> (HypergeometricDistribution -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c HypergeometricDistribution))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HypergeometricDistribution))
-> ((forall b. Data b => b -> b)
-> HypergeometricDistribution -> HypergeometricDistribution)
-> (forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> HypergeometricDistribution
-> r)
-> (forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> HypergeometricDistribution
-> r)
-> (forall u.
(forall d. Data d => d -> u) -> HypergeometricDistribution -> [u])
-> (forall u.
Int
-> (forall d. Data d => d -> u) -> HypergeometricDistribution -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HypergeometricDistribution -> m HypergeometricDistribution)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HypergeometricDistribution -> m HypergeometricDistribution)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HypergeometricDistribution -> m HypergeometricDistribution)
-> Data HypergeometricDistribution
HypergeometricDistribution -> DataType
HypergeometricDistribution -> Constr
(forall b. Data b => b -> b)
-> HypergeometricDistribution -> HypergeometricDistribution
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> HypergeometricDistribution
-> c HypergeometricDistribution
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HypergeometricDistribution
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int
-> (forall d. Data d => d -> u) -> HypergeometricDistribution -> u
forall u.
(forall d. Data d => d -> u) -> HypergeometricDistribution -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> HypergeometricDistribution
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> HypergeometricDistribution
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HypergeometricDistribution -> m HypergeometricDistribution
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HypergeometricDistribution -> m HypergeometricDistribution
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HypergeometricDistribution
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> HypergeometricDistribution
-> c HypergeometricDistribution
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c HypergeometricDistribution)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HypergeometricDistribution)
$cHD :: Constr
$tHypergeometricDistribution :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> HypergeometricDistribution -> m HypergeometricDistribution
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HypergeometricDistribution -> m HypergeometricDistribution
gmapMp :: (forall d. Data d => d -> m d)
-> HypergeometricDistribution -> m HypergeometricDistribution
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> HypergeometricDistribution -> m HypergeometricDistribution
gmapM :: (forall d. Data d => d -> m d)
-> HypergeometricDistribution -> m HypergeometricDistribution
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> HypergeometricDistribution -> m HypergeometricDistribution
gmapQi :: Int
-> (forall d. Data d => d -> u) -> HypergeometricDistribution -> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u) -> HypergeometricDistribution -> u
gmapQ :: (forall d. Data d => d -> u) -> HypergeometricDistribution -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> HypergeometricDistribution -> [u]
gmapQr :: (r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> HypergeometricDistribution
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> HypergeometricDistribution
-> r
gmapQl :: (r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> HypergeometricDistribution
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> HypergeometricDistribution
-> r
gmapT :: (forall b. Data b => b -> b)
-> HypergeometricDistribution -> HypergeometricDistribution
$cgmapT :: (forall b. Data b => b -> b)
-> HypergeometricDistribution -> HypergeometricDistribution
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HypergeometricDistribution)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c HypergeometricDistribution)
dataCast1 :: (forall d. Data d => c (t d))
-> Maybe (c HypergeometricDistribution)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c HypergeometricDistribution)
dataTypeOf :: HypergeometricDistribution -> DataType
$cdataTypeOf :: HypergeometricDistribution -> DataType
toConstr :: HypergeometricDistribution -> Constr
$ctoConstr :: HypergeometricDistribution -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HypergeometricDistribution
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c HypergeometricDistribution
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> HypergeometricDistribution
-> c HypergeometricDistribution
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> HypergeometricDistribution
-> c HypergeometricDistribution
$cp1Data :: Typeable HypergeometricDistribution
Data, (forall x.
HypergeometricDistribution -> Rep HypergeometricDistribution x)
-> (forall x.
Rep HypergeometricDistribution x -> HypergeometricDistribution)
-> Generic HypergeometricDistribution
forall x.
Rep HypergeometricDistribution x -> HypergeometricDistribution
forall x.
HypergeometricDistribution -> Rep HypergeometricDistribution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep HypergeometricDistribution x -> HypergeometricDistribution
$cfrom :: forall x.
HypergeometricDistribution -> Rep HypergeometricDistribution x
Generic)
instance Show HypergeometricDistribution where
showsPrec :: Int -> HypergeometricDistribution -> ShowS
showsPrec Int
i (HD Int
m Int
l Int
k) = String -> Int -> Int -> Int -> Int -> ShowS
forall a b c.
(Show a, Show b, Show c) =>
String -> a -> b -> c -> Int -> ShowS
defaultShow3 String
"hypergeometric" Int
m Int
l Int
k Int
i
instance Read HypergeometricDistribution where
readPrec :: ReadPrec HypergeometricDistribution
readPrec = String
-> (Int -> Int -> Int -> Maybe HypergeometricDistribution)
-> ReadPrec HypergeometricDistribution
forall a b c r.
(Read a, Read b, Read c) =>
String -> (a -> b -> c -> Maybe r) -> ReadPrec r
defaultReadPrecM3 String
"hypergeometric" Int -> Int -> Int -> Maybe HypergeometricDistribution
hypergeometricE
instance ToJSON HypergeometricDistribution
instance FromJSON HypergeometricDistribution where
parseJSON :: Value -> Parser HypergeometricDistribution
parseJSON (Object Object
v) = do
Int
m <- Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"hdM"
Int
l <- Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"hdL"
Int
k <- Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"hdK"
Parser HypergeometricDistribution
-> (HypergeometricDistribution
-> Parser HypergeometricDistribution)
-> Maybe HypergeometricDistribution
-> Parser HypergeometricDistribution
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Parser HypergeometricDistribution
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser HypergeometricDistribution)
-> String -> Parser HypergeometricDistribution
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> String
errMsg Int
m Int
l Int
k) HypergeometricDistribution -> Parser HypergeometricDistribution
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe HypergeometricDistribution
-> Parser HypergeometricDistribution)
-> Maybe HypergeometricDistribution
-> Parser HypergeometricDistribution
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> Maybe HypergeometricDistribution
hypergeometricE Int
m Int
l Int
k
parseJSON Value
_ = Parser HypergeometricDistribution
forall (f :: * -> *) a. Alternative f => f a
empty
instance Binary HypergeometricDistribution where
put :: HypergeometricDistribution -> Put
put (HD Int
m Int
l Int
k) = Int -> Put
forall t. Binary t => t -> Put
put Int
m Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> Put
forall t. Binary t => t -> Put
put Int
l Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> Put
forall t. Binary t => t -> Put
put Int
k
get :: Get HypergeometricDistribution
get = do
Int
m <- Get Int
forall t. Binary t => Get t
get
Int
l <- Get Int
forall t. Binary t => Get t
get
Int
k <- Get Int
forall t. Binary t => Get t
get
Get HypergeometricDistribution
-> (HypergeometricDistribution -> Get HypergeometricDistribution)
-> Maybe HypergeometricDistribution
-> Get HypergeometricDistribution
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Get HypergeometricDistribution
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get HypergeometricDistribution)
-> String -> Get HypergeometricDistribution
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> String
errMsg Int
m Int
l Int
k) HypergeometricDistribution -> Get HypergeometricDistribution
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe HypergeometricDistribution
-> Get HypergeometricDistribution)
-> Maybe HypergeometricDistribution
-> Get HypergeometricDistribution
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> Maybe HypergeometricDistribution
hypergeometricE Int
m Int
l Int
k
instance D.Distribution HypergeometricDistribution where
cumulative :: HypergeometricDistribution -> Double -> Double
cumulative = HypergeometricDistribution -> Double -> Double
cumulative
instance D.DiscreteDistr HypergeometricDistribution where
probability :: HypergeometricDistribution -> Int -> Double
probability = HypergeometricDistribution -> Int -> Double
probability
logProbability :: HypergeometricDistribution -> Int -> Double
logProbability = HypergeometricDistribution -> Int -> Double
logProbability
instance D.Mean HypergeometricDistribution where
mean :: HypergeometricDistribution -> Double
mean = HypergeometricDistribution -> Double
mean
instance D.Variance HypergeometricDistribution where
variance :: HypergeometricDistribution -> Double
variance = HypergeometricDistribution -> Double
variance
instance D.MaybeMean HypergeometricDistribution where
maybeMean :: HypergeometricDistribution -> Maybe Double
maybeMean = Double -> Maybe Double
forall a. a -> Maybe a
Just (Double -> Maybe Double)
-> (HypergeometricDistribution -> Double)
-> HypergeometricDistribution
-> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HypergeometricDistribution -> Double
forall d. Mean d => d -> Double
D.mean
instance D.MaybeVariance HypergeometricDistribution where
maybeStdDev :: HypergeometricDistribution -> Maybe Double
maybeStdDev = Double -> Maybe Double
forall a. a -> Maybe a
Just (Double -> Maybe Double)
-> (HypergeometricDistribution -> Double)
-> HypergeometricDistribution
-> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HypergeometricDistribution -> Double
forall d. Variance d => d -> Double
D.stdDev
maybeVariance :: HypergeometricDistribution -> Maybe Double
maybeVariance = Double -> Maybe Double
forall a. a -> Maybe a
Just (Double -> Maybe Double)
-> (HypergeometricDistribution -> Double)
-> HypergeometricDistribution
-> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HypergeometricDistribution -> Double
forall d. Variance d => d -> Double
D.variance
instance D.Entropy HypergeometricDistribution where
entropy :: HypergeometricDistribution -> Double
entropy = HypergeometricDistribution -> Double
directEntropy
instance D.MaybeEntropy HypergeometricDistribution where
maybeEntropy :: HypergeometricDistribution -> Maybe Double
maybeEntropy = Double -> Maybe Double
forall a. a -> Maybe a
Just (Double -> Maybe Double)
-> (HypergeometricDistribution -> Double)
-> HypergeometricDistribution
-> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HypergeometricDistribution -> Double
forall d. Entropy d => d -> Double
D.entropy
variance :: HypergeometricDistribution -> Double
variance :: HypergeometricDistribution -> Double
variance (HD Int
m Int
l Int
k) = (Double
k' Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
ml) Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
ml) Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Double
l' Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
k') Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Double
l' Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
1)
where m' :: Double
m' = Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
m
l' :: Double
l' = Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l
k' :: Double
k' = Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k
ml :: Double
ml = Double
m' Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
l'
mean :: HypergeometricDistribution -> Double
mean :: HypergeometricDistribution -> Double
mean (HD Int
m Int
l Int
k) = Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k Double -> Double -> Double
forall a. Num a => a -> a -> a
* Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
m Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l
directEntropy :: HypergeometricDistribution -> Double
directEntropy :: HypergeometricDistribution -> Double
directEntropy d :: HypergeometricDistribution
d@(HD Int
m Int
_ Int
_)
= Double -> Double
forall a. Num a => a -> a
negate (Double -> Double) -> ([Double] -> Double) -> [Double] -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum
([Double] -> Double) -> [Double] -> Double
forall a b. (a -> b) -> a -> b
$ (Double -> Bool) -> [Double] -> [Double]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double -> Double
forall a. Num a => a -> a
negate Double
m_epsilon)
([Double] -> [Double]) -> [Double] -> [Double]
forall a b. (a -> b) -> a -> b
$ (Double -> Bool) -> [Double] -> [Double]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Bool -> Bool
not (Bool -> Bool) -> (Double -> Bool) -> Double -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double -> Double
forall a. Num a => a -> a
negate Double
m_epsilon))
[ let x :: Double
x = HypergeometricDistribution -> Int -> Double
probability HypergeometricDistribution
d Int
n in Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double -> Double
forall a. Floating a => a -> a
log Double
x | Int
n <- [Int
0..Int
m]]
hypergeometric :: Int
-> Int
-> Int
-> HypergeometricDistribution
hypergeometric :: Int -> Int -> Int -> HypergeometricDistribution
hypergeometric Int
m Int
l Int
k
= HypergeometricDistribution
-> (HypergeometricDistribution -> HypergeometricDistribution)
-> Maybe HypergeometricDistribution
-> HypergeometricDistribution
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> HypergeometricDistribution
forall a. HasCallStack => String -> a
error (String -> HypergeometricDistribution)
-> String -> HypergeometricDistribution
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> String
errMsg Int
m Int
l Int
k) HypergeometricDistribution -> HypergeometricDistribution
forall a. a -> a
id (Maybe HypergeometricDistribution -> HypergeometricDistribution)
-> Maybe HypergeometricDistribution -> HypergeometricDistribution
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> Maybe HypergeometricDistribution
hypergeometricE Int
m Int
l Int
k
hypergeometricE :: Int
-> Int
-> Int
-> Maybe HypergeometricDistribution
hypergeometricE :: Int -> Int -> Int -> Maybe HypergeometricDistribution
hypergeometricE Int
m Int
l Int
k
| Bool -> Bool
not (Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) = Maybe HypergeometricDistribution
forall a. Maybe a
Nothing
| Bool -> Bool
not (Int
m Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
m Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
l) = Maybe HypergeometricDistribution
forall a. Maybe a
Nothing
| Bool -> Bool
not (Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
&& Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
l) = Maybe HypergeometricDistribution
forall a. Maybe a
Nothing
| Bool
otherwise = HypergeometricDistribution -> Maybe HypergeometricDistribution
forall a. a -> Maybe a
Just (Int -> Int -> Int -> HypergeometricDistribution
HD Int
m Int
l Int
k)
errMsg :: Int -> Int -> Int -> String
errMsg :: Int -> Int -> Int -> String
errMsg Int
m Int
l Int
k
= String
"Statistics.Distribution.Hypergeometric.hypergeometric: "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"m=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
m
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"l=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
l
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"k=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
k
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" should hold: l>0 & m in [0,l] & k in (0,l]"
probability :: HypergeometricDistribution -> Int -> Double
probability :: HypergeometricDistribution -> Int -> Double
probability (HD Int
mi Int
li Int
ki) Int
n
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int
miInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
kiInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
li) Bool -> Bool -> Bool
|| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
mi Int
ki = Double
0
| Int
li Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1000 = Int -> Int -> Double
choose Int
mi Int
n Double -> Double -> Double
forall a. Num a => a -> a -> a
* Int -> Int -> Double
choose (Int
li Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
mi) (Int
ki Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n)
Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Int -> Int -> Double
choose Int
li Int
ki
| Bool
otherwise = Double -> Double
forall a. Floating a => a -> a
exp (Double -> Double) -> Double -> Double
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Double
logChoose Int
mi Int
n
Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Int -> Int -> Double
logChoose (Int
li Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
mi) (Int
ki Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n)
Double -> Double -> Double
forall a. Num a => a -> a -> a
- Int -> Int -> Double
logChoose Int
li Int
ki
logProbability :: HypergeometricDistribution -> Int -> Double
logProbability :: HypergeometricDistribution -> Int -> Double
logProbability (HD Int
mi Int
li Int
ki) Int
n
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int
miInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
kiInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
li) Bool -> Bool -> Bool
|| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
mi Int
ki = Double
m_neg_inf
| Bool
otherwise = Int -> Int -> Double
logChoose Int
mi Int
n
Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Int -> Int -> Double
logChoose (Int
li Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
mi) (Int
ki Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n)
Double -> Double -> Double
forall a. Num a => a -> a -> a
- Int -> Int -> Double
logChoose Int
li Int
ki
cumulative :: HypergeometricDistribution -> Double -> Double
cumulative :: HypergeometricDistribution -> Double -> Double
cumulative d :: HypergeometricDistribution
d@(HD Int
mi Int
li Int
ki) Double
x
| Double -> Bool
forall a. RealFloat a => a -> Bool
isNaN Double
x = String -> Double
forall a. HasCallStack => String -> a
error String
"Statistics.Distribution.Hypergeometric.cumulative: NaN argument"
| Double -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Double
x = if Double
x Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 then Double
1 else Double
0
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
minN = Double
0
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
maxN = Double
1
| Bool
otherwise = HypergeometricDistribution -> Int -> Int -> Double
forall d. DiscreteDistr d => d -> Int -> Int -> Double
D.sumProbabilities HypergeometricDistribution
d Int
minN Int
n
where
n :: Int
n = Double -> Int
forall a b. (RealFrac a, Integral b) => a -> b
floor Double
x
minN :: Int
minN = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int
miInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
kiInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
li)
maxN :: Int
maxN = Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
mi Int
ki