{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
module Statistics.Distribution.Exponential
(
ExponentialDistribution
, exponential
, exponentialE
, 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
(ExponentialDistribution -> ExponentialDistribution -> Bool)
-> (ExponentialDistribution -> ExponentialDistribution -> Bool)
-> Eq ExponentialDistribution
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExponentialDistribution -> ExponentialDistribution -> Bool
== :: ExponentialDistribution -> ExponentialDistribution -> Bool
$c/= :: ExponentialDistribution -> ExponentialDistribution -> Bool
/= :: ExponentialDistribution -> ExponentialDistribution -> Bool
Eq, Typeable, Typeable ExponentialDistribution
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 -> Constr
ExponentialDistribution -> DataType
(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)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ExponentialDistribution
-> c ExponentialDistribution
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> ExponentialDistribution
-> c ExponentialDistribution
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExponentialDistribution
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ExponentialDistribution
$ctoConstr :: ExponentialDistribution -> Constr
toConstr :: ExponentialDistribution -> Constr
$cdataTypeOf :: ExponentialDistribution -> DataType
dataTypeOf :: ExponentialDistribution -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExponentialDistribution)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ExponentialDistribution)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExponentialDistribution)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ExponentialDistribution)
$cgmapT :: (forall b. Data b => b -> b)
-> ExponentialDistribution -> ExponentialDistribution
gmapT :: (forall b. Data b => b -> b)
-> ExponentialDistribution -> ExponentialDistribution
$cgmapQl :: 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
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ExponentialDistribution
-> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r
-> (forall d. Data d => d -> r')
-> ExponentialDistribution
-> r
$cgmapQ :: forall u.
(forall d. Data d => d -> u) -> ExponentialDistribution -> [u]
gmapQ :: forall u.
(forall d. Data d => d -> u) -> ExponentialDistribution -> [u]
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ExponentialDistribution -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ExponentialDistribution -> u
$cgmapM :: forall (m :: * -> *).
Monad 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
$cgmapMp :: 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
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ExponentialDistribution -> m ExponentialDistribution
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ExponentialDistribution -> m 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
$cfrom :: forall x. ExponentialDistribution -> Rep ExponentialDistribution x
from :: forall x. ExponentialDistribution -> Rep ExponentialDistribution x
$cto :: forall x. Rep ExponentialDistribution x -> ExponentialDistribution
to :: forall x. Rep ExponentialDistribution x -> ExponentialDistribution
Generic)
instance Show ExponentialDistribution where
showsPrec :: Int -> ExponentialDistribution -> ShowS
showsPrec Int
n (ED Double
l) = [Char] -> Double -> Int -> ShowS
forall a. Show a => [Char] -> a -> Int -> ShowS
defaultShow1 [Char]
"exponential" Double
l Int
n
instance Read ExponentialDistribution where
readPrec :: ReadPrec ExponentialDistribution
readPrec = [Char]
-> (Double -> Maybe ExponentialDistribution)
-> ReadPrec ExponentialDistribution
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 Object -> Key -> Parser Double
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"edLambda"
Parser ExponentialDistribution
-> (ExponentialDistribution -> Parser ExponentialDistribution)
-> Maybe ExponentialDistribution
-> Parser ExponentialDistribution
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> Parser ExponentialDistribution
forall a. [Char] -> Parser a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> Parser ExponentialDistribution)
-> [Char] -> Parser ExponentialDistribution
forall a b. (a -> b) -> a -> b
$ Double -> [Char]
errMsg Double
l) ExponentialDistribution -> Parser ExponentialDistribution
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ExponentialDistribution -> Parser ExponentialDistribution)
-> Maybe ExponentialDistribution -> Parser ExponentialDistribution
forall a b. (a -> b) -> a -> b
$ Double -> Maybe ExponentialDistribution
exponentialE Double
l
parseJSON Value
_ = Parser ExponentialDistribution
forall a. Parser a
forall (f :: * -> *) a. Alternative f => f a
empty
instance Binary ExponentialDistribution where
put :: ExponentialDistribution -> Put
put = Double -> Put
forall t. Binary t => t -> Put
put (Double -> Put)
-> (ExponentialDistribution -> Double)
-> ExponentialDistribution
-> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExponentialDistribution -> Double
edLambda
get :: Get ExponentialDistribution
get = do
Double
l <- Get Double
forall t. Binary t => Get t
get
Get ExponentialDistribution
-> (ExponentialDistribution -> Get ExponentialDistribution)
-> Maybe ExponentialDistribution
-> Get ExponentialDistribution
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> Get ExponentialDistribution
forall a. [Char] -> Get a
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail ([Char] -> Get ExponentialDistribution)
-> [Char] -> Get ExponentialDistribution
forall a b. (a -> b) -> a -> b
$ Double -> [Char]
errMsg Double
l) ExponentialDistribution -> Get ExponentialDistribution
forall a. a -> Get a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ExponentialDistribution -> Get ExponentialDistribution)
-> Maybe ExponentialDistribution -> Get ExponentialDistribution
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 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 :: forall g (m :: * -> *).
StatefulGen g m =>
ExponentialDistribution -> g -> m Double
genContVar = Double -> g -> m Double
forall g (m :: * -> *). StatefulGen g m => Double -> g -> m Double
MWC.exponential (Double -> g -> m Double)
-> (ExponentialDistribution -> Double)
-> ExponentialDistribution
-> g
-> 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 =
[Char] -> Double
forall a. HasCallStack => [Char] -> a
error ([Char] -> Double) -> [Char] -> Double
forall a b. (a -> b) -> a -> b
$ [Char]
"Statistics.Distribution.Exponential.quantile: p must be in [0,1] range. Got: "[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++Double -> [Char]
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 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 =
[Char] -> Double
forall a. HasCallStack => [Char] -> a
error ([Char] -> Double) -> [Char] -> Double
forall a b. (a -> b) -> a -> b
$ [Char]
"Statistics.Distribution.Exponential.quantile: p must be in [0,1] range. Got: "[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++Double -> [Char]
forall a. Show a => a -> [Char]
show Double
p
exponential :: Double
-> ExponentialDistribution
exponential :: Double -> ExponentialDistribution
exponential Double
l = ExponentialDistribution
-> (ExponentialDistribution -> ExponentialDistribution)
-> Maybe ExponentialDistribution
-> ExponentialDistribution
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Char] -> ExponentialDistribution
forall a. HasCallStack => [Char] -> a
error ([Char] -> ExponentialDistribution)
-> [Char] -> ExponentialDistribution
forall a b. (a -> b) -> a -> b
$ Double -> [Char]
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
exponentialE :: Double
-> 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 -> [Char]
errMsg Double
l = [Char]
"Statistics.Distribution.Exponential.exponential: scale parameter must be positive. Got " [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Double -> [Char]
forall a. Show a => a -> [Char]
show Double
l
instance D.FromSample ExponentialDistribution Double where
fromSample :: forall (v :: * -> *).
Vector v Double =>
v Double -> Maybe ExponentialDistribution
fromSample v Double
xs = let m :: Double
m = v Double -> Double
forall (v :: * -> *). Vector v Double => v Double -> Double
S.mean v Double
xs
in if Double
m Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
0 then ExponentialDistribution -> Maybe ExponentialDistribution
forall a. a -> Maybe a
Just (Double -> ExponentialDistribution
ED (Double
1Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/Double
m)) else Maybe ExponentialDistribution
forall a. Maybe a
Nothing