{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
-- |
-- Module    : Statistics.Distribution.Exponential
-- Copyright : (c) 2009 Bryan O'Sullivan
-- License   : BSD3
--
-- Maintainer  : bos@serpentine.com
-- Stability   : experimental
-- Portability : portable
--
-- The exponential distribution.  This is the continuous probability
-- distribution of the times between events in a Poisson process, in
-- which events occur continuously and independently at a constant
-- average rate.

module Statistics.Distribution.Exponential
    (
      ExponentialDistribution
    -- * Constructors
    , exponential
    , exponentialE
    -- * Accessors
    , edLambda
    ) where

import Control.Applicative
import Data.Aeson                      (FromJSON(..),ToJSON,Value(..),(.:))
import Data.Binary                     (Binary, put, get)
import Data.Data                       (Data, Typeable)
import GHC.Generics                    (Generic)
import Numeric.SpecFunctions           (log1p,expm1)
import Numeric.MathFunctions.Constants (m_neg_inf)
import qualified System.Random.MWC.Distributions as MWC

import qualified Statistics.Distribution         as D
import qualified Statistics.Sample               as S
import Statistics.Internal



newtype ExponentialDistribution = ED {
      ExponentialDistribution -> Double
edLambda :: Double
    } deriving (ExponentialDistribution -> ExponentialDistribution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExponentialDistribution -> ExponentialDistribution -> Bool
$c/= :: ExponentialDistribution -> ExponentialDistribution -> Bool
== :: ExponentialDistribution -> ExponentialDistribution -> Bool
$c== :: ExponentialDistribution -> ExponentialDistribution -> Bool
Eq, Typeable, Typeable ExponentialDistribution
ExponentialDistribution -> DataType
ExponentialDistribution -> Constr
(forall b. Data b => b -> b)
-> ExponentialDistribution -> ExponentialDistribution
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) -> ExponentialDistribution -> u
forall u.
(forall d. Data d => d -> u) -> ExponentialDistribution -> [u]
forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ExponentialDistribution
-> r
forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ExponentialDistribution
-> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ExponentialDistribution -> m ExponentialDistribution
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ExponentialDistribution -> m ExponentialDistribution
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExponentialDistribution
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ExponentialDistribution
-> c ExponentialDistribution
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExponentialDistribution)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExponentialDistribution)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ExponentialDistribution -> m ExponentialDistribution
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ExponentialDistribution -> m ExponentialDistribution
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ExponentialDistribution -> m ExponentialDistribution
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ExponentialDistribution -> m ExponentialDistribution
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ExponentialDistribution -> m ExponentialDistribution
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ExponentialDistribution -> m ExponentialDistribution
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ExponentialDistribution -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ExponentialDistribution -> u
gmapQ :: forall u.
(forall d. Data d => d -> u) -> ExponentialDistribution -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> ExponentialDistribution -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ExponentialDistribution
-> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ExponentialDistribution
-> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ExponentialDistribution
-> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r
-> (forall d. Data d => d -> r')
-> ExponentialDistribution
-> r
gmapT :: (forall b. Data b => b -> b)
-> ExponentialDistribution -> ExponentialDistribution
$cgmapT :: (forall b. Data b => b -> b)
-> ExponentialDistribution -> ExponentialDistribution
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExponentialDistribution)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExponentialDistribution)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExponentialDistribution)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExponentialDistribution)
dataTypeOf :: ExponentialDistribution -> DataType
$cdataTypeOf :: ExponentialDistribution -> DataType
toConstr :: ExponentialDistribution -> Constr
$ctoConstr :: ExponentialDistribution -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExponentialDistribution
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExponentialDistribution
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ExponentialDistribution
-> c ExponentialDistribution
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ExponentialDistribution
-> c ExponentialDistribution
Data, forall x. Rep ExponentialDistribution x -> ExponentialDistribution
forall x. ExponentialDistribution -> Rep ExponentialDistribution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExponentialDistribution x -> ExponentialDistribution
$cfrom :: forall x. ExponentialDistribution -> Rep ExponentialDistribution x
Generic)

instance Show ExponentialDistribution where
  showsPrec :: Int -> ExponentialDistribution -> ShowS
showsPrec Int
n (ED Double
l) = forall a. Show a => [Char] -> a -> Int -> ShowS
defaultShow1 [Char]
"exponential" Double
l Int
n
instance Read ExponentialDistribution where
  readPrec :: ReadPrec ExponentialDistribution
readPrec = forall a r. Read a => [Char] -> (a -> Maybe r) -> ReadPrec r
defaultReadPrecM1 [Char]
"exponential" Double -> Maybe ExponentialDistribution
exponentialE

instance ToJSON ExponentialDistribution
instance FromJSON ExponentialDistribution where
  parseJSON :: Value -> Parser ExponentialDistribution
parseJSON (Object Object
v) = do
    Double
l <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"edLambda"
    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 -> [Char]
errMsg Double
l) forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Double -> Maybe ExponentialDistribution
exponentialE Double
l
  parseJSON Value
_ = forall (f :: * -> *) a. Alternative f => f a
empty

instance Binary ExponentialDistribution where
  put :: ExponentialDistribution -> Put
put = forall t. Binary t => t -> Put
put forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExponentialDistribution -> Double
edLambda
  get :: Get ExponentialDistribution
get = do
    Double
l <- 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 -> [Char]
errMsg Double
l) forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Double -> Maybe ExponentialDistribution
exponentialE Double
l

instance D.Distribution ExponentialDistribution where
    cumulative :: ExponentialDistribution -> Double -> Double
cumulative      = ExponentialDistribution -> Double -> Double
cumulative
    complCumulative :: ExponentialDistribution -> Double -> Double
complCumulative = ExponentialDistribution -> Double -> Double
complCumulative

instance D.ContDistr ExponentialDistribution where
    density :: ExponentialDistribution -> Double -> Double
density (ED Double
l) Double
x
      | Double
x forall a. Ord a => a -> a -> Bool
< Double
0     = Double
0
      | Bool
otherwise = Double
l forall a. Num a => a -> a -> a
* forall a. Floating a => a -> a
exp (-Double
l forall a. Num a => a -> a -> a
* Double
x)
    logDensity :: ExponentialDistribution -> Double -> Double
logDensity (ED Double
l) Double
x
      | Double
x forall a. Ord a => a -> a -> Bool
< Double
0     = Double
m_neg_inf
      | Bool
otherwise = forall a. Floating a => a -> a
log Double
l forall a. Num a => a -> a -> a
+ (-Double
l forall a. Num a => a -> a -> a
* Double
x)
    quantile :: ExponentialDistribution -> Double -> Double
quantile      = ExponentialDistribution -> Double -> Double
quantile
    complQuantile :: ExponentialDistribution -> Double -> Double
complQuantile = ExponentialDistribution -> Double -> Double
complQuantile

instance D.Mean ExponentialDistribution where
    mean :: ExponentialDistribution -> Double
mean (ED Double
l) = Double
1 forall a. Fractional a => a -> a -> a
/ Double
l

instance D.Variance ExponentialDistribution where
    variance :: ExponentialDistribution -> Double
variance (ED Double
l) = Double
1 forall a. Fractional a => a -> a -> a
/ (Double
l forall a. Num a => a -> a -> a
* Double
l)

instance D.MaybeMean ExponentialDistribution where
    maybeMean :: ExponentialDistribution -> 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 ExponentialDistribution where
    maybeStdDev :: ExponentialDistribution -> 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 :: ExponentialDistribution -> 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 ExponentialDistribution where
  entropy :: ExponentialDistribution -> Double
entropy (ED Double
l) = Double
1 forall a. Num a => a -> a -> a
- forall a. Floating a => a -> a
log Double
l

instance D.MaybeEntropy ExponentialDistribution where
  maybeEntropy :: ExponentialDistribution -> 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

instance D.ContGen ExponentialDistribution where
  genContVar :: forall g (m :: * -> *).
StatefulGen g m =>
ExponentialDistribution -> g -> m Double
genContVar = forall g (m :: * -> *). StatefulGen g m => Double -> g -> m Double
MWC.exponential forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExponentialDistribution -> Double
edLambda

cumulative :: ExponentialDistribution -> Double -> Double
cumulative :: ExponentialDistribution -> Double -> Double
cumulative (ED Double
l) Double
x | Double
x forall a. Ord a => a -> a -> Bool
<= Double
0    = Double
0
                    | Bool
otherwise = - forall a. Floating a => a -> a
expm1 (-Double
l forall a. Num a => a -> a -> a
* Double
x)

complCumulative :: ExponentialDistribution -> Double -> Double
complCumulative :: ExponentialDistribution -> Double -> Double
complCumulative (ED Double
l) Double
x | Double
x forall a. Ord a => a -> a -> Bool
<= Double
0    = Double
1
                         | Bool
otherwise = forall a. Floating a => a -> a
exp (-Double
l forall a. Num a => a -> a -> a
* Double
x)


quantile :: ExponentialDistribution -> Double -> Double
quantile :: ExponentialDistribution -> Double -> Double
quantile (ED Double
l) Double
p
  | Double
p forall a. Ord a => a -> a -> Bool
>= Double
0 Bool -> Bool -> Bool
&& Double
p forall a. Ord a => a -> a -> Bool
<= Double
1 = - forall a. Floating a => a -> a
log1p(-Double
p) forall a. Fractional a => a -> a -> a
/ Double
l
  | Bool
otherwise        =
    forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Statistics.Distribution.Exponential.quantile: p must be in [0,1] range. Got: "forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> [Char]
show Double
p

complQuantile :: ExponentialDistribution -> Double -> Double
complQuantile :: ExponentialDistribution -> Double -> Double
complQuantile (ED Double
l) Double
p
  | Double
p forall a. Eq a => a -> a -> Bool
== Double
0          = Double
0
  | Double
p forall a. Ord a => a -> a -> Bool
>= Double
0 Bool -> Bool -> Bool
&& Double
p forall a. Ord a => a -> a -> Bool
< Double
1 = -forall a. Floating a => a -> a
log Double
p forall a. Fractional a => a -> a -> a
/ Double
l
  | Bool
otherwise       =
    forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Statistics.Distribution.Exponential.quantile: p must be in [0,1] range. Got: "forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> [Char]
show Double
p

-- | Create an exponential distribution.
exponential :: Double            -- ^ Rate parameter.
            -> ExponentialDistribution
exponential :: Double -> ExponentialDistribution
exponential Double
l = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ Double -> [Char]
errMsg Double
l) forall a. a -> a
id forall a b. (a -> b) -> a -> b
$ Double -> Maybe ExponentialDistribution
exponentialE Double
l

-- | Create an exponential distribution.
exponentialE :: Double            -- ^ Rate parameter.
             -> Maybe ExponentialDistribution
exponentialE :: Double -> Maybe ExponentialDistribution
exponentialE Double
l
  | Double
l forall a. Ord a => a -> a -> Bool
> Double
0     = forall a. a -> Maybe a
Just (Double -> ExponentialDistribution
ED Double
l)
  | Bool
otherwise = forall a. Maybe a
Nothing

errMsg :: Double -> String
errMsg :: Double -> [Char]
errMsg Double
l = [Char]
"Statistics.Distribution.Exponential.exponential: scale parameter must be positive. Got " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> [Char]
show Double
l

-- | Create exponential distribution from sample.  Estimates the rate
--   with the maximum likelihood estimator, which is biased. Returns
--   @Nothing@ if the sample mean does not exist or is not positive.
instance D.FromSample ExponentialDistribution Double where
  fromSample :: forall (v :: * -> *).
Vector v Double =>
v Double -> Maybe ExponentialDistribution
fromSample v Double
xs = let m :: Double
m = forall (v :: * -> *). Vector v Double => v Double -> Double
S.mean v Double
xs
                  in  if Double
m forall a. Ord a => a -> a -> Bool
> Double
0 then forall a. a -> Maybe a
Just (Double -> ExponentialDistribution
ED (Double
1forall a. Fractional a => a -> a -> a
/Double
m)) else forall a. Maybe a
Nothing