| Copyright | (c) A. V. H. McPhail 2010, 2015 |
|---|---|
| License | BSD3 |
| Maintainer | haskell.vivian.mcphail <at> gmail <dot> com |
| Stability | provisional |
| Portability | uses ffi |
| Safe Haskell | None |
| Language | Haskell2010 |
Numeric.GSL.Distribution.Continuous
Description
GSL continuous random distribution functions
- data ZeroParamDist = Landau
- data OneParamDist
- data TwoParamDist
- data ThreeParamDist = LevySkew
- data MultiParamDist = Dirichlet
- data BivariateDist = BiGaussian
- data DistFunc
- random_0p :: ZeroParamDist -> Int -> Double
- random_0p_s :: RNG -> ZeroParamDist -> IO Double
- random_0p_v :: ZeroParamDist -> Int -> Int -> Vector Double
- density_0p :: ZeroParamDist -> DistFunc -> Double -> Double
- random_1p :: OneParamDist -> Int -> Double -> Double
- random_1p_s :: RNG -> OneParamDist -> Double -> IO Double
- random_1p_v :: OneParamDist -> Int -> Double -> Int -> Vector Double
- density_1p :: OneParamDist -> DistFunc -> Double -> Double -> Double
- random_2p :: TwoParamDist -> Int -> Double -> Double -> Double
- random_2p_s :: RNG -> TwoParamDist -> Double -> Double -> IO Double
- random_2p_v :: TwoParamDist -> Int -> Double -> Double -> Int -> Vector Double
- density_2p :: TwoParamDist -> DistFunc -> Double -> Double -> Double -> Double
- random_3p :: ThreeParamDist -> Int -> Double -> Double -> Double -> Double
- random_3p_s :: RNG -> ThreeParamDist -> Double -> Double -> Double -> IO Double
- random_3p_v :: ThreeParamDist -> Int -> Double -> Double -> Double -> Int -> Vector Double
- density_3p :: ThreeParamDist -> DistFunc -> Double -> Double -> Double -> Double -> Double
- random_mp :: MultiParamDist -> Int -> Vector Double -> Vector Double
- random_mp_s :: RNG -> MultiParamDist -> Vector Double -> IO (Vector Double)
- density_mp :: MultiParamDist -> DistFunc -> Vector Double -> Vector Double -> Double
- random_biv :: BivariateDist -> Int -> Double -> Double -> Double -> (Double, Double)
- random_biv_s :: RNG -> BivariateDist -> Double -> Double -> Double -> IO (Double, Double)
- random_biv_v :: BivariateDist -> Int -> Double -> Double -> Double -> Int -> (Vector Double, Vector Double)
- density_biv :: BivariateDist -> DistFunc -> Double -> Double -> Double -> (Double, Double) -> Double
- spherical_vector :: Int -> Int -> Vector Double
Documentation
data OneParamDist Source
Constructors
| Gaussian | standard deviation |
| Exponential | mean |
| Laplace | width |
| Cauchy | scale |
| Rayleigh | standard deviation |
| ChiSq | degrees of freedom |
| TDist | degrees of freedom |
| Logistic | scale |
Instances
data TwoParamDist Source
Constructors
| GaussianTail | limit, standard deviation |
| ExpPower | scale, exponent |
| RayleighTail | lower limit, standard deviation |
| Levy | scale, exponent |
| Gamma | par1, par2 |
| Uniform | lower, upper |
| Lognormal | offset, standard deviation |
| FDist | degrees of freedom, degrees of freedom |
| Beta | parameter a, parameter b |
| Pareto | exponent, scale |
| Weibull | scale, exponent |
| GumbellI | A, B |
| GumbellII | A, B |
Instances
data BivariateDist Source
Constructors
| BiGaussian | standard deviation, standard deviation, correlation coefficient |
Instances
Arguments
| :: ZeroParamDist | distribution type |
| -> Int | random seed |
| -> Double | result |
draw a sample from a zero parameter distribution
Arguments
| :: RNG | the random number generator |
| -> ZeroParamDist | distribution type |
| -> IO Double | result |
draw a sample from a zero parameter distribution
Arguments
| :: ZeroParamDist | distribution type |
| -> Int | random seed |
| -> Int | number of samples |
| -> Vector Double | result |
draw samples from a zero parameter distribution
Arguments
| :: ZeroParamDist | density type |
| -> DistFunc | distribution function type |
| -> Double | value |
| -> Double | result |
probability of a variate take a value outside the argument
Arguments
| :: OneParamDist | distribution type |
| -> Int | random seed |
| -> Double | parameter |
| -> Double | result |
draw a sample from a one parameter distribution
Arguments
| :: RNG | the random number generator |
| -> OneParamDist | distribution type |
| -> Double | parameter |
| -> IO Double | result |
draw a sample from a one parameter distribution
Arguments
| :: OneParamDist | distribution type |
| -> Int | random seed |
| -> Double | parameter |
| -> Int | number of samples |
| -> Vector Double | result |
draw samples from a one parameter distribution
Arguments
| :: OneParamDist | density type |
| -> DistFunc | distribution function type |
| -> Double | parameter |
| -> Double | value |
| -> Double | result |
probability of a variate take a value outside the argument
Arguments
| :: TwoParamDist | distribution type |
| -> Int | random seed |
| -> Double | parameter 1 |
| -> Double | parameter 2 |
| -> Double | result |
draw a sample from a two parameter distribution
Arguments
| :: RNG | the random number generator |
| -> TwoParamDist | distribution type |
| -> Double | parameter 1 |
| -> Double | parameter 2 |
| -> IO Double | result |
draw a sample from a two parameter distribution
Arguments
| :: TwoParamDist | distribution type |
| -> Int | random seed |
| -> Double | parameter 1 |
| -> Double | parameter 2 |
| -> Int | number of samples |
| -> Vector Double | result |
draw samples from a two parameter distribution
Arguments
| :: TwoParamDist | density type |
| -> DistFunc | distribution function type |
| -> Double | parameter 1 |
| -> Double | parameter 2 |
| -> Double | value |
| -> Double | result |
probability of a variate take a value outside the argument
Arguments
| :: ThreeParamDist | distribution type |
| -> Int | random seed |
| -> Double | parameter 1 |
| -> Double | parameter 2 |
| -> Double | parameter 3 |
| -> Double | result |
draw a sample from a three parameter distribution
Arguments
| :: RNG | the random number generator |
| -> ThreeParamDist | distribution type |
| -> Double | parameter 1 |
| -> Double | parameter 2 |
| -> Double | parameter 3 |
| -> IO Double | result |
draw a sample from a three parameter distribution
Arguments
| :: ThreeParamDist | distribution type |
| -> Int | random seed |
| -> Double | parameter 1 |
| -> Double | parameter 2 |
| -> Double | parameter 3 |
| -> Int | number of samples |
| -> Vector Double | result |
draw samples from a three parameter distribution
Arguments
| :: ThreeParamDist | density type |
| -> DistFunc | distribution function type |
| -> Double | parameter 1 |
| -> Double | parameter 2 |
| -> Double | parameter 3 |
| -> Double | value |
| -> Double | result |
probability of a variate take a value outside the argument
Arguments
| :: MultiParamDist | distribution type |
| -> Int | random seed |
| -> Vector Double | parameters |
| -> Vector Double | result |
draw a sample from a multi parameter distribution
Arguments
| :: RNG | the random number generator |
| -> MultiParamDist | distribution type |
| -> Vector Double | parameters |
| -> IO (Vector Double) | result |
draw a sample from a multi parameter distribution
Arguments
| :: MultiParamDist | density type |
| -> DistFunc | distribution function type |
| -> Vector Double | parameters |
| -> Vector Double | values |
| -> Double | result |
probability of a variate take a value outside the argument
Arguments
| :: BivariateDist | distribution type |
| -> Int | random seed |
| -> Double | parameter 1 |
| -> Double | parameter 2 |
| -> Double | parameter 3 |
| -> (Double, Double) | result |
draw a sample from a bivariate distribution
Arguments
| :: RNG | the random number generator |
| -> BivariateDist | distribution type |
| -> Double | parameter 1 |
| -> Double | parameter 2 |
| -> Double | parameter 3 |
| -> IO (Double, Double) | result |
draw a sample from a bivariate distribution
Arguments
| :: BivariateDist | distribution type |
| -> Int | random seed |
| -> Double | parameter 1 |
| -> Double | parameter 2 |
| -> Double | parameter 3 |
| -> Int | number of samples |
| -> (Vector Double, Vector Double) | result |
draw a sample from a bivariate distribution