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

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

Statistics.Distribution.Normal

Contents

Description

The normal distribution. This is a continuous probability distribution that describes data that cluster around a mean.

Synopsis

Documentation

data NormalDistribution Source #

The normal distribution.

Instances
Eq NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

Data NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

Methods

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

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

toConstr :: NormalDistribution -> Constr #

dataTypeOf :: NormalDistribution -> DataType #

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

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

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

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

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

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

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

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

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

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

Read NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

Show NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

Generic NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

Associated Types

type Rep NormalDistribution :: Type -> Type #

ToJSON NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

FromJSON NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

Binary NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

ContGen NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

Entropy NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

MaybeEntropy NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

Variance NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

MaybeVariance NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

Mean NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

MaybeMean NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

ContDistr NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

Distribution NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

FromSample NormalDistribution Double Source #

Variance is estimated using maximum likelihood method (biased estimation).

Returns Nothing if sample contains less than one element or variance is zero (all elements are equal)

Instance details

Defined in Statistics.Distribution.Normal

type Rep NormalDistribution Source # 
Instance details

Defined in Statistics.Distribution.Normal

type Rep NormalDistribution = D1 (MetaData "NormalDistribution" "Statistics.Distribution.Normal" "statistics-0.15.2.0-FCVAYbUNN6k6ys2hOZ1wTy" False) (C1 (MetaCons "ND" PrefixI True) ((S1 (MetaSel (Just "mean") SourceUnpack SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "stdDev") SourceUnpack SourceStrict DecidedStrict) (Rec0 Double)) :*: (S1 (MetaSel (Just "ndPdfDenom") SourceUnpack SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "ndCdfDenom") SourceUnpack SourceStrict DecidedStrict) (Rec0 Double))))

Constructors

normalDistr Source #

Arguments

:: Double

Mean of distribution

-> Double

Standard deviation of distribution

-> NormalDistribution 

Create normal distribution from parameters.

IMPORTANT: prior to 0.10 release second parameter was variance not standard deviation.

normalDistrE Source #

Arguments

:: Double

Mean of distribution

-> Double

Standard deviation of distribution

-> Maybe NormalDistribution 

Create normal distribution from parameters.

IMPORTANT: prior to 0.10 release second parameter was variance not standard deviation.

standard :: NormalDistribution Source #

Standard normal distribution with mean equal to 0 and variance equal to 1