random-fu-0.3.0.0: Random number generation
Safe HaskellNone
LanguageHaskell2010

Data.Random.Distribution.Binomial

Synopsis

Documentation

integralBinomialCDF :: (Integral a, Real b) => a -> b -> a -> Double Source #

integralBinomialPDF :: (Integral a, Real b) => a -> b -> a -> Double Source #

The probability of getting exactly k successes in n trials is given by the probability mass function:

\[ f(k;n,p) = \Pr(X = k) = \binom n k p^k(1-p)^{n-k} \]

Note that in integralBinomialPDF the parameters of the mass function are given first and the range of the random variable distributed according to the binomial distribution is given last. That is, \(f(2;4,0.5)\) is calculated by integralBinomialPDF 4 0.5 2.

integralBinomialLogPdf :: (Integral a, Real b) => a -> b -> a -> Double Source #

We use the method given in "Fast and accurate computation of binomial probabilities, Loader, C", http://octave.1599824.n4.nabble.com/attachment/3829107/0/loader2000Fast.pdf

binomial :: Distribution (Binomial b) a => a -> b -> RVar a Source #

binomialT :: Distribution (Binomial b) a => a -> b -> RVarT m a Source #

data Binomial b a Source #

Constructors

Binomial a b 

Instances

Instances details
CDF (Binomial b) Integer => CDF (Binomial b) Double Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

cdf :: Binomial b Double -> Double -> Double Source #

CDF (Binomial b) Integer => CDF (Binomial b) Float Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

cdf :: Binomial b Float -> Float -> Double Source #

(Real b, Distribution (Binomial b) Word64) => CDF (Binomial b) Word64 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

cdf :: Binomial b Word64 -> Word64 -> Double Source #

(Real b, Distribution (Binomial b) Word32) => CDF (Binomial b) Word32 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

cdf :: Binomial b Word32 -> Word32 -> Double Source #

(Real b, Distribution (Binomial b) Word16) => CDF (Binomial b) Word16 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

cdf :: Binomial b Word16 -> Word16 -> Double Source #

(Real b, Distribution (Binomial b) Word8) => CDF (Binomial b) Word8 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

cdf :: Binomial b Word8 -> Word8 -> Double Source #

(Real b, Distribution (Binomial b) Word) => CDF (Binomial b) Word Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

cdf :: Binomial b Word -> Word -> Double Source #

(Real b, Distribution (Binomial b) Int64) => CDF (Binomial b) Int64 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

cdf :: Binomial b Int64 -> Int64 -> Double Source #

(Real b, Distribution (Binomial b) Int32) => CDF (Binomial b) Int32 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

cdf :: Binomial b Int32 -> Int32 -> Double Source #

(Real b, Distribution (Binomial b) Int16) => CDF (Binomial b) Int16 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

cdf :: Binomial b Int16 -> Int16 -> Double Source #

(Real b, Distribution (Binomial b) Int8) => CDF (Binomial b) Int8 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

cdf :: Binomial b Int8 -> Int8 -> Double Source #

(Real b, Distribution (Binomial b) Int) => CDF (Binomial b) Int Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

cdf :: Binomial b Int -> Int -> Double Source #

(Real b, Distribution (Binomial b) Integer) => CDF (Binomial b) Integer Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

PDF (Binomial b) Integer => PDF (Binomial b) Double Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

PDF (Binomial b) Integer => PDF (Binomial b) Float Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

(Real b, Distribution (Binomial b) Word64) => PDF (Binomial b) Word64 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

(Real b, Distribution (Binomial b) Word32) => PDF (Binomial b) Word32 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

(Real b, Distribution (Binomial b) Word16) => PDF (Binomial b) Word16 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

(Real b, Distribution (Binomial b) Word8) => PDF (Binomial b) Word8 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

(Real b, Distribution (Binomial b) Word) => PDF (Binomial b) Word Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

(Real b, Distribution (Binomial b) Int64) => PDF (Binomial b) Int64 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

(Real b, Distribution (Binomial b) Int32) => PDF (Binomial b) Int32 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

(Real b, Distribution (Binomial b) Int16) => PDF (Binomial b) Int16 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

(Real b, Distribution (Binomial b) Int8) => PDF (Binomial b) Int8 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

(Real b, Distribution (Binomial b) Int) => PDF (Binomial b) Int Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

(Real b, Distribution (Binomial b) Integer) => PDF (Binomial b) Integer Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Distribution (Binomial b) Integer => Distribution (Binomial b) Double Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

rvar :: Binomial b Double -> RVar Double Source #

rvarT :: forall (n :: Type -> Type). Binomial b Double -> RVarT n Double Source #

Distribution (Binomial b) Integer => Distribution (Binomial b) Float Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

rvar :: Binomial b Float -> RVar Float Source #

rvarT :: forall (n :: Type -> Type). Binomial b Float -> RVarT n Float Source #

(Floating b, Ord b, Distribution Beta b, Distribution StdUniform b) => Distribution (Binomial b) Word64 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

rvar :: Binomial b Word64 -> RVar Word64 Source #

rvarT :: forall (n :: Type -> Type). Binomial b Word64 -> RVarT n Word64 Source #

(Floating b, Ord b, Distribution Beta b, Distribution StdUniform b) => Distribution (Binomial b) Word32 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

rvar :: Binomial b Word32 -> RVar Word32 Source #

rvarT :: forall (n :: Type -> Type). Binomial b Word32 -> RVarT n Word32 Source #

(Floating b, Ord b, Distribution Beta b, Distribution StdUniform b) => Distribution (Binomial b) Word16 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

rvar :: Binomial b Word16 -> RVar Word16 Source #

rvarT :: forall (n :: Type -> Type). Binomial b Word16 -> RVarT n Word16 Source #

(Floating b, Ord b, Distribution Beta b, Distribution StdUniform b) => Distribution (Binomial b) Word8 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

rvar :: Binomial b Word8 -> RVar Word8 Source #

rvarT :: forall (n :: Type -> Type). Binomial b Word8 -> RVarT n Word8 Source #

(Floating b, Ord b, Distribution Beta b, Distribution StdUniform b) => Distribution (Binomial b) Word Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

rvar :: Binomial b Word -> RVar Word Source #

rvarT :: forall (n :: Type -> Type). Binomial b Word -> RVarT n Word Source #

(Floating b, Ord b, Distribution Beta b, Distribution StdUniform b) => Distribution (Binomial b) Int64 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

rvar :: Binomial b Int64 -> RVar Int64 Source #

rvarT :: forall (n :: Type -> Type). Binomial b Int64 -> RVarT n Int64 Source #

(Floating b, Ord b, Distribution Beta b, Distribution StdUniform b) => Distribution (Binomial b) Int32 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

rvar :: Binomial b Int32 -> RVar Int32 Source #

rvarT :: forall (n :: Type -> Type). Binomial b Int32 -> RVarT n Int32 Source #

(Floating b, Ord b, Distribution Beta b, Distribution StdUniform b) => Distribution (Binomial b) Int16 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

rvar :: Binomial b Int16 -> RVar Int16 Source #

rvarT :: forall (n :: Type -> Type). Binomial b Int16 -> RVarT n Int16 Source #

(Floating b, Ord b, Distribution Beta b, Distribution StdUniform b) => Distribution (Binomial b) Int8 Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

rvar :: Binomial b Int8 -> RVar Int8 Source #

rvarT :: forall (n :: Type -> Type). Binomial b Int8 -> RVarT n Int8 Source #

(Floating b, Ord b, Distribution Beta b, Distribution StdUniform b) => Distribution (Binomial b) Int Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

rvar :: Binomial b Int -> RVar Int Source #

rvarT :: forall (n :: Type -> Type). Binomial b Int -> RVarT n Int Source #

(Floating b, Ord b, Distribution Beta b, Distribution StdUniform b) => Distribution (Binomial b) Integer Source # 
Instance details

Defined in Data.Random.Distribution.Binomial

Methods

rvar :: Binomial b Integer -> RVar Integer Source #

rvarT :: forall (n :: Type -> Type). Binomial b Integer -> RVarT n Integer Source #