{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
-- |
-- Module    : Statistics.Distribution.Gamma
-- Copyright : (c) 2009, 2011 Bryan O'Sullivan
-- License   : BSD3
--
-- Maintainer  : bos@serpentine.com
-- Stability   : experimental
-- Portability : portable
--
-- The gamma distribution.  This is a continuous probability
-- distribution with two parameters, /k/ and ϑ. If /k/ is
-- integral, the distribution represents the sum of /k/ independent
-- exponentially distributed random variables, each of which has a
-- mean of ϑ.

module Statistics.Distribution.Gamma
    (
      GammaDistribution
    -- * Constructors
    , gammaDistr
    , gammaDistrE
    , improperGammaDistr
    , improperGammaDistrE
    -- * Accessors
    , gdShape
    , gdScale
    ) 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_pos_inf, m_NaN, m_neg_inf)
import Numeric.SpecFunctions (incompleteGamma, invIncompleteGamma, logGamma, digamma)
import qualified System.Random.MWC.Distributions as MWC
import qualified Numeric.Sum as Sum

import Statistics.Distribution.Poisson.Internal as Poisson
import qualified Statistics.Distribution as D
import Statistics.Internal


-- | The gamma distribution.
data GammaDistribution = GD {
      GammaDistribution -> Double
gdShape :: {-# UNPACK #-} !Double -- ^ Shape parameter, /k/.
    , GammaDistribution -> Double
gdScale :: {-# UNPACK #-} !Double -- ^ Scale parameter, ϑ.
    } deriving (GammaDistribution -> GammaDistribution -> Bool
(GammaDistribution -> GammaDistribution -> Bool)
-> (GammaDistribution -> GammaDistribution -> Bool)
-> Eq GammaDistribution
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GammaDistribution -> GammaDistribution -> Bool
$c/= :: GammaDistribution -> GammaDistribution -> Bool
== :: GammaDistribution -> GammaDistribution -> Bool
$c== :: GammaDistribution -> GammaDistribution -> Bool
Eq, Typeable, Typeable GammaDistribution
DataType
Constr
Typeable GammaDistribution
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> GammaDistribution
    -> c GammaDistribution)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c GammaDistribution)
-> (GammaDistribution -> Constr)
-> (GammaDistribution -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c GammaDistribution))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c GammaDistribution))
-> ((forall b. Data b => b -> b)
    -> GammaDistribution -> GammaDistribution)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> GammaDistribution -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> GammaDistribution -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> GammaDistribution -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> GammaDistribution -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> GammaDistribution -> m GammaDistribution)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> GammaDistribution -> m GammaDistribution)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> GammaDistribution -> m GammaDistribution)
-> Data GammaDistribution
GammaDistribution -> DataType
GammaDistribution -> Constr
(forall b. Data b => b -> b)
-> GammaDistribution -> GammaDistribution
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GammaDistribution -> c GammaDistribution
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GammaDistribution
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) -> GammaDistribution -> u
forall u. (forall d. Data d => d -> u) -> GammaDistribution -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GammaDistribution -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GammaDistribution -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> GammaDistribution -> m GammaDistribution
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> GammaDistribution -> m GammaDistribution
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GammaDistribution
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GammaDistribution -> c GammaDistribution
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c GammaDistribution)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c GammaDistribution)
$cGD :: Constr
$tGammaDistribution :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> GammaDistribution -> m GammaDistribution
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> GammaDistribution -> m GammaDistribution
gmapMp :: (forall d. Data d => d -> m d)
-> GammaDistribution -> m GammaDistribution
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> GammaDistribution -> m GammaDistribution
gmapM :: (forall d. Data d => d -> m d)
-> GammaDistribution -> m GammaDistribution
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> GammaDistribution -> m GammaDistribution
gmapQi :: Int -> (forall d. Data d => d -> u) -> GammaDistribution -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> GammaDistribution -> u
gmapQ :: (forall d. Data d => d -> u) -> GammaDistribution -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> GammaDistribution -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GammaDistribution -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> GammaDistribution -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GammaDistribution -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> GammaDistribution -> r
gmapT :: (forall b. Data b => b -> b)
-> GammaDistribution -> GammaDistribution
$cgmapT :: (forall b. Data b => b -> b)
-> GammaDistribution -> GammaDistribution
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c GammaDistribution)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c GammaDistribution)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c GammaDistribution)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c GammaDistribution)
dataTypeOf :: GammaDistribution -> DataType
$cdataTypeOf :: GammaDistribution -> DataType
toConstr :: GammaDistribution -> Constr
$ctoConstr :: GammaDistribution -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GammaDistribution
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c GammaDistribution
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GammaDistribution -> c GammaDistribution
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> GammaDistribution -> c GammaDistribution
$cp1Data :: Typeable GammaDistribution
Data, (forall x. GammaDistribution -> Rep GammaDistribution x)
-> (forall x. Rep GammaDistribution x -> GammaDistribution)
-> Generic GammaDistribution
forall x. Rep GammaDistribution x -> GammaDistribution
forall x. GammaDistribution -> Rep GammaDistribution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GammaDistribution x -> GammaDistribution
$cfrom :: forall x. GammaDistribution -> Rep GammaDistribution x
Generic)

instance Show GammaDistribution where
  showsPrec :: Int -> GammaDistribution -> ShowS
showsPrec Int
i (GD Double
k Double
theta) = String -> Double -> Double -> Int -> ShowS
forall a b. (Show a, Show b) => String -> a -> b -> Int -> ShowS
defaultShow2 String
"improperGammaDistr" Double
k Double
theta Int
i
instance Read GammaDistribution where
  readPrec :: ReadPrec GammaDistribution
readPrec = String
-> (Double -> Double -> Maybe GammaDistribution)
-> ReadPrec GammaDistribution
forall a b r.
(Read a, Read b) =>
String -> (a -> b -> Maybe r) -> ReadPrec r
defaultReadPrecM2 String
"improperGammaDistr" Double -> Double -> Maybe GammaDistribution
improperGammaDistrE


instance ToJSON GammaDistribution
instance FromJSON GammaDistribution where
  parseJSON :: Value -> Parser GammaDistribution
parseJSON (Object Object
v) = do
    Double
k     <- Object
v Object -> Key -> Parser Double
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"gdShape"
    Double
theta <- Object
v Object -> Key -> Parser Double
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"gdScale"
    Parser GammaDistribution
-> (GammaDistribution -> Parser GammaDistribution)
-> Maybe GammaDistribution
-> Parser GammaDistribution
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Parser GammaDistribution
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser GammaDistribution)
-> String -> Parser GammaDistribution
forall a b. (a -> b) -> a -> b
$ Double -> Double -> String
errMsgI Double
k Double
theta) GammaDistribution -> Parser GammaDistribution
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe GammaDistribution -> Parser GammaDistribution)
-> Maybe GammaDistribution -> Parser GammaDistribution
forall a b. (a -> b) -> a -> b
$ Double -> Double -> Maybe GammaDistribution
improperGammaDistrE Double
k Double
theta
  parseJSON Value
_ = Parser GammaDistribution
forall (f :: * -> *) a. Alternative f => f a
empty

instance Binary GammaDistribution where
  put :: GammaDistribution -> Put
put (GD Double
x Double
y) = Double -> Put
forall t. Binary t => t -> Put
put Double
x Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Double -> Put
forall t. Binary t => t -> Put
put Double
y
  get :: Get GammaDistribution
get = do
    Double
k     <- Get Double
forall t. Binary t => Get t
get
    Double
theta <- Get Double
forall t. Binary t => Get t
get
    Get GammaDistribution
-> (GammaDistribution -> Get GammaDistribution)
-> Maybe GammaDistribution
-> Get GammaDistribution
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Get GammaDistribution
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Get GammaDistribution)
-> String -> Get GammaDistribution
forall a b. (a -> b) -> a -> b
$ Double -> Double -> String
errMsgI Double
k Double
theta) GammaDistribution -> Get GammaDistribution
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe GammaDistribution -> Get GammaDistribution)
-> Maybe GammaDistribution -> Get GammaDistribution
forall a b. (a -> b) -> a -> b
$ Double -> Double -> Maybe GammaDistribution
improperGammaDistrE Double
k Double
theta


-- | Create gamma distribution. Both shape and scale parameters must
-- be positive.
gammaDistr :: Double            -- ^ Shape parameter. /k/
           -> Double            -- ^ Scale parameter, &#977;.
           -> GammaDistribution
gammaDistr :: Double -> Double -> GammaDistribution
gammaDistr Double
k Double
theta
  = GammaDistribution
-> (GammaDistribution -> GammaDistribution)
-> Maybe GammaDistribution
-> GammaDistribution
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> GammaDistribution
forall a. HasCallStack => String -> a
error (String -> GammaDistribution) -> String -> GammaDistribution
forall a b. (a -> b) -> a -> b
$ Double -> Double -> String
errMsg Double
k Double
theta) GammaDistribution -> GammaDistribution
forall a. a -> a
id (Maybe GammaDistribution -> GammaDistribution)
-> Maybe GammaDistribution -> GammaDistribution
forall a b. (a -> b) -> a -> b
$ Double -> Double -> Maybe GammaDistribution
gammaDistrE Double
k Double
theta

errMsg :: Double -> Double -> String
errMsg :: Double -> Double -> String
errMsg Double
k Double
theta
  =  String
"Statistics.Distribution.Gamma.gammaDistr: "
  String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"k=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Double -> String
forall a. Show a => a -> String
show Double
k
  String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"theta=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Double -> String
forall a. Show a => a -> String
show Double
theta
  String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" but must be positive"

-- | Create gamma distribution. Both shape and scale parameters must
-- be positive.
gammaDistrE :: Double            -- ^ Shape parameter. /k/
            -> Double            -- ^ Scale parameter, &#977;.
            -> Maybe GammaDistribution
gammaDistrE :: Double -> Double -> Maybe GammaDistribution
gammaDistrE Double
k Double
theta
  | Double
k Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 Bool -> Bool -> Bool
&& Double
theta Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 = GammaDistribution -> Maybe GammaDistribution
forall a. a -> Maybe a
Just (Double -> Double -> GammaDistribution
GD Double
k Double
theta)
  | Bool
otherwise          = Maybe GammaDistribution
forall a. Maybe a
Nothing


-- | Create gamma distribution. Both shape and scale parameters must
-- be non-negative.
improperGammaDistr :: Double            -- ^ Shape parameter. /k/
                   -> Double            -- ^ Scale parameter, &#977;.
                   -> GammaDistribution
improperGammaDistr :: Double -> Double -> GammaDistribution
improperGammaDistr Double
k Double
theta
  = GammaDistribution
-> (GammaDistribution -> GammaDistribution)
-> Maybe GammaDistribution
-> GammaDistribution
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> GammaDistribution
forall a. HasCallStack => String -> a
error (String -> GammaDistribution) -> String -> GammaDistribution
forall a b. (a -> b) -> a -> b
$ Double -> Double -> String
errMsgI Double
k Double
theta) GammaDistribution -> GammaDistribution
forall a. a -> a
id (Maybe GammaDistribution -> GammaDistribution)
-> Maybe GammaDistribution -> GammaDistribution
forall a b. (a -> b) -> a -> b
$ Double -> Double -> Maybe GammaDistribution
improperGammaDistrE Double
k Double
theta

errMsgI :: Double -> Double -> String
errMsgI :: Double -> Double -> String
errMsgI Double
k Double
theta
  =  String
"Statistics.Distribution.Gamma.gammaDistr: "
  String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"k=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Double -> String
forall a. Show a => a -> String
show Double
k
  String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"theta=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Double -> String
forall a. Show a => a -> String
show Double
theta
  String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" but must be non-negative"

-- | Create gamma distribution. Both shape and scale parameters must
-- be non-negative.
improperGammaDistrE :: Double            -- ^ Shape parameter. /k/
                    -> Double            -- ^ Scale parameter, &#977;.
                    -> Maybe GammaDistribution
improperGammaDistrE :: Double -> Double -> Maybe GammaDistribution
improperGammaDistrE Double
k Double
theta
  | Double
k Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
0 Bool -> Bool -> Bool
&& Double
theta Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
0 = GammaDistribution -> Maybe GammaDistribution
forall a. a -> Maybe a
Just (Double -> Double -> GammaDistribution
GD Double
k Double
theta)
  | Bool
otherwise            = Maybe GammaDistribution
forall a. Maybe a
Nothing

instance D.Distribution GammaDistribution where
    cumulative :: GammaDistribution -> Double -> Double
cumulative = GammaDistribution -> Double -> Double
cumulative

instance D.ContDistr GammaDistribution where
    density :: GammaDistribution -> Double -> Double
density    = GammaDistribution -> Double -> Double
density
    logDensity :: GammaDistribution -> Double -> Double
logDensity (GD Double
k Double
theta) Double
x
      | Double
x Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
0    = Double
m_neg_inf
      | Bool
otherwise = (KBNSum -> Double) -> [Double] -> Double
forall s (f :: * -> *).
(Summation s, Foldable f) =>
(s -> Double) -> f Double -> Double
Sum.sum KBNSum -> Double
Sum.kbn [ Double -> Double
forall a. Floating a => a -> a
log Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Double
k Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
1)
                                    , - (Double
x Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
theta)
                                    , - Double -> Double
logGamma Double
k
                                    , - Double -> Double
forall a. Floating a => a -> a
log Double
theta Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
k
                                    ]
    quantile :: GammaDistribution -> Double -> Double
quantile   = GammaDistribution -> Double -> Double
quantile

instance D.Variance GammaDistribution where
    variance :: GammaDistribution -> Double
variance (GD Double
a Double
l) = Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
l Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
l

instance D.Mean GammaDistribution where
    mean :: GammaDistribution -> Double
mean (GD Double
a Double
l) = Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
l

instance D.MaybeMean GammaDistribution where
    maybeMean :: GammaDistribution -> Maybe Double
maybeMean = Double -> Maybe Double
forall a. a -> Maybe a
Just (Double -> Maybe Double)
-> (GammaDistribution -> Double)
-> GammaDistribution
-> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GammaDistribution -> Double
forall d. Mean d => d -> Double
D.mean

instance D.MaybeVariance GammaDistribution where
    maybeStdDev :: GammaDistribution -> Maybe Double
maybeStdDev   = Double -> Maybe Double
forall a. a -> Maybe a
Just (Double -> Maybe Double)
-> (GammaDistribution -> Double)
-> GammaDistribution
-> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GammaDistribution -> Double
forall d. Variance d => d -> Double
D.stdDev
    maybeVariance :: GammaDistribution -> Maybe Double
maybeVariance = Double -> Maybe Double
forall a. a -> Maybe a
Just (Double -> Maybe Double)
-> (GammaDistribution -> Double)
-> GammaDistribution
-> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GammaDistribution -> Double
forall d. Variance d => d -> Double
D.variance

instance D.MaybeEntropy GammaDistribution where
  maybeEntropy :: GammaDistribution -> Maybe Double
maybeEntropy (GD Double
a Double
l)
    | Double
a Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 Bool -> Bool -> Bool
&& Double
l Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 =
      Double -> Maybe Double
forall a. a -> Maybe a
Just (Double -> Maybe Double) -> Double -> Maybe Double
forall a b. (a -> b) -> a -> b
$
      Double
a
      Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double -> Double
forall a. Floating a => a -> a
log Double
l
      Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double -> Double
logGamma Double
a
      Double -> Double -> Double
forall a. Num a => a -> a -> a
+ (Double
1Double -> Double -> Double
forall a. Num a => a -> a -> a
-Double
a) Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double -> Double
digamma Double
a
    | Bool
otherwise = Maybe Double
forall a. Maybe a
Nothing

instance D.ContGen GammaDistribution where
    genContVar :: GammaDistribution -> g -> m Double
genContVar (GD Double
a Double
l) = Double -> Double -> g -> m Double
forall g (m :: * -> *).
StatefulGen g m =>
Double -> Double -> g -> m Double
MWC.gamma Double
a Double
l


density :: GammaDistribution -> Double -> Double
density :: GammaDistribution -> Double -> Double
density (GD Double
a Double
l) Double
x
  | Double
a Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0 Bool -> Bool -> Bool
|| Double
l Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
0   = Double
m_NaN
  | Double
x Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
0            = Double
0
  | Double
a Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0            = if Double
x Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0 then Double
m_pos_inf else Double
0
  | Double
x Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0            = if Double
a Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
1 then Double
m_pos_inf else if Double
a Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
1 then Double
0 else Double
1Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
l
  | Double
a Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
1             = Double -> Double -> Double
Poisson.probability (Double
xDouble -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
l) Double
a Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
a Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
x
  | Bool
otherwise         = Double -> Double -> Double
Poisson.probability (Double
xDouble -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
l) (Double
aDouble -> Double -> Double
forall a. Num a => a -> a -> a
-Double
1) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
l

cumulative :: GammaDistribution -> Double -> Double
cumulative :: GammaDistribution -> Double -> Double
cumulative (GD Double
k Double
l) Double
x
  | Double
x Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
0    = Double
0
  | Bool
otherwise = Double -> Double -> Double
incompleteGamma Double
k (Double
xDouble -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
l)

quantile :: GammaDistribution -> Double -> Double
quantile :: GammaDistribution -> Double -> Double
quantile (GD Double
k Double
l) Double
p
  | Double
p Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0         = Double
0
  | Double
p Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
1         = Double
1Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
0
  | Double
p Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 Bool -> Bool -> Bool
&& Double
p Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
1 = Double
l Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double -> Double -> Double
invIncompleteGamma Double
k Double
p
  | Bool
otherwise      =
    String -> Double
forall a. HasCallStack => String -> a
error (String -> Double) -> String -> Double
forall a b. (a -> b) -> a -> b
$ String
"Statistics.Distribution.Gamma.quantile: p must be in [0,1] range. Got: "String -> ShowS
forall a. [a] -> [a] -> [a]
++Double -> String
forall a. Show a => a -> String
show Double
p