module Bindings.Gsl.RandomNumberDistributions where
import Foreign.Ptr (Ptr,FunPtr,plusPtr)
import Foreign.Ptr (wordPtrToPtr,castPtrToFunPtr)
import Foreign.Storable
import Foreign.C.Types
import Foreign.C.String (CString,CStringLen,CWString,CWStringLen)
import Foreign.Marshal.Array (peekArray,pokeArray)
import Data.Int
import Data.Word
import Bindings.Gsl.RandomNumberGeneration
foreign import ccall "gsl_ran_bernoulli" c'gsl_ran_bernoulli
:: Ptr C'gsl_rng -> CDouble -> IO CUInt
foreign import ccall "&gsl_ran_bernoulli" p'gsl_ran_bernoulli
:: FunPtr (Ptr C'gsl_rng -> CDouble -> IO CUInt)
foreign import ccall "gsl_ran_bernoulli_pdf" c'gsl_ran_bernoulli_pdf
:: CUInt -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_bernoulli_pdf" p'gsl_ran_bernoulli_pdf
:: FunPtr (CUInt -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_beta" c'gsl_ran_beta
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_beta" p'gsl_ran_beta
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_beta_pdf" c'gsl_ran_beta_pdf
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_beta_pdf" p'gsl_ran_beta_pdf
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_binomial" c'gsl_ran_binomial
:: Ptr C'gsl_rng -> CDouble -> CUInt -> IO CUInt
foreign import ccall "&gsl_ran_binomial" p'gsl_ran_binomial
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CUInt -> IO CUInt)
foreign import ccall "gsl_ran_binomial_knuth" c'gsl_ran_binomial_knuth
:: Ptr C'gsl_rng -> CDouble -> CUInt -> IO CUInt
foreign import ccall "&gsl_ran_binomial_knuth" p'gsl_ran_binomial_knuth
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CUInt -> IO CUInt)
foreign import ccall "gsl_ran_binomial_tpe" c'gsl_ran_binomial_tpe
:: Ptr C'gsl_rng -> CDouble -> CUInt -> IO CUInt
foreign import ccall "&gsl_ran_binomial_tpe" p'gsl_ran_binomial_tpe
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CUInt -> IO CUInt)
foreign import ccall "gsl_ran_binomial_pdf" c'gsl_ran_binomial_pdf
:: CUInt -> CDouble -> CUInt -> IO CDouble
foreign import ccall "&gsl_ran_binomial_pdf" p'gsl_ran_binomial_pdf
:: FunPtr (CUInt -> CDouble -> CUInt -> IO CDouble)
foreign import ccall "gsl_ran_exponential" c'gsl_ran_exponential
:: Ptr C'gsl_rng -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_exponential" p'gsl_ran_exponential
:: FunPtr (Ptr C'gsl_rng -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_exponential_pdf" c'gsl_ran_exponential_pdf
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_exponential_pdf" p'gsl_ran_exponential_pdf
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_exppow" c'gsl_ran_exppow
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_exppow" p'gsl_ran_exppow
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_exppow_pdf" c'gsl_ran_exppow_pdf
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_exppow_pdf" p'gsl_ran_exppow_pdf
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_cauchy" c'gsl_ran_cauchy
:: Ptr C'gsl_rng -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_cauchy" p'gsl_ran_cauchy
:: FunPtr (Ptr C'gsl_rng -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_cauchy_pdf" c'gsl_ran_cauchy_pdf
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_cauchy_pdf" p'gsl_ran_cauchy_pdf
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_chisq" c'gsl_ran_chisq
:: Ptr C'gsl_rng -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_chisq" p'gsl_ran_chisq
:: FunPtr (Ptr C'gsl_rng -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_chisq_pdf" c'gsl_ran_chisq_pdf
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_chisq_pdf" p'gsl_ran_chisq_pdf
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_dirichlet" c'gsl_ran_dirichlet
:: Ptr C'gsl_rng -> CSize -> Ptr CDouble -> Ptr CDouble -> IO ()
foreign import ccall "&gsl_ran_dirichlet" p'gsl_ran_dirichlet
:: FunPtr (Ptr C'gsl_rng -> CSize -> Ptr CDouble -> Ptr CDouble -> IO ())
foreign import ccall "gsl_ran_dirichlet_pdf" c'gsl_ran_dirichlet_pdf
:: CSize -> Ptr CDouble -> Ptr CDouble -> IO CDouble
foreign import ccall "&gsl_ran_dirichlet_pdf" p'gsl_ran_dirichlet_pdf
:: FunPtr (CSize -> Ptr CDouble -> Ptr CDouble -> IO CDouble)
foreign import ccall "gsl_ran_dirichlet_lnpdf" c'gsl_ran_dirichlet_lnpdf
:: CSize -> Ptr CDouble -> Ptr CDouble -> IO CDouble
foreign import ccall "&gsl_ran_dirichlet_lnpdf" p'gsl_ran_dirichlet_lnpdf
:: FunPtr (CSize -> Ptr CDouble -> Ptr CDouble -> IO CDouble)
foreign import ccall "gsl_ran_erlang" c'gsl_ran_erlang
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_erlang" p'gsl_ran_erlang
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_erlang_pdf" c'gsl_ran_erlang_pdf
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_erlang_pdf" p'gsl_ran_erlang_pdf
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_fdist" c'gsl_ran_fdist
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_fdist" p'gsl_ran_fdist
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_fdist_pdf" c'gsl_ran_fdist_pdf
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_fdist_pdf" p'gsl_ran_fdist_pdf
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_flat" c'gsl_ran_flat
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_flat" p'gsl_ran_flat
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_flat_pdf" c'gsl_ran_flat_pdf
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_flat_pdf" p'gsl_ran_flat_pdf
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_gamma" c'gsl_ran_gamma
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_gamma" p'gsl_ran_gamma
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_gamma_int" c'gsl_ran_gamma_int
:: Ptr C'gsl_rng -> CUInt -> IO CDouble
foreign import ccall "&gsl_ran_gamma_int" p'gsl_ran_gamma_int
:: FunPtr (Ptr C'gsl_rng -> CUInt -> IO CDouble)
foreign import ccall "gsl_ran_gamma_pdf" c'gsl_ran_gamma_pdf
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_gamma_pdf" p'gsl_ran_gamma_pdf
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_gamma_mt" c'gsl_ran_gamma_mt
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_gamma_mt" p'gsl_ran_gamma_mt
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_gamma_knuth" c'gsl_ran_gamma_knuth
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_gamma_knuth" p'gsl_ran_gamma_knuth
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_gaussian" c'gsl_ran_gaussian
:: Ptr C'gsl_rng -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_gaussian" p'gsl_ran_gaussian
:: FunPtr (Ptr C'gsl_rng -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_gaussian_ratio_method" c'gsl_ran_gaussian_ratio_method
:: Ptr C'gsl_rng -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_gaussian_ratio_method" p'gsl_ran_gaussian_ratio_method
:: FunPtr (Ptr C'gsl_rng -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_gaussian_ziggurat" c'gsl_ran_gaussian_ziggurat
:: Ptr C'gsl_rng -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_gaussian_ziggurat" p'gsl_ran_gaussian_ziggurat
:: FunPtr (Ptr C'gsl_rng -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_gaussian_pdf" c'gsl_ran_gaussian_pdf
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_gaussian_pdf" p'gsl_ran_gaussian_pdf
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_ugaussian" c'gsl_ran_ugaussian
:: Ptr C'gsl_rng -> IO CDouble
foreign import ccall "&gsl_ran_ugaussian" p'gsl_ran_ugaussian
:: FunPtr (Ptr C'gsl_rng -> IO CDouble)
foreign import ccall "gsl_ran_ugaussian_ratio_method" c'gsl_ran_ugaussian_ratio_method
:: Ptr C'gsl_rng -> IO CDouble
foreign import ccall "&gsl_ran_ugaussian_ratio_method" p'gsl_ran_ugaussian_ratio_method
:: FunPtr (Ptr C'gsl_rng -> IO CDouble)
foreign import ccall "gsl_ran_ugaussian_pdf" c'gsl_ran_ugaussian_pdf
:: CDouble -> IO CDouble
foreign import ccall "&gsl_ran_ugaussian_pdf" p'gsl_ran_ugaussian_pdf
:: FunPtr (CDouble -> IO CDouble)
foreign import ccall "gsl_ran_gaussian_tail" c'gsl_ran_gaussian_tail
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_gaussian_tail" p'gsl_ran_gaussian_tail
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_gaussian_tail_pdf" c'gsl_ran_gaussian_tail_pdf
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_gaussian_tail_pdf" p'gsl_ran_gaussian_tail_pdf
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_ugaussian_tail" c'gsl_ran_ugaussian_tail
:: Ptr C'gsl_rng -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_ugaussian_tail" p'gsl_ran_ugaussian_tail
:: FunPtr (Ptr C'gsl_rng -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_ugaussian_tail_pdf" c'gsl_ran_ugaussian_tail_pdf
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_ugaussian_tail_pdf" p'gsl_ran_ugaussian_tail_pdf
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_bivariate_gaussian" c'gsl_ran_bivariate_gaussian
:: Ptr C'gsl_rng -> CDouble -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()
foreign import ccall "&gsl_ran_bivariate_gaussian" p'gsl_ran_bivariate_gaussian
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> CDouble -> Ptr CDouble -> Ptr CDouble -> IO ())
foreign import ccall "gsl_ran_bivariate_gaussian_pdf" c'gsl_ran_bivariate_gaussian_pdf
:: CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_bivariate_gaussian_pdf" p'gsl_ran_bivariate_gaussian_pdf
:: FunPtr (CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_landau" c'gsl_ran_landau
:: Ptr C'gsl_rng -> IO CDouble
foreign import ccall "&gsl_ran_landau" p'gsl_ran_landau
:: FunPtr (Ptr C'gsl_rng -> IO CDouble)
foreign import ccall "gsl_ran_landau_pdf" c'gsl_ran_landau_pdf
:: CDouble -> IO CDouble
foreign import ccall "&gsl_ran_landau_pdf" p'gsl_ran_landau_pdf
:: FunPtr (CDouble -> IO CDouble)
foreign import ccall "gsl_ran_geometric" c'gsl_ran_geometric
:: Ptr C'gsl_rng -> CDouble -> IO CUInt
foreign import ccall "&gsl_ran_geometric" p'gsl_ran_geometric
:: FunPtr (Ptr C'gsl_rng -> CDouble -> IO CUInt)
foreign import ccall "gsl_ran_geometric_pdf" c'gsl_ran_geometric_pdf
:: CUInt -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_geometric_pdf" p'gsl_ran_geometric_pdf
:: FunPtr (CUInt -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_hypergeometric" c'gsl_ran_hypergeometric
:: Ptr C'gsl_rng -> CUInt -> CUInt -> CUInt -> IO CUInt
foreign import ccall "&gsl_ran_hypergeometric" p'gsl_ran_hypergeometric
:: FunPtr (Ptr C'gsl_rng -> CUInt -> CUInt -> CUInt -> IO CUInt)
foreign import ccall "gsl_ran_hypergeometric_pdf" c'gsl_ran_hypergeometric_pdf
:: CUInt -> CUInt -> CUInt -> CUInt -> IO CDouble
foreign import ccall "&gsl_ran_hypergeometric_pdf" p'gsl_ran_hypergeometric_pdf
:: FunPtr (CUInt -> CUInt -> CUInt -> CUInt -> IO CDouble)
foreign import ccall "gsl_ran_gumbel1" c'gsl_ran_gumbel1
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_gumbel1" p'gsl_ran_gumbel1
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_gumbel1_pdf" c'gsl_ran_gumbel1_pdf
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_gumbel1_pdf" p'gsl_ran_gumbel1_pdf
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_gumbel2" c'gsl_ran_gumbel2
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_gumbel2" p'gsl_ran_gumbel2
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_gumbel2_pdf" c'gsl_ran_gumbel2_pdf
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_gumbel2_pdf" p'gsl_ran_gumbel2_pdf
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_logistic" c'gsl_ran_logistic
:: Ptr C'gsl_rng -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_logistic" p'gsl_ran_logistic
:: FunPtr (Ptr C'gsl_rng -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_logistic_pdf" c'gsl_ran_logistic_pdf
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_logistic_pdf" p'gsl_ran_logistic_pdf
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_lognormal" c'gsl_ran_lognormal
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_lognormal" p'gsl_ran_lognormal
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_lognormal_pdf" c'gsl_ran_lognormal_pdf
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_lognormal_pdf" p'gsl_ran_lognormal_pdf
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_logarithmic" c'gsl_ran_logarithmic
:: Ptr C'gsl_rng -> CDouble -> IO CUInt
foreign import ccall "&gsl_ran_logarithmic" p'gsl_ran_logarithmic
:: FunPtr (Ptr C'gsl_rng -> CDouble -> IO CUInt)
foreign import ccall "gsl_ran_logarithmic_pdf" c'gsl_ran_logarithmic_pdf
:: CUInt -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_logarithmic_pdf" p'gsl_ran_logarithmic_pdf
:: FunPtr (CUInt -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_multinomial" c'gsl_ran_multinomial
:: Ptr C'gsl_rng -> CSize -> CUInt -> Ptr CDouble -> Ptr CUInt -> IO ()
foreign import ccall "&gsl_ran_multinomial" p'gsl_ran_multinomial
:: FunPtr (Ptr C'gsl_rng -> CSize -> CUInt -> Ptr CDouble -> Ptr CUInt -> IO ())
foreign import ccall "gsl_ran_multinomial_pdf" c'gsl_ran_multinomial_pdf
:: CSize -> Ptr CDouble -> Ptr CUInt -> IO CDouble
foreign import ccall "&gsl_ran_multinomial_pdf" p'gsl_ran_multinomial_pdf
:: FunPtr (CSize -> Ptr CDouble -> Ptr CUInt -> IO CDouble)
foreign import ccall "gsl_ran_multinomial_lnpdf" c'gsl_ran_multinomial_lnpdf
:: CSize -> Ptr CDouble -> Ptr CUInt -> IO CDouble
foreign import ccall "&gsl_ran_multinomial_lnpdf" p'gsl_ran_multinomial_lnpdf
:: FunPtr (CSize -> Ptr CDouble -> Ptr CUInt -> IO CDouble)
foreign import ccall "gsl_ran_negative_binomial" c'gsl_ran_negative_binomial
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CUInt
foreign import ccall "&gsl_ran_negative_binomial" p'gsl_ran_negative_binomial
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CUInt)
foreign import ccall "gsl_ran_negative_binomial_pdf" c'gsl_ran_negative_binomial_pdf
:: CUInt -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_negative_binomial_pdf" p'gsl_ran_negative_binomial_pdf
:: FunPtr (CUInt -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_pascal" c'gsl_ran_pascal
:: Ptr C'gsl_rng -> CDouble -> CUInt -> IO CUInt
foreign import ccall "&gsl_ran_pascal" p'gsl_ran_pascal
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CUInt -> IO CUInt)
foreign import ccall "gsl_ran_pascal_pdf" c'gsl_ran_pascal_pdf
:: CUInt -> CDouble -> CUInt -> IO CDouble
foreign import ccall "&gsl_ran_pascal_pdf" p'gsl_ran_pascal_pdf
:: FunPtr (CUInt -> CDouble -> CUInt -> IO CDouble)
foreign import ccall "gsl_ran_pareto" c'gsl_ran_pareto
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_pareto" p'gsl_ran_pareto
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_pareto_pdf" c'gsl_ran_pareto_pdf
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_pareto_pdf" p'gsl_ran_pareto_pdf
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_poisson" c'gsl_ran_poisson
:: Ptr C'gsl_rng -> CDouble -> IO CUInt
foreign import ccall "&gsl_ran_poisson" p'gsl_ran_poisson
:: FunPtr (Ptr C'gsl_rng -> CDouble -> IO CUInt)
foreign import ccall "gsl_ran_poisson_array" c'gsl_ran_poisson_array
:: Ptr C'gsl_rng -> CSize -> Ptr CUInt -> CDouble -> IO ()
foreign import ccall "&gsl_ran_poisson_array" p'gsl_ran_poisson_array
:: FunPtr (Ptr C'gsl_rng -> CSize -> Ptr CUInt -> CDouble -> IO ())
foreign import ccall "gsl_ran_poisson_pdf" c'gsl_ran_poisson_pdf
:: CUInt -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_poisson_pdf" p'gsl_ran_poisson_pdf
:: FunPtr (CUInt -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_rayleigh" c'gsl_ran_rayleigh
:: Ptr C'gsl_rng -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_rayleigh" p'gsl_ran_rayleigh
:: FunPtr (Ptr C'gsl_rng -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_rayleigh_pdf" c'gsl_ran_rayleigh_pdf
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_rayleigh_pdf" p'gsl_ran_rayleigh_pdf
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_rayleigh_tail" c'gsl_ran_rayleigh_tail
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_rayleigh_tail" p'gsl_ran_rayleigh_tail
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_rayleigh_tail_pdf" c'gsl_ran_rayleigh_tail_pdf
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_rayleigh_tail_pdf" p'gsl_ran_rayleigh_tail_pdf
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_tdist" c'gsl_ran_tdist
:: Ptr C'gsl_rng -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_tdist" p'gsl_ran_tdist
:: FunPtr (Ptr C'gsl_rng -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_tdist_pdf" c'gsl_ran_tdist_pdf
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_tdist_pdf" p'gsl_ran_tdist_pdf
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_laplace" c'gsl_ran_laplace
:: Ptr C'gsl_rng -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_laplace" p'gsl_ran_laplace
:: FunPtr (Ptr C'gsl_rng -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_laplace_pdf" c'gsl_ran_laplace_pdf
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_laplace_pdf" p'gsl_ran_laplace_pdf
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_levy" c'gsl_ran_levy
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_levy" p'gsl_ran_levy
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_levy_skew" c'gsl_ran_levy_skew
:: Ptr C'gsl_rng -> CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_levy_skew" p'gsl_ran_levy_skew
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_weibull" c'gsl_ran_weibull
:: Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_weibull" p'gsl_ran_weibull
:: FunPtr (Ptr C'gsl_rng -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_weibull_pdf" c'gsl_ran_weibull_pdf
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_ran_weibull_pdf" p'gsl_ran_weibull_pdf
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_ran_dir_2d" c'gsl_ran_dir_2d
:: Ptr C'gsl_rng -> Ptr CDouble -> Ptr CDouble -> IO ()
foreign import ccall "&gsl_ran_dir_2d" p'gsl_ran_dir_2d
:: FunPtr (Ptr C'gsl_rng -> Ptr CDouble -> Ptr CDouble -> IO ())
foreign import ccall "gsl_ran_dir_2d_trig_method" c'gsl_ran_dir_2d_trig_method
:: Ptr C'gsl_rng -> Ptr CDouble -> Ptr CDouble -> IO ()
foreign import ccall "&gsl_ran_dir_2d_trig_method" p'gsl_ran_dir_2d_trig_method
:: FunPtr (Ptr C'gsl_rng -> Ptr CDouble -> Ptr CDouble -> IO ())
foreign import ccall "gsl_ran_dir_3d" c'gsl_ran_dir_3d
:: Ptr C'gsl_rng -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ()
foreign import ccall "&gsl_ran_dir_3d" p'gsl_ran_dir_3d
:: FunPtr (Ptr C'gsl_rng -> Ptr CDouble -> Ptr CDouble -> Ptr CDouble -> IO ())
foreign import ccall "gsl_ran_dir_nd" c'gsl_ran_dir_nd
:: Ptr C'gsl_rng -> CSize -> Ptr CDouble -> IO ()
foreign import ccall "&gsl_ran_dir_nd" p'gsl_ran_dir_nd
:: FunPtr (Ptr C'gsl_rng -> CSize -> Ptr CDouble -> IO ())
foreign import ccall "gsl_ran_shuffle" c'gsl_ran_shuffle
:: Ptr C'gsl_rng -> Ptr () -> CSize -> CSize -> IO ()
foreign import ccall "&gsl_ran_shuffle" p'gsl_ran_shuffle
:: FunPtr (Ptr C'gsl_rng -> Ptr () -> CSize -> CSize -> IO ())
foreign import ccall "gsl_ran_choose" c'gsl_ran_choose
:: Ptr C'gsl_rng -> Ptr () -> CSize -> Ptr () -> CSize -> CSize -> IO CInt
foreign import ccall "&gsl_ran_choose" p'gsl_ran_choose
:: FunPtr (Ptr C'gsl_rng -> Ptr () -> CSize -> Ptr () -> CSize -> CSize -> IO CInt)
foreign import ccall "gsl_ran_sample" c'gsl_ran_sample
:: Ptr C'gsl_rng -> Ptr () -> CSize -> Ptr () -> CSize -> CSize -> IO ()
foreign import ccall "&gsl_ran_sample" p'gsl_ran_sample
:: FunPtr (Ptr C'gsl_rng -> Ptr () -> CSize -> Ptr () -> CSize -> CSize -> IO ())
data C'gsl_ran_discrete_t = C'gsl_ran_discrete_t{
c'gsl_ran_discrete_t'K :: CSize
,
c'gsl_ran_discrete_t'A :: Ptr CSize
,
c'gsl_ran_discrete_t'F :: Ptr CDouble
} deriving (Eq,Show)
instance Storable C'gsl_ran_discrete_t where
sizeOf _ = 12
alignment = sizeOf
peek p = do
v0 <- peekByteOff p 0
v1 <- peekByteOff p 4
v2 <- peekByteOff p 8
return $ C'gsl_ran_discrete_t v0 v1 v2
poke p (C'gsl_ran_discrete_t v0 v1 v2) = do
pokeByteOff p 0 v0
pokeByteOff p 4 v1
pokeByteOff p 8 v2
return ()
foreign import ccall "gsl_ran_discrete_preproc" c'gsl_ran_discrete_preproc
:: CSize -> Ptr CDouble -> IO (Ptr C'gsl_ran_discrete_t)
foreign import ccall "&gsl_ran_discrete_preproc" p'gsl_ran_discrete_preproc
:: FunPtr (CSize -> Ptr CDouble -> IO (Ptr C'gsl_ran_discrete_t))
foreign import ccall "gsl_ran_discrete_free" c'gsl_ran_discrete_free
:: Ptr C'gsl_ran_discrete_t -> IO ()
foreign import ccall "&gsl_ran_discrete_free" p'gsl_ran_discrete_free
:: FunPtr (Ptr C'gsl_ran_discrete_t -> IO ())
foreign import ccall "gsl_ran_discrete" c'gsl_ran_discrete
:: Ptr C'gsl_rng -> Ptr C'gsl_ran_discrete_t -> IO CSize
foreign import ccall "&gsl_ran_discrete" p'gsl_ran_discrete
:: FunPtr (Ptr C'gsl_rng -> Ptr C'gsl_ran_discrete_t -> IO CSize)
foreign import ccall "gsl_ran_discrete_pdf" c'gsl_ran_discrete_pdf
:: CSize -> Ptr C'gsl_ran_discrete_t -> IO CDouble
foreign import ccall "&gsl_ran_discrete_pdf" p'gsl_ran_discrete_pdf
:: FunPtr (CSize -> Ptr C'gsl_ran_discrete_t -> IO CDouble)
foreign import ccall "gsl_cdf_ugaussian_P" c'gsl_cdf_ugaussian_P
:: CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_ugaussian_P" p'gsl_cdf_ugaussian_P
:: FunPtr (CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_ugaussian_Q" c'gsl_cdf_ugaussian_Q
:: CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_ugaussian_Q" p'gsl_cdf_ugaussian_Q
:: FunPtr (CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_ugaussian_Pinv" c'gsl_cdf_ugaussian_Pinv
:: CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_ugaussian_Pinv" p'gsl_cdf_ugaussian_Pinv
:: FunPtr (CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_ugaussian_Qinv" c'gsl_cdf_ugaussian_Qinv
:: CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_ugaussian_Qinv" p'gsl_cdf_ugaussian_Qinv
:: FunPtr (CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gaussian_P" c'gsl_cdf_gaussian_P
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gaussian_P" p'gsl_cdf_gaussian_P
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gaussian_Q" c'gsl_cdf_gaussian_Q
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gaussian_Q" p'gsl_cdf_gaussian_Q
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gaussian_Pinv" c'gsl_cdf_gaussian_Pinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gaussian_Pinv" p'gsl_cdf_gaussian_Pinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gaussian_Qinv" c'gsl_cdf_gaussian_Qinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gaussian_Qinv" p'gsl_cdf_gaussian_Qinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gamma_P" c'gsl_cdf_gamma_P
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gamma_P" p'gsl_cdf_gamma_P
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gamma_Q" c'gsl_cdf_gamma_Q
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gamma_Q" p'gsl_cdf_gamma_Q
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gamma_Pinv" c'gsl_cdf_gamma_Pinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gamma_Pinv" p'gsl_cdf_gamma_Pinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gamma_Qinv" c'gsl_cdf_gamma_Qinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gamma_Qinv" p'gsl_cdf_gamma_Qinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_cauchy_P" c'gsl_cdf_cauchy_P
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_cauchy_P" p'gsl_cdf_cauchy_P
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_cauchy_Q" c'gsl_cdf_cauchy_Q
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_cauchy_Q" p'gsl_cdf_cauchy_Q
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_cauchy_Pinv" c'gsl_cdf_cauchy_Pinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_cauchy_Pinv" p'gsl_cdf_cauchy_Pinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_cauchy_Qinv" c'gsl_cdf_cauchy_Qinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_cauchy_Qinv" p'gsl_cdf_cauchy_Qinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_laplace_P" c'gsl_cdf_laplace_P
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_laplace_P" p'gsl_cdf_laplace_P
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_laplace_Q" c'gsl_cdf_laplace_Q
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_laplace_Q" p'gsl_cdf_laplace_Q
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_laplace_Pinv" c'gsl_cdf_laplace_Pinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_laplace_Pinv" p'gsl_cdf_laplace_Pinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_laplace_Qinv" c'gsl_cdf_laplace_Qinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_laplace_Qinv" p'gsl_cdf_laplace_Qinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_rayleigh_P" c'gsl_cdf_rayleigh_P
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_rayleigh_P" p'gsl_cdf_rayleigh_P
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_rayleigh_Q" c'gsl_cdf_rayleigh_Q
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_rayleigh_Q" p'gsl_cdf_rayleigh_Q
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_rayleigh_Pinv" c'gsl_cdf_rayleigh_Pinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_rayleigh_Pinv" p'gsl_cdf_rayleigh_Pinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_rayleigh_Qinv" c'gsl_cdf_rayleigh_Qinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_rayleigh_Qinv" p'gsl_cdf_rayleigh_Qinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_chisq_P" c'gsl_cdf_chisq_P
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_chisq_P" p'gsl_cdf_chisq_P
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_chisq_Q" c'gsl_cdf_chisq_Q
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_chisq_Q" p'gsl_cdf_chisq_Q
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_chisq_Pinv" c'gsl_cdf_chisq_Pinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_chisq_Pinv" p'gsl_cdf_chisq_Pinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_chisq_Qinv" c'gsl_cdf_chisq_Qinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_chisq_Qinv" p'gsl_cdf_chisq_Qinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_exponential_P" c'gsl_cdf_exponential_P
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_exponential_P" p'gsl_cdf_exponential_P
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_exponential_Q" c'gsl_cdf_exponential_Q
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_exponential_Q" p'gsl_cdf_exponential_Q
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_exponential_Pinv" c'gsl_cdf_exponential_Pinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_exponential_Pinv" p'gsl_cdf_exponential_Pinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_exponential_Qinv" c'gsl_cdf_exponential_Qinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_exponential_Qinv" p'gsl_cdf_exponential_Qinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_exppow_P" c'gsl_cdf_exppow_P
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_exppow_P" p'gsl_cdf_exppow_P
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_exppow_Q" c'gsl_cdf_exppow_Q
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_exppow_Q" p'gsl_cdf_exppow_Q
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_tdist_P" c'gsl_cdf_tdist_P
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_tdist_P" p'gsl_cdf_tdist_P
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_tdist_Q" c'gsl_cdf_tdist_Q
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_tdist_Q" p'gsl_cdf_tdist_Q
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_tdist_Pinv" c'gsl_cdf_tdist_Pinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_tdist_Pinv" p'gsl_cdf_tdist_Pinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_tdist_Qinv" c'gsl_cdf_tdist_Qinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_tdist_Qinv" p'gsl_cdf_tdist_Qinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_fdist_P" c'gsl_cdf_fdist_P
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_fdist_P" p'gsl_cdf_fdist_P
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_fdist_Q" c'gsl_cdf_fdist_Q
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_fdist_Q" p'gsl_cdf_fdist_Q
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_fdist_Pinv" c'gsl_cdf_fdist_Pinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_fdist_Pinv" p'gsl_cdf_fdist_Pinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_fdist_Qinv" c'gsl_cdf_fdist_Qinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_fdist_Qinv" p'gsl_cdf_fdist_Qinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_beta_P" c'gsl_cdf_beta_P
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_beta_P" p'gsl_cdf_beta_P
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_beta_Q" c'gsl_cdf_beta_Q
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_beta_Q" p'gsl_cdf_beta_Q
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_beta_Pinv" c'gsl_cdf_beta_Pinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_beta_Pinv" p'gsl_cdf_beta_Pinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_beta_Qinv" c'gsl_cdf_beta_Qinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_beta_Qinv" p'gsl_cdf_beta_Qinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_flat_P" c'gsl_cdf_flat_P
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_flat_P" p'gsl_cdf_flat_P
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_flat_Q" c'gsl_cdf_flat_Q
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_flat_Q" p'gsl_cdf_flat_Q
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_flat_Pinv" c'gsl_cdf_flat_Pinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_flat_Pinv" p'gsl_cdf_flat_Pinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_flat_Qinv" c'gsl_cdf_flat_Qinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_flat_Qinv" p'gsl_cdf_flat_Qinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_lognormal_P" c'gsl_cdf_lognormal_P
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_lognormal_P" p'gsl_cdf_lognormal_P
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_lognormal_Q" c'gsl_cdf_lognormal_Q
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_lognormal_Q" p'gsl_cdf_lognormal_Q
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_lognormal_Pinv" c'gsl_cdf_lognormal_Pinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_lognormal_Pinv" p'gsl_cdf_lognormal_Pinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_lognormal_Qinv" c'gsl_cdf_lognormal_Qinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_lognormal_Qinv" p'gsl_cdf_lognormal_Qinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gumbel1_P" c'gsl_cdf_gumbel1_P
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gumbel1_P" p'gsl_cdf_gumbel1_P
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gumbel1_Q" c'gsl_cdf_gumbel1_Q
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gumbel1_Q" p'gsl_cdf_gumbel1_Q
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gumbel1_Pinv" c'gsl_cdf_gumbel1_Pinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gumbel1_Pinv" p'gsl_cdf_gumbel1_Pinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gumbel1_Qinv" c'gsl_cdf_gumbel1_Qinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gumbel1_Qinv" p'gsl_cdf_gumbel1_Qinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gumbel2_P" c'gsl_cdf_gumbel2_P
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gumbel2_P" p'gsl_cdf_gumbel2_P
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gumbel2_Q" c'gsl_cdf_gumbel2_Q
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gumbel2_Q" p'gsl_cdf_gumbel2_Q
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gumbel2_Pinv" c'gsl_cdf_gumbel2_Pinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gumbel2_Pinv" p'gsl_cdf_gumbel2_Pinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_gumbel2_Qinv" c'gsl_cdf_gumbel2_Qinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_gumbel2_Qinv" p'gsl_cdf_gumbel2_Qinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_weibull_P" c'gsl_cdf_weibull_P
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_weibull_P" p'gsl_cdf_weibull_P
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_weibull_Q" c'gsl_cdf_weibull_Q
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_weibull_Q" p'gsl_cdf_weibull_Q
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_weibull_Pinv" c'gsl_cdf_weibull_Pinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_weibull_Pinv" p'gsl_cdf_weibull_Pinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_weibull_Qinv" c'gsl_cdf_weibull_Qinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_weibull_Qinv" p'gsl_cdf_weibull_Qinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_pareto_P" c'gsl_cdf_pareto_P
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_pareto_P" p'gsl_cdf_pareto_P
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_pareto_Q" c'gsl_cdf_pareto_Q
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_pareto_Q" p'gsl_cdf_pareto_Q
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_pareto_Pinv" c'gsl_cdf_pareto_Pinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_pareto_Pinv" p'gsl_cdf_pareto_Pinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_pareto_Qinv" c'gsl_cdf_pareto_Qinv
:: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_pareto_Qinv" p'gsl_cdf_pareto_Qinv
:: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_logistic_P" c'gsl_cdf_logistic_P
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_logistic_P" p'gsl_cdf_logistic_P
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_logistic_Q" c'gsl_cdf_logistic_Q
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_logistic_Q" p'gsl_cdf_logistic_Q
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_logistic_Pinv" c'gsl_cdf_logistic_Pinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_logistic_Pinv" p'gsl_cdf_logistic_Pinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_logistic_Qinv" c'gsl_cdf_logistic_Qinv
:: CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_logistic_Qinv" p'gsl_cdf_logistic_Qinv
:: FunPtr (CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_binomial_P" c'gsl_cdf_binomial_P
:: CUInt -> CDouble -> CUInt -> IO CDouble
foreign import ccall "&gsl_cdf_binomial_P" p'gsl_cdf_binomial_P
:: FunPtr (CUInt -> CDouble -> CUInt -> IO CDouble)
foreign import ccall "gsl_cdf_binomial_Q" c'gsl_cdf_binomial_Q
:: CUInt -> CDouble -> CUInt -> IO CDouble
foreign import ccall "&gsl_cdf_binomial_Q" p'gsl_cdf_binomial_Q
:: FunPtr (CUInt -> CDouble -> CUInt -> IO CDouble)
foreign import ccall "gsl_cdf_poisson_P" c'gsl_cdf_poisson_P
:: CUInt -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_poisson_P" p'gsl_cdf_poisson_P
:: FunPtr (CUInt -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_poisson_Q" c'gsl_cdf_poisson_Q
:: CUInt -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_poisson_Q" p'gsl_cdf_poisson_Q
:: FunPtr (CUInt -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_geometric_P" c'gsl_cdf_geometric_P
:: CUInt -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_geometric_P" p'gsl_cdf_geometric_P
:: FunPtr (CUInt -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_geometric_Q" c'gsl_cdf_geometric_Q
:: CUInt -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_geometric_Q" p'gsl_cdf_geometric_Q
:: FunPtr (CUInt -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_negative_binomial_P" c'gsl_cdf_negative_binomial_P
:: CUInt -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_negative_binomial_P" p'gsl_cdf_negative_binomial_P
:: FunPtr (CUInt -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_negative_binomial_Q" c'gsl_cdf_negative_binomial_Q
:: CUInt -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&gsl_cdf_negative_binomial_Q" p'gsl_cdf_negative_binomial_Q
:: FunPtr (CUInt -> CDouble -> CDouble -> IO CDouble)
foreign import ccall "gsl_cdf_pascal_P" c'gsl_cdf_pascal_P
:: CUInt -> CDouble -> CUInt -> IO CDouble
foreign import ccall "&gsl_cdf_pascal_P" p'gsl_cdf_pascal_P
:: FunPtr (CUInt -> CDouble -> CUInt -> IO CDouble)
foreign import ccall "gsl_cdf_pascal_Q" c'gsl_cdf_pascal_Q
:: CUInt -> CDouble -> CUInt -> IO CDouble
foreign import ccall "&gsl_cdf_pascal_Q" p'gsl_cdf_pascal_Q
:: FunPtr (CUInt -> CDouble -> CUInt -> IO CDouble)
foreign import ccall "gsl_cdf_hypergeometric_P" c'gsl_cdf_hypergeometric_P
:: CUInt -> CUInt -> CUInt -> CUInt -> IO CDouble
foreign import ccall "&gsl_cdf_hypergeometric_P" p'gsl_cdf_hypergeometric_P
:: FunPtr (CUInt -> CUInt -> CUInt -> CUInt -> IO CDouble)
foreign import ccall "gsl_cdf_hypergeometric_Q" c'gsl_cdf_hypergeometric_Q
:: CUInt -> CUInt -> CUInt -> CUInt -> IO CDouble
foreign import ccall "&gsl_cdf_hypergeometric_Q" p'gsl_cdf_hypergeometric_Q
:: FunPtr (CUInt -> CUInt -> CUInt -> CUInt -> IO CDouble)