{-# LANGUAGE OverloadedStrings, PatternGuards,
DeriveDataTypeable, DeriveGeneric #-}
module Statistics.Distribution.NegativeBinomial (
NegativeBinomialDistribution
, negativeBinomial
, negativeBinomialE
, nbdSuccesses
, nbdProbability
) where
import Control.Applicative
import Data.Aeson (FromJSON(..), ToJSON, Value(..), (.:))
import Data.Binary (Binary(..))
import Data.Data (Data, Typeable)
import Data.Foldable (foldl')
import GHC.Generics (Generic)
import Numeric.SpecFunctions (incompleteBeta, log1p)
import Numeric.SpecFunctions.Extra (logChooseFast)
import Numeric.MathFunctions.Constants (m_epsilon, m_tiny)
import qualified Statistics.Distribution as D
import Statistics.Internal
gChoose :: Double -> Int -> Double
gChoose :: Double -> Int -> Double
gChoose Double
n Int
k
| Int
k forall a. Ord a => a -> a -> Bool
< Int
0 = Double
0
| Double
k' forall a. Ord a => a -> a -> Bool
>= Double
50 = forall a. Floating a => a -> a
exp forall a b. (a -> b) -> a -> b
$ Double -> Double -> Double
logChooseFast Double
n Double
k'
| Bool
otherwise = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' forall a. Num a => a -> a -> a
(*) Double
1 [Double]
factors
where factors :: [Double]
factors = [ (Double
n forall a. Num a => a -> a -> a
- Double
k' forall a. Num a => a -> a -> a
+ Double
j) forall a. Fractional a => a -> a -> a
/ Double
j | Double
j <- [Double
1..Double
k'] ]
k' :: Double
k' = forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k
data NegativeBinomialDistribution = NBD {
NegativeBinomialDistribution -> Double
nbdSuccesses :: {-# UNPACK #-} !Double
, NegativeBinomialDistribution -> Double
nbdProbability :: {-# UNPACK #-} !Double
} deriving (NegativeBinomialDistribution
-> NegativeBinomialDistribution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NegativeBinomialDistribution
-> NegativeBinomialDistribution -> Bool
$c/= :: NegativeBinomialDistribution
-> NegativeBinomialDistribution -> Bool
== :: NegativeBinomialDistribution
-> NegativeBinomialDistribution -> Bool
$c== :: NegativeBinomialDistribution
-> NegativeBinomialDistribution -> Bool
Eq, Typeable, Typeable NegativeBinomialDistribution
NegativeBinomialDistribution -> DataType
NegativeBinomialDistribution -> Constr
(forall b. Data b => b -> b)
-> NegativeBinomialDistribution -> NegativeBinomialDistribution
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)
-> NegativeBinomialDistribution
-> u
forall u.
(forall d. Data d => d -> u) -> NegativeBinomialDistribution -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> NegativeBinomialDistribution
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> NegativeBinomialDistribution
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NegativeBinomialDistribution -> m NegativeBinomialDistribution
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NegativeBinomialDistribution -> m NegativeBinomialDistribution
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NegativeBinomialDistribution
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> NegativeBinomialDistribution
-> c NegativeBinomialDistribution
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c NegativeBinomialDistribution)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NegativeBinomialDistribution)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NegativeBinomialDistribution -> m NegativeBinomialDistribution
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NegativeBinomialDistribution -> m NegativeBinomialDistribution
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NegativeBinomialDistribution -> m NegativeBinomialDistribution
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> NegativeBinomialDistribution -> m NegativeBinomialDistribution
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NegativeBinomialDistribution -> m NegativeBinomialDistribution
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> NegativeBinomialDistribution -> m NegativeBinomialDistribution
gmapQi :: forall u.
Int
-> (forall d. Data d => d -> u)
-> NegativeBinomialDistribution
-> u
$cgmapQi :: forall u.
Int
-> (forall d. Data d => d -> u)
-> NegativeBinomialDistribution
-> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> NegativeBinomialDistribution -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> NegativeBinomialDistribution -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> NegativeBinomialDistribution
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> NegativeBinomialDistribution
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> NegativeBinomialDistribution
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> NegativeBinomialDistribution
-> r
gmapT :: (forall b. Data b => b -> b)
-> NegativeBinomialDistribution -> NegativeBinomialDistribution
$cgmapT :: (forall b. Data b => b -> b)
-> NegativeBinomialDistribution -> NegativeBinomialDistribution
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NegativeBinomialDistribution)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c NegativeBinomialDistribution)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c NegativeBinomialDistribution)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d))
-> Maybe (c NegativeBinomialDistribution)
dataTypeOf :: NegativeBinomialDistribution -> DataType
$cdataTypeOf :: NegativeBinomialDistribution -> DataType
toConstr :: NegativeBinomialDistribution -> Constr
$ctoConstr :: NegativeBinomialDistribution -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NegativeBinomialDistribution
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c NegativeBinomialDistribution
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> NegativeBinomialDistribution
-> c NegativeBinomialDistribution
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> NegativeBinomialDistribution
-> c NegativeBinomialDistribution
Data, forall x.
Rep NegativeBinomialDistribution x -> NegativeBinomialDistribution
forall x.
NegativeBinomialDistribution -> Rep NegativeBinomialDistribution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep NegativeBinomialDistribution x -> NegativeBinomialDistribution
$cfrom :: forall x.
NegativeBinomialDistribution -> Rep NegativeBinomialDistribution x
Generic)
instance Show NegativeBinomialDistribution where
showsPrec :: Int -> NegativeBinomialDistribution -> ShowS
showsPrec Int
i (NBD Double
r Double
p) = forall a b. (Show a, Show b) => [Char] -> a -> b -> Int -> ShowS
defaultShow2 [Char]
"negativeBinomial" Double
r Double
p Int
i
instance Read NegativeBinomialDistribution where
readPrec :: ReadPrec NegativeBinomialDistribution
readPrec = forall a b r.
(Read a, Read b) =>
[Char] -> (a -> b -> Maybe r) -> ReadPrec r
defaultReadPrecM2 [Char]
"negativeBinomial" Double -> Double -> Maybe NegativeBinomialDistribution
negativeBinomialE
instance ToJSON NegativeBinomialDistribution
instance FromJSON NegativeBinomialDistribution where
parseJSON :: Value -> Parser NegativeBinomialDistribution
parseJSON (Object Object
v) = do
Double
r <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"nbdSuccesses"
Double
p <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"nbdProbability"
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ Double -> Double -> [Char]
errMsg Double
r Double
p) forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Double -> Double -> Maybe NegativeBinomialDistribution
negativeBinomialE Double
r Double
p
parseJSON Value
_ = forall (f :: * -> *) a. Alternative f => f a
empty
instance Binary NegativeBinomialDistribution where
put :: NegativeBinomialDistribution -> Put
put (NBD Double
r Double
p) = forall t. Binary t => t -> Put
put Double
r forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall t. Binary t => t -> Put
put Double
p
get :: Get NegativeBinomialDistribution
get = do
Double
r <- forall t. Binary t => Get t
get
Double
p <- forall t. Binary t => Get t
get
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ Double -> Double -> [Char]
errMsg Double
r Double
p) forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Double -> Double -> Maybe NegativeBinomialDistribution
negativeBinomialE Double
r Double
p
instance D.Distribution NegativeBinomialDistribution where
cumulative :: NegativeBinomialDistribution -> Double -> Double
cumulative = NegativeBinomialDistribution -> Double -> Double
cumulative
complCumulative :: NegativeBinomialDistribution -> Double -> Double
complCumulative = NegativeBinomialDistribution -> Double -> Double
complCumulative
instance D.DiscreteDistr NegativeBinomialDistribution where
probability :: NegativeBinomialDistribution -> Int -> Double
probability = NegativeBinomialDistribution -> Int -> Double
probability
logProbability :: NegativeBinomialDistribution -> Int -> Double
logProbability = NegativeBinomialDistribution -> Int -> Double
logProbability
instance D.Mean NegativeBinomialDistribution where
mean :: NegativeBinomialDistribution -> Double
mean = NegativeBinomialDistribution -> Double
mean
instance D.Variance NegativeBinomialDistribution where
variance :: NegativeBinomialDistribution -> Double
variance = NegativeBinomialDistribution -> Double
variance
instance D.MaybeMean NegativeBinomialDistribution where
maybeMean :: NegativeBinomialDistribution -> Maybe Double
maybeMean = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall d. Mean d => d -> Double
D.mean
instance D.MaybeVariance NegativeBinomialDistribution where
maybeStdDev :: NegativeBinomialDistribution -> Maybe Double
maybeStdDev = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall d. Variance d => d -> Double
D.stdDev
maybeVariance :: NegativeBinomialDistribution -> Maybe Double
maybeVariance = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall d. Variance d => d -> Double
D.variance
instance D.Entropy NegativeBinomialDistribution where
entropy :: NegativeBinomialDistribution -> Double
entropy = NegativeBinomialDistribution -> Double
directEntropy
instance D.MaybeEntropy NegativeBinomialDistribution where
maybeEntropy :: NegativeBinomialDistribution -> Maybe Double
maybeEntropy = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall d. Entropy d => d -> Double
D.entropy
probability :: NegativeBinomialDistribution -> Int -> Double
probability :: NegativeBinomialDistribution -> Int -> Double
probability d :: NegativeBinomialDistribution
d@(NBD Double
r Double
p) Int
k
| Int
k forall a. Ord a => a -> a -> Bool
< Int
0 = Double
0
| Double
k' forall a. Num a => a -> a -> a
+ Double
r forall a. Ord a => a -> a -> Bool
< Double
1000
, Double
pK forall a. Ord a => a -> a -> Bool
>= Double
m_tiny
, Double
pR forall a. Ord a => a -> a -> Bool
>= Double
m_tiny = Double -> Int -> Double
gChoose (Double
k' forall a. Num a => a -> a -> a
+ Double
r forall a. Num a => a -> a -> a
- Double
1) Int
k forall a. Num a => a -> a -> a
* Double
pK forall a. Num a => a -> a -> a
* Double
pR
| Bool
otherwise = forall a. Floating a => a -> a
exp forall a b. (a -> b) -> a -> b
$ NegativeBinomialDistribution -> Int -> Double
logProbability NegativeBinomialDistribution
d Int
k
where
pK :: Double
pK = forall a. Floating a => a -> a
exp forall a b. (a -> b) -> a -> b
$ forall a. Floating a => a -> a
log1p (-Double
p) forall a. Num a => a -> a -> a
* Double
k'
pR :: Double
pR = Double
pforall a. Floating a => a -> a -> a
**Double
r
k' :: Double
k' = forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k
logProbability :: NegativeBinomialDistribution -> Int -> Double
logProbability :: NegativeBinomialDistribution -> Int -> Double
logProbability (NBD Double
r Double
p) Int
k
| Int
k forall a. Ord a => a -> a -> Bool
< Int
0 = (-Double
1)forall a. Fractional a => a -> a -> a
/Double
0
| Bool
otherwise = Double -> Double -> Double
logChooseFast (Double
k' forall a. Num a => a -> a -> a
+ Double
r forall a. Num a => a -> a -> a
- Double
1) Double
k'
forall a. Num a => a -> a -> a
+ forall a. Floating a => a -> a
log1p (-Double
p) forall a. Num a => a -> a -> a
* Double
k'
forall a. Num a => a -> a -> a
+ forall a. Floating a => a -> a
log Double
p forall a. Num a => a -> a -> a
* Double
r
where k' :: Double
k' = forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
k
cumulative :: NegativeBinomialDistribution -> Double -> Double
cumulative :: NegativeBinomialDistribution -> Double -> Double
cumulative (NBD Double
r Double
p) Double
x
| forall a. RealFloat a => a -> Bool
isNaN Double
x = forall a. HasCallStack => [Char] -> a
error [Char]
"Statistics.Distribution.NegativeBinomial.cumulative: NaN input"
| forall a. RealFloat a => a -> Bool
isInfinite Double
x = if Double
x forall a. Ord a => a -> a -> Bool
> Double
0 then Double
1 else Double
0
| Integer
k forall a. Ord a => a -> a -> Bool
< Integer
0 = Double
0
| Bool
otherwise = Double -> Double -> Double -> Double
incompleteBeta Double
r (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
kforall a. Num a => a -> a -> a
+Integer
1)) Double
p
where
k :: Integer
k = forall a b. (RealFrac a, Integral b) => a -> b
floor Double
x :: Integer
complCumulative :: NegativeBinomialDistribution -> Double -> Double
complCumulative :: NegativeBinomialDistribution -> Double -> Double
complCumulative (NBD Double
r Double
p) Double
x
| forall a. RealFloat a => a -> Bool
isNaN Double
x = forall a. HasCallStack => [Char] -> a
error [Char]
"Statistics.Distribution.NegativeBinomial.complCumulative: NaN input"
| forall a. RealFloat a => a -> Bool
isInfinite Double
x = if Double
x forall a. Ord a => a -> a -> Bool
> Double
0 then Double
0 else Double
1
| Integer
k forall a. Ord a => a -> a -> Bool
< Integer
0 = Double
1
| Bool
otherwise = Double -> Double -> Double -> Double
incompleteBeta (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer
kforall a. Num a => a -> a -> a
+Integer
1)) Double
r (Double
1 forall a. Num a => a -> a -> a
- Double
p)
where
k :: Integer
k = (forall a b. (RealFrac a, Integral b) => a -> b
floor Double
x)::Integer
mean :: NegativeBinomialDistribution -> Double
mean :: NegativeBinomialDistribution -> Double
mean (NBD Double
r Double
p) = Double
r forall a. Num a => a -> a -> a
* (Double
1 forall a. Num a => a -> a -> a
- Double
p)forall a. Fractional a => a -> a -> a
/Double
p
variance :: NegativeBinomialDistribution -> Double
variance :: NegativeBinomialDistribution -> Double
variance (NBD Double
r Double
p) = Double
r forall a. Num a => a -> a -> a
* (Double
1 forall a. Num a => a -> a -> a
- Double
p)forall a. Fractional a => a -> a -> a
/(Double
p forall a. Num a => a -> a -> a
* Double
p)
directEntropy :: NegativeBinomialDistribution -> Double
directEntropy :: NegativeBinomialDistribution -> Double
directEntropy NegativeBinomialDistribution
d =
forall a. Num a => a -> a
negate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum forall a b. (a -> b) -> a -> b
$
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (forall a. Ord a => a -> a -> Bool
< -Double
m_epsilon) forall a b. (a -> b) -> a -> b
$
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Ord a => a -> a -> Bool
>= -Double
m_epsilon) forall a b. (a -> b) -> a -> b
$
[ let x :: Double
x = NegativeBinomialDistribution -> Int -> Double
probability NegativeBinomialDistribution
d Int
k in Double
x forall a. Num a => a -> a -> a
* forall a. Floating a => a -> a
log Double
x | Int
k <- [Int
0..]]
negativeBinomial :: Double
-> Double
-> NegativeBinomialDistribution
negativeBinomial :: Double -> Double -> NegativeBinomialDistribution
negativeBinomial Double
r Double
p = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ Double -> Double -> [Char]
errMsg Double
r Double
p) forall a. a -> a
id forall a b. (a -> b) -> a -> b
$ Double -> Double -> Maybe NegativeBinomialDistribution
negativeBinomialE Double
r Double
p
negativeBinomialE :: Double
-> Double
-> Maybe NegativeBinomialDistribution
negativeBinomialE :: Double -> Double -> Maybe NegativeBinomialDistribution
negativeBinomialE Double
r Double
p
| Double
r forall a. Ord a => a -> a -> Bool
> Double
0 Bool -> Bool -> Bool
&& Double
0 forall a. Ord a => a -> a -> Bool
< Double
p Bool -> Bool -> Bool
&& Double
p forall a. Ord a => a -> a -> Bool
<= Double
1 = forall a. a -> Maybe a
Just (Double -> Double -> NegativeBinomialDistribution
NBD Double
r Double
p)
| Bool
otherwise = forall a. Maybe a
Nothing
errMsg :: Double -> Double -> String
errMsg :: Double -> Double -> [Char]
errMsg Double
r Double
p
= [Char]
"Statistics.Distribution.NegativeBinomial.negativeBinomial: r=" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Double
r
forall a. [a] -> [a] -> [a]
++ [Char]
" p=" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Double
p forall a. [a] -> [a] -> [a]
++ [Char]
", but need r>0 and p in (0,1]"