random-fu-0.2.7.0: Random number generation

Safe HaskellNone
LanguageHaskell98

Data.Random.Distribution

Synopsis

Documentation

class Distribution d t where Source #

A Distribution is a data representation of a random variable's probability structure. For example, in Data.Random.Distribution.Normal, the Normal distribution is defined as:

data Normal a
    = StdNormal
    | Normal a a

Where the two parameters of the Normal data constructor are the mean and standard deviation of the random variable, respectively. To make use of the Normal type, one can convert it to an rvar and manipulate it or sample it directly:

x <- sample (rvar (Normal 10 2))
x <- sample (Normal 10 2)

A Distribution is typically more transparent than an RVar but less composable (precisely because of that transparency). There are several practical uses for types implementing Distribution:

  • Typically, a Distribution will expose several parameters of a standard mathematical model of a probability distribution, such as mean and std deviation for the normal distribution. Thus, they can be manipulated analytically using mathematical insights about the distributions they represent. For example, a collection of bernoulli variables could be simplified into a (hopefully) smaller collection of binomial variables.
  • Because they are generally just containers for parameters, they can be easily serialized to persistent storage or read from user-supplied configurations (eg, initialization data for a simulation).
  • If a type additionally implements the CDF subclass, which extends Distribution with a cumulative density function, an arbitrary random variable x can be tested against the distribution by testing fmap (cdf dist) x for uniformity.

On the other hand, most Distributions will not be closed under all the same operations as RVar (which, being a monad, has a fully turing-complete internal computational model). The sum of two uniformly-distributed variables, for example, is not uniformly distributed. To support general composition, the Distribution class defines a function rvar to construct the more-abstract and more-composable RVar representation of a random variable.

Methods

rvar :: d t -> RVar t Source #

Return a random variable with this distribution.

rvarT :: d t -> RVarT n t Source #

Return a random variable with the given distribution, pre-lifted to an arbitrary RVarT. Any arbitrary RVar can also be converted to an 'RVarT m' for an arbitrary m, using either lift or sample.

Instances

Distribution StdUniform Bool Source # 
Distribution StdUniform Char Source # 
Distribution StdUniform Double Source # 
Distribution StdUniform Float Source # 
Distribution StdUniform Int Source # 
Distribution StdUniform Int8 Source # 
Distribution StdUniform Int16 Source # 
Distribution StdUniform Int32 Source # 
Distribution StdUniform Int64 Source # 
Distribution StdUniform Ordering Source # 
Distribution StdUniform Word Source # 
Distribution StdUniform Word8 Source # 
Distribution StdUniform Word16 Source # 
Distribution StdUniform Word32 Source # 
Distribution StdUniform Word64 Source # 
Distribution StdUniform () Source # 

Methods

rvar :: StdUniform () -> RVar () Source #

rvarT :: StdUniform () -> RVarT n () Source #

Distribution Uniform Bool Source # 
Distribution Uniform Char Source # 
Distribution Uniform Double Source # 
Distribution Uniform Float Source # 
Distribution Uniform Int Source # 
Distribution Uniform Int8 Source # 
Distribution Uniform Int16 Source # 
Distribution Uniform Int32 Source # 
Distribution Uniform Int64 Source # 
Distribution Uniform Integer Source # 
Distribution Uniform Ordering Source # 
Distribution Uniform Word Source # 
Distribution Uniform Word8 Source # 
Distribution Uniform Word16 Source # 
Distribution Uniform Word32 Source # 
Distribution Uniform Word64 Source # 
Distribution Uniform () Source # 

Methods

rvar :: Uniform () -> RVar () Source #

rvarT :: Uniform () -> RVarT n () Source #

(Floating a, Distribution StdUniform a) => Distribution Exponential a Source # 

Methods

rvar :: Exponential a -> RVar a Source #

rvarT :: Exponential a -> RVarT n a Source #

(Floating a, Distribution StdUniform a) => Distribution StretchedExponential a Source # 
Distribution Normal Double Source # 
Distribution Normal Float Source # 
(Floating a, Ord a, Distribution Normal a, Distribution StdUniform a) => Distribution Gamma a Source # 

Methods

rvar :: Gamma a -> RVar a Source #

rvarT :: Gamma a -> RVarT n a Source #

Distribution Beta Double Source # 
Distribution Beta Float Source # 
(Fractional t, Distribution Gamma t) => Distribution ChiSquare t Source # 

Methods

rvar :: ChiSquare t -> RVar t Source #

rvarT :: ChiSquare t -> RVarT n t Source #

(RealFloat a, Distribution StdUniform a) => Distribution Rayleigh a Source # 

Methods

rvar :: Rayleigh a -> RVar a Source #

rvarT :: Rayleigh a -> RVarT n a Source #

(Floating a, Distribution Normal a, Distribution ChiSquare a) => Distribution T a Source # 

Methods

rvar :: T a -> RVar a Source #

rvarT :: T a -> RVarT n a Source #

(RealFloat a, Ord a, Distribution StdUniform a) => Distribution Triangular a Source # 

Methods

rvar :: Triangular a -> RVar a Source #

rvarT :: Triangular a -> RVarT n a Source #

(Floating a, Distribution StdUniform a) => Distribution Weibull a Source # 

Methods

rvar :: Weibull a -> RVar a Source #

rvarT :: Weibull a -> RVarT n a Source #

(Floating a, Distribution StdUniform a) => Distribution Pareto a Source # 

Methods

rvar :: Pareto a -> RVar a Source #

rvarT :: Pareto a -> RVarT n a Source #

HasResolution r => Distribution StdUniform (Fixed r) Source # 

Methods

rvar :: StdUniform (Fixed r) -> RVar (Fixed r) Source #

rvarT :: StdUniform (Fixed r) -> RVarT n (Fixed r) Source #

HasResolution r => Distribution Uniform (Fixed r) Source # 

Methods

rvar :: Uniform (Fixed r) -> RVar (Fixed r) Source #

rvarT :: Uniform (Fixed r) -> RVarT n (Fixed r) Source #

(Fractional a, Distribution Gamma a) => Distribution Dirichlet [a] Source # 

Methods

rvar :: Dirichlet [a] -> RVar [a] Source #

rvarT :: Dirichlet [a] -> RVarT n [a] Source #

(Ord a, Fractional a, Distribution StdUniform a) => Distribution StdSimplex [a] Source # 

Methods

rvar :: StdSimplex [a] -> RVar [a] Source #

rvarT :: StdSimplex [a] -> RVarT n [a] Source #

(Fractional b, Ord b, Distribution StdUniform b) => Distribution (Bernoulli b) Bool Source # 
Distribution (Bernoulli b0) Bool => Distribution (Bernoulli b0) Word64 Source # 
Distribution (Bernoulli b0) Bool => Distribution (Bernoulli b0) Word32 Source # 
Distribution (Bernoulli b0) Bool => Distribution (Bernoulli b0) Word16 Source # 
Distribution (Bernoulli b0) Bool => Distribution (Bernoulli b0) Word8 Source # 
Distribution (Bernoulli b0) Bool => Distribution (Bernoulli b0) Word Source # 
Distribution (Bernoulli b0) Bool => Distribution (Bernoulli b0) Int64 Source # 
Distribution (Bernoulli b0) Bool => Distribution (Bernoulli b0) Int32 Source # 
Distribution (Bernoulli b0) Bool => Distribution (Bernoulli b0) Int16 Source # 
Distribution (Bernoulli b0) Bool => Distribution (Bernoulli b0) Int8 Source # 
Distribution (Bernoulli b0) Bool => Distribution (Bernoulli b0) Int Source # 
Distribution (Bernoulli b0) Bool => Distribution (Bernoulli b0) Integer Source # 
Distribution (Bernoulli b0) Bool => Distribution (Bernoulli b0) Double Source # 
Distribution (Bernoulli b0) Bool => Distribution (Bernoulli b0) Float Source # 
(Fractional p, Ord p, Distribution Uniform p) => Distribution (Categorical p) a Source # 

Methods

rvar :: Categorical p a -> RVar a Source #

rvarT :: Categorical p a -> RVarT n a Source #

(Num t, Ord t, Vector v t) => Distribution (Ziggurat v) t Source # 

Methods

rvar :: Ziggurat v t -> RVar t Source #

rvarT :: Ziggurat v t -> RVarT n t Source #

(Integral a, Floating b, Ord b, Distribution Normal b, Distribution StdUniform b) => Distribution (Erlang a) b Source # 

Methods

rvar :: Erlang a b -> RVar b Source #

rvarT :: Erlang a b -> RVarT n b Source #

(Floating b0, Ord b0, Distribution Beta b0, Distribution StdUniform b0) => Distribution (Binomial b0) Word64 Source # 
(Floating b0, Ord b0, Distribution Beta b0, Distribution StdUniform b0) => Distribution (Binomial b0) Word32 Source # 
(Floating b0, Ord b0, Distribution Beta b0, Distribution StdUniform b0) => Distribution (Binomial b0) Word16 Source # 
(Floating b0, Ord b0, Distribution Beta b0, Distribution StdUniform b0) => Distribution (Binomial b0) Word8 Source # 
(Floating b0, Ord b0, Distribution Beta b0, Distribution StdUniform b0) => Distribution (Binomial b0) Word Source # 
(Floating b0, Ord b0, Distribution Beta b0, Distribution StdUniform b0) => Distribution (Binomial b0) Int64 Source # 
(Floating b0, Ord b0, Distribution Beta b0, Distribution StdUniform b0) => Distribution (Binomial b0) Int32 Source # 
(Floating b0, Ord b0, Distribution Beta b0, Distribution StdUniform b0) => Distribution (Binomial b0) Int16 Source # 
(Floating b0, Ord b0, Distribution Beta b0, Distribution StdUniform b0) => Distribution (Binomial b0) Int8 Source # 
(Floating b0, Ord b0, Distribution Beta b0, Distribution StdUniform b0) => Distribution (Binomial b0) Int Source # 
(Floating b0, Ord b0, Distribution Beta b0, Distribution StdUniform b0) => Distribution (Binomial b0) Integer Source # 
Distribution (Binomial b0) Integer => Distribution (Binomial b0) Double Source # 
Distribution (Binomial b0) Integer => Distribution (Binomial b0) Float Source # 
(RealFloat b0, Distribution StdUniform b0, Distribution (Erlang Word64) b0, Distribution (Binomial b0) Word64) => Distribution (Poisson b0) Word64 Source # 
(RealFloat b0, Distribution StdUniform b0, Distribution (Erlang Word32) b0, Distribution (Binomial b0) Word32) => Distribution (Poisson b0) Word32 Source # 
(RealFloat b0, Distribution StdUniform b0, Distribution (Erlang Word16) b0, Distribution (Binomial b0) Word16) => Distribution (Poisson b0) Word16 Source # 
(RealFloat b0, Distribution StdUniform b0, Distribution (Erlang Word8) b0, Distribution (Binomial b0) Word8) => Distribution (Poisson b0) Word8 Source # 
(RealFloat b0, Distribution StdUniform b0, Distribution (Erlang Word) b0, Distribution (Binomial b0) Word) => Distribution (Poisson b0) Word Source # 
(RealFloat b0, Distribution StdUniform b0, Distribution (Erlang Int64) b0, Distribution (Binomial b0) Int64) => Distribution (Poisson b0) Int64 Source # 
(RealFloat b0, Distribution StdUniform b0, Distribution (Erlang Int32) b0, Distribution (Binomial b0) Int32) => Distribution (Poisson b0) Int32 Source # 
(RealFloat b0, Distribution StdUniform b0, Distribution (Erlang Int16) b0, Distribution (Binomial b0) Int16) => Distribution (Poisson b0) Int16 Source # 
(RealFloat b0, Distribution StdUniform b0, Distribution (Erlang Int8) b0, Distribution (Binomial b0) Int8) => Distribution (Poisson b0) Int8 Source # 
(RealFloat b0, Distribution StdUniform b0, Distribution (Erlang Int) b0, Distribution (Binomial b0) Int) => Distribution (Poisson b0) Int Source # 

Methods

rvar :: Poisson b0 Int -> RVar Int Source #

rvarT :: Poisson b0 Int -> RVarT n Int Source #

(RealFloat b0, Distribution StdUniform b0, Distribution (Erlang Integer) b0, Distribution (Binomial b0) Integer) => Distribution (Poisson b0) Integer Source # 
Distribution (Poisson b0) Integer => Distribution (Poisson b0) Double Source # 
Distribution (Poisson b0) Integer => Distribution (Poisson b0) Float Source # 
(Distribution (Bernoulli b) Bool, RealFloat a) => Distribution (Bernoulli b) (Complex a) Source # 

Methods

rvar :: Bernoulli b (Complex a) -> RVar (Complex a) Source #

rvarT :: Bernoulli b (Complex a) -> RVarT n (Complex a) Source #

(Distribution (Bernoulli b) Bool, Integral a) => Distribution (Bernoulli b) (Ratio a) Source # 

Methods

rvar :: Bernoulli b (Ratio a) -> RVar (Ratio a) Source #

rvarT :: Bernoulli b (Ratio a) -> RVarT n (Ratio a) Source #

(Num a, Eq a, Fractional p, Distribution (Binomial p) a) => Distribution (Multinomial p) [a] Source # 

Methods

rvar :: Multinomial p [a] -> RVar [a] Source #

rvarT :: Multinomial p [a] -> RVarT n [a] Source #

class Distribution d t => PDF d t where Source #

Methods

pdf :: d t -> t -> Double Source #

logPdf :: d t -> t -> Double Source #

Instances

PDF StdUniform Double Source # 
PDF StdUniform Float Source # 
(Real a, Floating a, Distribution Normal a) => PDF Normal a Source # 

Methods

pdf :: Normal a -> a -> Double Source #

logPdf :: Normal a -> a -> Double Source #

PDF Beta Double Source # 
PDF Beta Float Source # 
(Real b0, Distribution (Binomial b0) Word64) => PDF (Binomial b0) Word64 Source # 
(Real b0, Distribution (Binomial b0) Word32) => PDF (Binomial b0) Word32 Source # 
(Real b0, Distribution (Binomial b0) Word16) => PDF (Binomial b0) Word16 Source # 
(Real b0, Distribution (Binomial b0) Word8) => PDF (Binomial b0) Word8 Source # 
(Real b0, Distribution (Binomial b0) Word) => PDF (Binomial b0) Word Source # 
(Real b0, Distribution (Binomial b0) Int64) => PDF (Binomial b0) Int64 Source # 
(Real b0, Distribution (Binomial b0) Int32) => PDF (Binomial b0) Int32 Source # 
(Real b0, Distribution (Binomial b0) Int16) => PDF (Binomial b0) Int16 Source # 
(Real b0, Distribution (Binomial b0) Int8) => PDF (Binomial b0) Int8 Source # 
(Real b0, Distribution (Binomial b0) Int) => PDF (Binomial b0) Int Source # 

Methods

pdf :: Binomial b0 Int -> Int -> Double Source #

logPdf :: Binomial b0 Int -> Int -> Double Source #

(Real b0, Distribution (Binomial b0) Integer) => PDF (Binomial b0) Integer Source # 
PDF (Binomial b0) Integer => PDF (Binomial b0) Double Source # 
PDF (Binomial b0) Integer => PDF (Binomial b0) Float Source # 

class Distribution d t => CDF d t where Source #

Minimal complete definition

cdf

Methods

cdf :: d t -> t -> Double Source #

Return the cumulative distribution function of this distribution. That is, a function taking x :: t to the probability that the next sample will return a value less than or equal to x, according to some order or partial order (not necessarily an obvious one).

In the case where t is an instance of Ord, cdf should correspond to the CDF with respect to that order.

In other cases, cdf is only required to satisfy the following law: fmap (cdf d) (rvar d) must be uniformly distributed over (0,1). Inclusion of either endpoint is optional, though the preferred range is (0,1].

Note that this definition requires that cdf for a product type should _not_ be a joint CDF as commonly defined, as that definition violates both conditions. Instead, it should be a univariate CDF over the product type. That is, it should represent the CDF with respect to the lexicographic order of the product.

The present specification is probably only really useful for testing conformance of a variable to its target distribution, and I am open to suggestions for more-useful specifications (especially with regard to the interaction with product types).

Instances

CDF StdUniform Bool Source # 
CDF StdUniform Char Source # 
CDF StdUniform Double Source # 
CDF StdUniform Float Source # 
CDF StdUniform Int Source # 

Methods

cdf :: StdUniform Int -> Int -> Double Source #

CDF StdUniform Int8 Source # 
CDF StdUniform Int16 Source # 
CDF StdUniform Int32 Source # 
CDF StdUniform Int64 Source # 
CDF StdUniform Ordering Source # 
CDF StdUniform Word Source # 
CDF StdUniform Word8 Source # 
CDF StdUniform Word16 Source # 
CDF StdUniform Word32 Source # 
CDF StdUniform Word64 Source # 
CDF StdUniform () Source # 

Methods

cdf :: StdUniform () -> () -> Double Source #

CDF Uniform Bool Source # 

Methods

cdf :: Uniform Bool -> Bool -> Double Source #

CDF Uniform Char Source # 

Methods

cdf :: Uniform Char -> Char -> Double Source #

CDF Uniform Double Source # 
CDF Uniform Float Source # 

Methods

cdf :: Uniform Float -> Float -> Double Source #

CDF Uniform Int Source # 

Methods

cdf :: Uniform Int -> Int -> Double Source #

CDF Uniform Int8 Source # 

Methods

cdf :: Uniform Int8 -> Int8 -> Double Source #

CDF Uniform Int16 Source # 

Methods

cdf :: Uniform Int16 -> Int16 -> Double Source #

CDF Uniform Int32 Source # 

Methods

cdf :: Uniform Int32 -> Int32 -> Double Source #

CDF Uniform Int64 Source # 

Methods

cdf :: Uniform Int64 -> Int64 -> Double Source #

CDF Uniform Integer Source # 
CDF Uniform Ordering Source # 
CDF Uniform Word Source # 

Methods

cdf :: Uniform Word -> Word -> Double Source #

CDF Uniform Word8 Source # 

Methods

cdf :: Uniform Word8 -> Word8 -> Double Source #

CDF Uniform Word16 Source # 
CDF Uniform Word32 Source # 
CDF Uniform Word64 Source # 
CDF Uniform () Source # 

Methods

cdf :: Uniform () -> () -> Double Source #

(Real a, Distribution Exponential a) => CDF Exponential a Source # 

Methods

cdf :: Exponential a -> a -> Double Source #

(Real a, Distribution StretchedExponential a) => CDF StretchedExponential a Source # 

Methods

cdf :: StretchedExponential a -> a -> Double Source #

(Real a, Distribution Normal a) => CDF Normal a Source # 

Methods

cdf :: Normal a -> a -> Double Source #

(Real a, Distribution Gamma a) => CDF Gamma a Source # 

Methods

cdf :: Gamma a -> a -> Double Source #

(Real t, Distribution ChiSquare t) => CDF ChiSquare t Source # 

Methods

cdf :: ChiSquare t -> t -> Double Source #

(Real a, Distribution Rayleigh a) => CDF Rayleigh a Source # 

Methods

cdf :: Rayleigh a -> a -> Double Source #

(Real a, Distribution T a) => CDF T a Source # 

Methods

cdf :: T a -> a -> Double Source #

(RealFrac a, Distribution Triangular a) => CDF Triangular a Source # 

Methods

cdf :: Triangular a -> a -> Double Source #

(Real a, Distribution Weibull a) => CDF Weibull a Source # 

Methods

cdf :: Weibull a -> a -> Double Source #

(Real a, Distribution Pareto a) => CDF Pareto a Source # 

Methods

cdf :: Pareto a -> a -> Double Source #

HasResolution r => CDF StdUniform (Fixed r) Source # 

Methods

cdf :: StdUniform (Fixed r) -> Fixed r -> Double Source #

HasResolution r => CDF Uniform (Fixed r) Source # 

Methods

cdf :: Uniform (Fixed r) -> Fixed r -> Double Source #

(Distribution (Bernoulli b) Bool, Real b) => CDF (Bernoulli b) Bool Source # 

Methods

cdf :: Bernoulli b Bool -> Bool -> Double Source #

CDF (Bernoulli b0) Bool => CDF (Bernoulli b0) Word64 Source # 

Methods

cdf :: Bernoulli b0 Word64 -> Word64 -> Double Source #

CDF (Bernoulli b0) Bool => CDF (Bernoulli b0) Word32 Source # 

Methods

cdf :: Bernoulli b0 Word32 -> Word32 -> Double Source #

CDF (Bernoulli b0) Bool => CDF (Bernoulli b0) Word16 Source # 

Methods

cdf :: Bernoulli b0 Word16 -> Word16 -> Double Source #

CDF (Bernoulli b0) Bool => CDF (Bernoulli b0) Word8 Source # 

Methods

cdf :: Bernoulli b0 Word8 -> Word8 -> Double Source #

CDF (Bernoulli b0) Bool => CDF (Bernoulli b0) Word Source # 

Methods

cdf :: Bernoulli b0 Word -> Word -> Double Source #

CDF (Bernoulli b0) Bool => CDF (Bernoulli b0) Int64 Source # 

Methods

cdf :: Bernoulli b0 Int64 -> Int64 -> Double Source #

CDF (Bernoulli b0) Bool => CDF (Bernoulli b0) Int32 Source # 

Methods

cdf :: Bernoulli b0 Int32 -> Int32 -> Double Source #

CDF (Bernoulli b0) Bool => CDF (Bernoulli b0) Int16 Source # 

Methods

cdf :: Bernoulli b0 Int16 -> Int16 -> Double Source #

CDF (Bernoulli b0) Bool => CDF (Bernoulli b0) Int8 Source # 

Methods

cdf :: Bernoulli b0 Int8 -> Int8 -> Double Source #

CDF (Bernoulli b0) Bool => CDF (Bernoulli b0) Int Source # 

Methods

cdf :: Bernoulli b0 Int -> Int -> Double Source #

CDF (Bernoulli b0) Bool => CDF (Bernoulli b0) Integer Source # 
CDF (Bernoulli b0) Bool => CDF (Bernoulli b0) Double Source # 

Methods

cdf :: Bernoulli b0 Double -> Double -> Double Source #

CDF (Bernoulli b0) Bool => CDF (Bernoulli b0) Float Source # 

Methods

cdf :: Bernoulli b0 Float -> Float -> Double Source #

(Integral a, Real b, Distribution (Erlang a) b) => CDF (Erlang a) b Source # 

Methods

cdf :: Erlang a b -> b -> Double Source #

(Real b0, Distribution (Binomial b0) Word64) => CDF (Binomial b0) Word64 Source # 

Methods

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

(Real b0, Distribution (Binomial b0) Word32) => CDF (Binomial b0) Word32 Source # 

Methods

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

(Real b0, Distribution (Binomial b0) Word16) => CDF (Binomial b0) Word16 Source # 

Methods

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

(Real b0, Distribution (Binomial b0) Word8) => CDF (Binomial b0) Word8 Source # 

Methods

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

(Real b0, Distribution (Binomial b0) Word) => CDF (Binomial b0) Word Source # 

Methods

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

(Real b0, Distribution (Binomial b0) Int64) => CDF (Binomial b0) Int64 Source # 

Methods

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

(Real b0, Distribution (Binomial b0) Int32) => CDF (Binomial b0) Int32 Source # 

Methods

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

(Real b0, Distribution (Binomial b0) Int16) => CDF (Binomial b0) Int16 Source # 

Methods

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

(Real b0, Distribution (Binomial b0) Int8) => CDF (Binomial b0) Int8 Source # 

Methods

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

(Real b0, Distribution (Binomial b0) Int) => CDF (Binomial b0) Int Source # 

Methods

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

(Real b0, Distribution (Binomial b0) Integer) => CDF (Binomial b0) Integer Source # 
CDF (Binomial b0) Integer => CDF (Binomial b0) Double Source # 

Methods

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

CDF (Binomial b0) Integer => CDF (Binomial b0) Float Source # 

Methods

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

(Real b0, Distribution (Poisson b0) Word64) => CDF (Poisson b0) Word64 Source # 

Methods

cdf :: Poisson b0 Word64 -> Word64 -> Double Source #

(Real b0, Distribution (Poisson b0) Word32) => CDF (Poisson b0) Word32 Source # 

Methods

cdf :: Poisson b0 Word32 -> Word32 -> Double Source #

(Real b0, Distribution (Poisson b0) Word16) => CDF (Poisson b0) Word16 Source # 

Methods

cdf :: Poisson b0 Word16 -> Word16 -> Double Source #

(Real b0, Distribution (Poisson b0) Word8) => CDF (Poisson b0) Word8 Source # 

Methods

cdf :: Poisson b0 Word8 -> Word8 -> Double Source #

(Real b0, Distribution (Poisson b0) Word) => CDF (Poisson b0) Word Source # 

Methods

cdf :: Poisson b0 Word -> Word -> Double Source #

(Real b0, Distribution (Poisson b0) Int64) => CDF (Poisson b0) Int64 Source # 

Methods

cdf :: Poisson b0 Int64 -> Int64 -> Double Source #

(Real b0, Distribution (Poisson b0) Int32) => CDF (Poisson b0) Int32 Source # 

Methods

cdf :: Poisson b0 Int32 -> Int32 -> Double Source #

(Real b0, Distribution (Poisson b0) Int16) => CDF (Poisson b0) Int16 Source # 

Methods

cdf :: Poisson b0 Int16 -> Int16 -> Double Source #

(Real b0, Distribution (Poisson b0) Int8) => CDF (Poisson b0) Int8 Source # 

Methods

cdf :: Poisson b0 Int8 -> Int8 -> Double Source #

(Real b0, Distribution (Poisson b0) Int) => CDF (Poisson b0) Int Source # 

Methods

cdf :: Poisson b0 Int -> Int -> Double Source #

(Real b0, Distribution (Poisson b0) Integer) => CDF (Poisson b0) Integer Source # 

Methods

cdf :: Poisson b0 Integer -> Integer -> Double Source #

CDF (Poisson b0) Integer => CDF (Poisson b0) Double Source # 

Methods

cdf :: Poisson b0 Double -> Double -> Double Source #

CDF (Poisson b0) Integer => CDF (Poisson b0) Float Source # 

Methods

cdf :: Poisson b0 Float -> Float -> Double Source #

(CDF (Bernoulli b) Bool, RealFloat a) => CDF (Bernoulli b) (Complex a) Source # 

Methods

cdf :: Bernoulli b (Complex a) -> Complex a -> Double Source #

(CDF (Bernoulli b) Bool, Integral a) => CDF (Bernoulli b) (Ratio a) Source # 

Methods

cdf :: Bernoulli b (Ratio a) -> Ratio a -> Double Source #