{-# 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.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 Data.Vector.Generic as G

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
(ExponentialDistribution -> ExponentialDistribution -> Bool)
-> (ExponentialDistribution -> ExponentialDistribution -> Bool)
-> Eq ExponentialDistribution
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
DataType
Constr
Typeable ExponentialDistribution
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> ExponentialDistribution
    -> c ExponentialDistribution)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ExponentialDistribution)
-> (ExponentialDistribution -> Constr)
-> (ExponentialDistribution -> DataType)
-> (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))
-> ((forall b. Data b => b -> b)
    -> ExponentialDistribution -> ExponentialDistribution)
-> (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 u.
    (forall d. Data d => d -> u) -> ExponentialDistribution -> [u])
-> (forall u.
    Int
    -> (forall d. Data d => d -> u) -> ExponentialDistribution -> u)
-> (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 (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> ExponentialDistribution -> m ExponentialDistribution)
-> Data ExponentialDistribution
ExponentialDistribution -> DataType
ExponentialDistribution -> Constr
(forall b. Data b => b -> b)
-> ExponentialDistribution -> ExponentialDistribution
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ExponentialDistribution
-> c ExponentialDistribution
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cED :: Constr
$tExponentialDistribution :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> ExponentialDistribution -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ExponentialDistribution -> u
gmapQ :: (forall d. Data d => d -> u) -> ExponentialDistribution -> [u]
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> ExponentialDistribution -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable ExponentialDistribution
Data, (forall x.
 ExponentialDistribution -> Rep ExponentialDistribution x)
-> (forall x.
    Rep ExponentialDistribution x -> ExponentialDistribution)
-> Generic ExponentialDistribution
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) = String -> Double -> Int -> ShowS
forall a. Show a => String -> a -> Int -> ShowS
defaultShow1 String
"exponential" Double
l Int
n
instance Read ExponentialDistribution where
  readPrec :: ReadPrec ExponentialDistribution
readPrec = String
-> (Double -> Maybe ExponentialDistribution)
-> ReadPrec ExponentialDistribution
forall a r. Read a => String -> (a -> Maybe r) -> ReadPrec r
defaultReadPrecM1 String
"exponential" Double -> Maybe ExponentialDistribution
exponentialE

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 Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0     = Double
0
      | Bool
otherwise = Double
l Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double -> Double
forall a. Floating a => a -> a
exp (-Double
l Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
x)
    logDensity :: ExponentialDistribution -> Double -> Double
logDensity (ED Double
l) Double
x
      | Double
x Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0     = Double
m_neg_inf
      | Bool
otherwise = Double -> Double
forall a. Floating a => a -> a
log Double
l Double -> Double -> Double
forall a. Num a => a -> a -> a
+ (-Double
l Double -> Double -> Double
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 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
l

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

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

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

instance D.Entropy ExponentialDistribution where
  entropy :: ExponentialDistribution -> Double
entropy (ED Double
l) = Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double -> Double
forall a. Floating a => a -> a
log Double
l

instance D.MaybeEntropy ExponentialDistribution where
  maybeEntropy :: ExponentialDistribution -> Maybe Double
maybeEntropy = Double -> Maybe Double
forall a. a -> Maybe a
Just (Double -> Maybe Double)
-> (ExponentialDistribution -> Double)
-> ExponentialDistribution
-> Maybe Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExponentialDistribution -> Double
forall d. Entropy d => d -> Double
D.entropy

instance D.ContGen ExponentialDistribution where
  genContVar :: ExponentialDistribution -> Gen (PrimState m) -> m Double
genContVar = Double -> Gen (PrimState m) -> m Double
forall g (m :: * -> *). StatefulGen g m => Double -> g -> m Double
MWC.exponential (Double -> Gen (PrimState m) -> m Double)
-> (ExponentialDistribution -> Double)
-> ExponentialDistribution
-> Gen (PrimState m)
-> m Double
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 Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
0    = Double
0
                    | Bool
otherwise = - Double -> Double
forall a. Floating a => a -> a
expm1 (-Double
l Double -> Double -> Double
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 Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
<= Double
0    = Double
1
                         | Bool
otherwise = Double -> Double
forall a. Floating a => a -> a
exp (-Double
l Double -> Double -> Double
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 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 -> Double
forall a. Floating a => a -> a
log1p(-Double
p) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
l
  | Bool
otherwise        =
    String -> Double
forall a. HasCallStack => String -> a
error (String -> Double) -> String -> Double
forall a b. (a -> b) -> a -> b
$ String
"Statistics.Distribution.Exponential.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

complQuantile :: ExponentialDistribution -> Double -> Double
complQuantile :: ExponentialDistribution -> Double -> Double
complQuantile (ED 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. 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 -> Double
forall a. Floating a => a -> a
log Double
p Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
l
  | Bool
otherwise       =
    String -> Double
forall a. HasCallStack => String -> a
error (String -> Double) -> String -> Double
forall a b. (a -> b) -> a -> b
$ String
"Statistics.Distribution.Exponential.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

-- | Create an exponential distribution.
exponential :: Double            -- ^ Rate parameter.
            -> ExponentialDistribution
exponential :: Double -> ExponentialDistribution
exponential Double
l = ExponentialDistribution
-> (ExponentialDistribution -> ExponentialDistribution)
-> Maybe ExponentialDistribution
-> ExponentialDistribution
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> ExponentialDistribution
forall a. HasCallStack => String -> a
error (String -> ExponentialDistribution)
-> String -> ExponentialDistribution
forall a b. (a -> b) -> a -> b
$ Double -> String
errMsg Double
l) ExponentialDistribution -> ExponentialDistribution
forall a. a -> a
id (Maybe ExponentialDistribution -> ExponentialDistribution)
-> Maybe ExponentialDistribution -> ExponentialDistribution
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 Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0     = ExponentialDistribution -> Maybe ExponentialDistribution
forall a. a -> Maybe a
Just (Double -> ExponentialDistribution
ED Double
l)
  | Bool
otherwise = Maybe ExponentialDistribution
forall a. Maybe a
Nothing

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

-- | Create exponential distribution from sample. Returns @Nothing@ if
--   sample is empty or contains negative elements. No other tests are
--   made to check whether it truly is exponential.
instance D.FromSample ExponentialDistribution Double where
  fromSample :: v Double -> Maybe ExponentialDistribution
fromSample v Double
xs
    | v Double -> Bool
forall (v :: * -> *) a. Vector v a => v a -> Bool
G.null v Double
xs       = Maybe ExponentialDistribution
forall a. Maybe a
Nothing
    | (Double -> Bool) -> v Double -> Bool
forall (v :: * -> *) a. Vector v a => (a -> Bool) -> v a -> Bool
G.all (Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
>= Double
0) v Double
xs = Maybe ExponentialDistribution
forall a. Maybe a
Nothing
    | Bool
otherwise       = ExponentialDistribution -> Maybe ExponentialDistribution
forall a. a -> Maybe a
Just (ExponentialDistribution -> Maybe ExponentialDistribution)
-> ExponentialDistribution -> Maybe ExponentialDistribution
forall a b. (a -> b) -> a -> b
$! Double -> ExponentialDistribution
ED (v Double -> Double
forall (v :: * -> *). Vector v Double => v Double -> Double
S.mean v Double
xs)