statistics-0.16.1.0: A library of statistical types, data, and functions
Copyright(c) 2020 Ximin Luo
LicenseBSD3
Maintainerinfinity0@pwned.gg
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Statistics.Distribution.Weibull

Contents

Description

The Weibull distribution. This is a continuous probability distribution that describes the occurrence of a single event whose probability changes over time, controlled by the shape parameter.

Synopsis

Documentation

data WeibullDistribution Source #

The Weibull distribution.

Instances

Instances details
Eq WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

Data WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WeibullDistribution -> c WeibullDistribution #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WeibullDistribution #

toConstr :: WeibullDistribution -> Constr #

dataTypeOf :: WeibullDistribution -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WeibullDistribution) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WeibullDistribution) #

gmapT :: (forall b. Data b => b -> b) -> WeibullDistribution -> WeibullDistribution #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WeibullDistribution -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WeibullDistribution -> r #

gmapQ :: (forall d. Data d => d -> u) -> WeibullDistribution -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WeibullDistribution -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WeibullDistribution -> m WeibullDistribution #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WeibullDistribution -> m WeibullDistribution #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WeibullDistribution -> m WeibullDistribution #

Read WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

Show WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

Generic WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

Associated Types

type Rep WeibullDistribution :: Type -> Type #

ToJSON WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

FromJSON WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

Binary WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

ContGen WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

Entropy WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

MaybeEntropy WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

Variance WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

MaybeVariance WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

Mean WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

MaybeMean WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

ContDistr WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

Distribution WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

FromSample WeibullDistribution Double Source #

Uses an approximation based on the mean and standard deviation in weibullDistrEstMeanStddevErr, with standard deviation estimated using maximum likelihood method (unbiased estimation).

Returns Nothing if sample contains less than one element or variance is zero (all elements are equal), or if the estimated mean and standard-deviation lies outside the range for which the approximation is accurate.

Instance details

Defined in Statistics.Distribution.Weibull

type Rep WeibullDistribution Source # 
Instance details

Defined in Statistics.Distribution.Weibull

type Rep WeibullDistribution = D1 ('MetaData "WeibullDistribution" "Statistics.Distribution.Weibull" "statistics-0.16.1.0-Enynx6Q4EvxI2Qo45Shyhp" 'False) (C1 ('MetaCons "WD" 'PrefixI 'True) (S1 ('MetaSel ('Just "wdShape") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "wdLambda") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Double)))

Constructors

weibullDistr Source #

Arguments

:: Double

Shape

-> Double

Lambda (scale)

-> WeibullDistribution 

Create Weibull distribution from parameters.

If the shape (first) parameter is 1.0, the distribution is equivalent to a ExponentialDistribution with parameter 1 / lambda the scale (second) parameter.

weibullDistrErr Source #

Arguments

:: Double

Shape

-> Double

Lambda (scale)

-> Either String WeibullDistribution 

Create Weibull distribution from parameters.

If the shape (first) parameter is 1.0, the distribution is equivalent to a ExponentialDistribution with parameter 1 / lambda the scale (second) parameter.

weibullStandard :: Double -> WeibullDistribution Source #

Standard Weibull distribution with scale factor (lambda) 1.

weibullDistrApproxMeanStddevErr Source #

Arguments

:: Double

Mean

-> Double

Stddev

-> Either String WeibullDistribution 

Create Weibull distribution from mean and standard deviation.

The algorithm is from "Methods for Estimating Wind Speed Frequency Distributions", C. G. Justus, W. R. Hargreaves, A. Mikhail, D. Graber, 1977. Given the identity:

\[ (\frac{\sigma}{\mu})^2 = \frac{\Gamma(1+2/k)}{\Gamma(1+1/k)^2} - 1 \]

\(k\) can be approximated by

\[ k \approx (\frac{\sigma}{\mu})^{-1.086} \]

\(\lambda\) is then calculated straightforwardly via the identity

\[ \lambda = \frac{\mu}{\Gamma(1+1/k)} \]

Numerically speaking, the approximation for \(k\) is accurate only within a certain range. We arbitrarily pick the range \(0.033 \le \frac{\sigma}{\mu} \le 1.45\) where it is good to ~6%, and will refuse to create a distribution outside of this range. The paper does not cover these details but it is straightforward to check them numerically.