statistics-0.13.3.0: A library of statistical types, data, and functions

Copyright(c) 2009, 2011 Bryan O'Sullivan
LicenseBSD3
Maintainerbos@serpentine.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Statistics.Distribution.Gamma

Contents

Description

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 ϑ.

Synopsis

Documentation

data GammaDistribution Source #

The gamma distribution.

Instances

Eq GammaDistribution Source # 
Data GammaDistribution Source # 

Methods

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

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

toConstr :: GammaDistribution -> Constr #

dataTypeOf :: GammaDistribution -> DataType #

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

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

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

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

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

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

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

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

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

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

Read GammaDistribution Source # 
Show GammaDistribution Source # 
Generic GammaDistribution Source # 
ToJSON GammaDistribution Source # 
FromJSON GammaDistribution Source # 
Binary GammaDistribution Source # 
ContGen GammaDistribution Source # 
MaybeEntropy GammaDistribution Source # 
Variance GammaDistribution Source # 
MaybeVariance GammaDistribution Source # 
Mean GammaDistribution Source # 
MaybeMean GammaDistribution Source # 
ContDistr GammaDistribution Source # 
Distribution GammaDistribution Source # 
type Rep GammaDistribution Source # 
type Rep GammaDistribution = D1 (MetaData "GammaDistribution" "Statistics.Distribution.Gamma" "statistics-0.13.3.0-4cjYwUsSjEQGDMfnb5oeqe" False) (C1 (MetaCons "GD" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "gdShape") SourceUnpack SourceStrict DecidedUnpack) (Rec0 Double)) (S1 (MetaSel (Just Symbol "gdScale") SourceUnpack SourceStrict DecidedUnpack) (Rec0 Double))))

Constructors

gammaDistr Source #

Arguments

:: Double

Shape parameter. k

-> Double

Scale parameter, ϑ.

-> GammaDistribution 

Create gamma distribution. Both shape and scale parameters must be positive.

improperGammaDistr Source #

Arguments

:: Double

Shape parameter. k

-> Double

Scale parameter, ϑ.

-> GammaDistribution 

Create gamma distribution. This constructor do not check whether parameters are valid

Accessors

gdShape :: GammaDistribution -> Double Source #

Shape parameter, k.

gdScale :: GammaDistribution -> Double Source #

Scale parameter, ϑ.