{-# LANGUAGE OverloadedStrings #-}{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}-- |-- Module : Statistics.Distribution.Hypergeometric-- Copyright : (c) 2009 Bryan O'Sullivan-- License : BSD3---- Maintainer : bos@serpentine.com-- Stability : experimental-- Portability : portable---- The Hypergeometric distribution. This is the discrete probability-- distribution that measures the probability of /k/ successes in /l/-- trials, without replacement, from a finite population.---- The parameters of the distribution describe /k/ elements chosen-- from a population of /l/, with /m/ elements of one type, and-- /l/-/m/ of the other (all are positive integers).moduleStatistics.Distribution.Hypergeometric(HypergeometricDistribution -- * Constructors,hypergeometric ,hypergeometricE -- ** Accessors,hdM ,hdL ,hdK )whereimportControl.ApplicativeimportData.Aeson(FromJSON(..),ToJSON,Value(..),(.:))importData.Binary(Binary(..))importData.Data(Data,Typeable)importGHC.Generics(Generic)importNumeric.MathFunctions.Constants(m_epsilon,m_neg_inf)importNumeric.SpecFunctions(choose,logChoose)importqualifiedStatistics.Distribution asDimportStatistics.Internal dataHypergeometricDistribution =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 $c== :: HypergeometricDistribution -> HypergeometricDistribution -> Bool == :: HypergeometricDistribution -> HypergeometricDistribution -> Bool $c/= :: HypergeometricDistribution -> HypergeometricDistribution -> Bool /= :: HypergeometricDistribution -> HypergeometricDistribution -> Bool Eq,Typeable,Typeable HypergeometricDistribution 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 -> Constr HypergeometricDistribution -> DataType (forall b. Data b => b -> b) -> HypergeometricDistribution -> 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) $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HypergeometricDistribution -> c HypergeometricDistribution gfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HypergeometricDistribution -> c HypergeometricDistribution $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HypergeometricDistribution gunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HypergeometricDistribution $ctoConstr :: HypergeometricDistribution -> Constr toConstr :: HypergeometricDistribution -> Constr $cdataTypeOf :: HypergeometricDistribution -> DataType dataTypeOf :: HypergeometricDistribution -> DataType $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HypergeometricDistribution) dataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HypergeometricDistribution) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HypergeometricDistribution) dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HypergeometricDistribution) $cgmapT :: (forall b. Data b => b -> b) -> HypergeometricDistribution -> HypergeometricDistribution gmapT :: (forall b. Data b => b -> b) -> HypergeometricDistribution -> HypergeometricDistribution $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HypergeometricDistribution -> r gmapQl :: forall r r'. (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 gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HypergeometricDistribution -> r $cgmapQ :: forall u. (forall d. Data d => d -> u) -> HypergeometricDistribution -> [u] gmapQ :: forall u. (forall d. Data d => d -> u) -> HypergeometricDistribution -> [u] $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> HypergeometricDistribution -> u gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> HypergeometricDistribution -> u $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> HypergeometricDistribution -> m HypergeometricDistribution gmapM :: forall (m :: * -> *). Monad m => (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 gmapMp :: forall (m :: * -> *). MonadPlus m => (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 gmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> HypergeometricDistribution -> m 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 $cfrom :: forall x. HypergeometricDistribution -> Rep HypergeometricDistribution x from :: forall x. HypergeometricDistribution -> Rep HypergeometricDistribution x $cto :: forall x. Rep HypergeometricDistribution x -> HypergeometricDistribution to :: forall x. Rep HypergeometricDistribution x -> HypergeometricDistribution Generic)instanceShowHypergeometricDistribution whereshowsPrec :: Int -> HypergeometricDistribution -> ShowS showsPrec Int i (HD Int m Int l Int k )=[Char] -> Int -> Int -> Int -> Int -> ShowS forall a b c. (Show a, Show b, Show c) => [Char] -> a -> b -> c -> Int -> ShowS defaultShow3 [Char] "hypergeometric"Int m Int l Int k Int i instanceReadHypergeometricDistribution wherereadPrec :: ReadPrec HypergeometricDistribution readPrec =[Char] -> (Int -> Int -> Int -> Maybe HypergeometricDistribution) -> ReadPrec HypergeometricDistribution forall a b c r. (Read a, Read b, Read c) => [Char] -> (a -> b -> c -> Maybe r) -> ReadPrec r defaultReadPrecM3 [Char] "hypergeometric"Int -> Int -> Int -> Maybe HypergeometricDistribution hypergeometricE instanceToJSONHypergeometricDistribution instanceFromJSONHypergeometricDistribution whereparseJSON :: Value -> Parser HypergeometricDistribution parseJSON (ObjectObject v )=doInt 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([Char] -> Parser HypergeometricDistribution forall a. [Char] -> Parser a forall (m :: * -> *) a. MonadFail m => [Char] -> m a fail([Char] -> Parser HypergeometricDistribution) -> [Char] -> Parser HypergeometricDistribution forall a b. (a -> b) -> a -> b $Int -> Int -> Int -> [Char] errMsg Int m Int l Int k )HypergeometricDistribution -> Parser HypergeometricDistribution forall a. a -> Parser a 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 parseJSONValue _=Parser HypergeometricDistribution forall a. Parser a forall (f :: * -> *) a. Alternative f => f a emptyinstanceBinaryHypergeometricDistribution whereput :: HypergeometricDistribution -> Put put (HD Int m Int l Int k )=Int -> Put forall t. Binary t => t -> Put putInt m Put -> Put -> Put forall a b. PutM a -> PutM b -> PutM b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >>Int -> Put forall t. Binary t => t -> Put putInt l Put -> Put -> Put forall a b. PutM a -> PutM b -> PutM b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >>Int -> Put forall t. Binary t => t -> Put putInt k get :: Get HypergeometricDistribution get =doInt m <-Get Int forall t. Binary t => Get t getInt l <-Get Int forall t. Binary t => Get t getInt k <-Get Int forall t. Binary t => Get t getGet HypergeometricDistribution -> (HypergeometricDistribution -> Get HypergeometricDistribution) -> Maybe HypergeometricDistribution -> Get HypergeometricDistribution forall b a. b -> (a -> b) -> Maybe a -> b maybe([Char] -> Get HypergeometricDistribution forall a. [Char] -> Get a forall (m :: * -> *) a. MonadFail m => [Char] -> m a fail([Char] -> Get HypergeometricDistribution) -> [Char] -> Get HypergeometricDistribution forall a b. (a -> b) -> a -> b $Int -> Int -> Int -> [Char] errMsg Int m Int l Int k )HypergeometricDistribution -> Get HypergeometricDistribution forall a. a -> Get a 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 instanceD.Distribution HypergeometricDistribution wherecumulative :: HypergeometricDistribution -> Double -> Double cumulative =HypergeometricDistribution -> Double -> Double cumulative complCumulative :: HypergeometricDistribution -> Double -> Double complCumulative =HypergeometricDistribution -> Double -> Double complCumulative instanceD.DiscreteDistr HypergeometricDistribution whereprobability :: HypergeometricDistribution -> Int -> Double probability =HypergeometricDistribution -> Int -> Double probability logProbability :: HypergeometricDistribution -> Int -> Double logProbability =HypergeometricDistribution -> Int -> Double logProbability instanceD.Mean HypergeometricDistribution wheremean :: HypergeometricDistribution -> Double mean =HypergeometricDistribution -> Double mean instanceD.Variance HypergeometricDistribution wherevariance :: HypergeometricDistribution -> Double variance =HypergeometricDistribution -> Double variance instanceD.MaybeMean HypergeometricDistribution wheremaybeMean :: 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 instanceD.MaybeVariance HypergeometricDistribution wheremaybeStdDev :: 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 instanceD.Entropy HypergeometricDistribution whereentropy :: HypergeometricDistribution -> Double entropy =HypergeometricDistribution -> Double directEntropy instanceD.MaybeEntropy HypergeometricDistribution wheremaybeEntropy :: 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 ->Doublevariance :: 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 1Double -> 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)wherem' :: Double m' =Int -> Double forall a b. (Integral a, Num b) => a -> b fromIntegralInt m l' :: Double l' =Int -> Double forall a b. (Integral a, Num b) => a -> b fromIntegralInt l k' :: Double k' =Int -> Double forall a b. (Integral a, Num b) => a -> b fromIntegralInt k ml :: Double ml =Double m' Double -> Double -> Double forall a. Fractional a => a -> a -> a /Double l' mean ::HypergeometricDistribution ->Doublemean :: HypergeometricDistribution -> Double mean (HD Int m Int l Int k )=Int -> Double forall a b. (Integral a, Num b) => a -> b fromIntegralInt k Double -> Double -> Double forall a. Num a => a -> a -> a *Int -> Double forall a b. (Integral a, Num b) => a -> b fromIntegralInt m Double -> Double -> Double forall a. Fractional a => a -> a -> a /Int -> Double forall a b. (Integral a, Num b) => a -> b fromIntegralInt l directEntropy ::HypergeometricDistribution ->DoubledirectEntropy :: 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 a. Num a => [a] -> a 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 negateDouble 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 negateDouble m_epsilon))[letx :: Double x =HypergeometricDistribution -> Int -> Double probability HypergeometricDistribution d Int n inDouble x Double -> Double -> Double forall a. Num a => a -> a -> a *Double -> Double forall a. Floating a => a -> a logDouble x |Int n <-[Int 0..Int m ]]hypergeometric ::Int-- ^ /m/->Int-- ^ /l/->Int-- ^ /k/->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([Char] -> HypergeometricDistribution forall a. HasCallStack => [Char] -> a error([Char] -> HypergeometricDistribution) -> [Char] -> HypergeometricDistribution forall a b. (a -> b) -> a -> b $Int -> Int -> Int -> [Char] 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-- ^ /m/->Int-- ^ /l/->Int-- ^ /k/->MaybeHypergeometricDistribution 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 0Bool -> 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 0Bool -> 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->StringerrMsg :: Int -> Int -> Int -> [Char] errMsg Int m Int l Int k =[Char] "Statistics.Distribution.Hypergeometric.hypergeometric:"[Char] -> ShowS forall a. [a] -> [a] -> [a] ++[Char] " m="[Char] -> ShowS forall a. [a] -> [a] -> [a] ++Int -> [Char] forall a. Show a => a -> [Char] showInt m [Char] -> ShowS forall a. [a] -> [a] -> [a] ++[Char] " l="[Char] -> ShowS forall a. [a] -> [a] -> [a] ++Int -> [Char] forall a. Show a => a -> [Char] showInt l [Char] -> ShowS forall a. [a] -> [a] -> [a] ++[Char] " k="[Char] -> ShowS forall a. [a] -> [a] -> [a] ++Int -> [Char] forall a. Show a => a -> [Char] showInt k [Char] -> ShowS forall a. [a] -> [a] -> [a] ++[Char] " should hold: l>0 & m in [0,l] & k in (0,l]"-- Naive implementationprobability ::HypergeometricDistribution ->Int->Doubleprobability :: 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 maxInt 0(Int mi Int -> Int -> Int forall a. Num a => a -> a -> a +Int ki Int -> 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 minInt mi Int ki =Double 0-- No overflow|Int li Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <Int 1000=Int -> Int -> Double chooseInt 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 chooseInt 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 logChooseInt 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 logChooseInt li Int ki logProbability ::HypergeometricDistribution ->Int->DoublelogProbability :: 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 maxInt 0(Int mi Int -> Int -> Int forall a. Num a => a -> a -> a +Int ki Int -> 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 minInt mi Int ki =Double m_neg_inf|Bool otherwise=Int -> Int -> Double logChooseInt 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 logChooseInt li Int ki cumulative ::HypergeometricDistribution ->Double->Doublecumulative :: HypergeometricDistribution -> Double -> Double cumulative d :: HypergeometricDistribution d @(HD Int mi Int li Int ki )Double x |Double -> Bool forall a. RealFloat a => a -> Bool isNaNDouble x =[Char] -> Double forall a. HasCallStack => [Char] -> a error[Char] "Statistics.Distribution.Hypergeometric.cumulative: NaN argument"|Double -> Bool forall a. RealFloat a => a -> Bool isInfiniteDouble x =ifDouble x Double -> Double -> Bool forall a. Ord a => a -> a -> Bool >Double 0thenDouble 1elseDouble 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 wheren :: Int n =Double -> Int forall b. Integral b => Double -> b forall a b. (RealFrac a, Integral b) => a -> b floorDouble x minN :: Int minN =Int -> Int -> Int forall a. Ord a => a -> a -> a maxInt 0(Int mi Int -> Int -> Int forall a. Num a => a -> a -> a +Int ki Int -> Int -> Int forall a. Num a => a -> a -> a -Int li )maxN :: Int maxN =Int -> Int -> Int forall a. Ord a => a -> a -> a minInt mi Int ki complCumulative ::HypergeometricDistribution ->Double->DoublecomplCumulative :: HypergeometricDistribution -> Double -> Double complCumulative d :: HypergeometricDistribution d @(HD Int mi Int li Int ki )Double x |Double -> Bool forall a. RealFloat a => a -> Bool isNaNDouble x =[Char] -> Double forall a. HasCallStack => [Char] -> a error[Char] "Statistics.Distribution.Hypergeometric.complCumulative: NaN argument"|Double -> Bool forall a. RealFloat a => a -> Bool isInfiniteDouble x =ifDouble x Double -> Double -> Bool forall a. Ord a => a -> a -> Bool >Double 0thenDouble 0elseDouble 1|Int n Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <Int minN =Double 1|Int n Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >=Int maxN =Double 0|Bool otherwise=HypergeometricDistribution -> Int -> Int -> Double forall d. DiscreteDistr d => d -> Int -> Int -> Double D.sumProbabilities HypergeometricDistribution d (Int n Int -> Int -> Int forall a. Num a => a -> a -> a +Int 1)Int maxN wheren :: Int n =Double -> Int forall b. Integral b => Double -> b forall a b. (RealFrac a, Integral b) => a -> b floorDouble x minN :: Int minN =Int -> Int -> Int forall a. Ord a => a -> a -> a maxInt 0(Int mi Int -> Int -> Int forall a. Num a => a -> a -> a +Int ki Int -> Int -> Int forall a. Num a => a -> a -> a -Int li )maxN :: Int maxN =Int -> Int -> Int forall a. Ord a => a -> a -> a minInt mi Int ki