stats_distribution_exponential

统计分布 -- 指数分布模块

rvs_exp - 指数分布随机变量

状态

实验性

描述

指数分布是泊松点过程中事件之间时间间隔的分布。逆尺度参数lambda指定事件之间的平均时间间隔 (),也称为事件速率。

不带参数时,该函数返回标准指数分布的随机样本.

带一个参数时,该函数返回指数分布的随机样本. 对于复数参数,实部和虚部独立地进行采样。

带两个参数时,该函数返回一个包含指数分布随机变量的秩 1 数组。

注意

用于生成指数随机变量的算法本质上仅限于双精度。1

语法

result = rvs_exp ([lambda] [[, array_size]])

类别

元素函数

参数

lambda: 可选参数具有intent(in),是类型为realcomplex的标量。如果lambdareal,则其值必须为正数。如果lambdacomplex,则实部和虚部都必须为正数。

array_size: 可选参数具有intent(in),是类型为integer且具有默认种类的标量。

返回值

结果是一个标量或秩 1 数组,大小为array_size,与lambda类型相同。如果lambda为非正数,则结果为NaN

示例

program example_exponential_rvs
  use stdlib_random, only: random_seed
  use stdlib_stats_distribution_exponential, only: rexp => rvs_exp

  implicit none
  complex :: scale
  integer :: seed_put, seed_get

  seed_put = 1234567
  call random_seed(seed_put, seed_get)

  print *, rexp()         !single standard exponential random variate

! 0.358690143

  print *, rexp(2.0)       !exponential random variate with lambda=2.0

! 0.816459715

  print *, rexp(0.3, 10)   !an array of 10 variates with lambda=0.3

!  1.84008647E-02  3.59742008E-02  0.136567295  0.262772143  3.62352766E-02
!  0.547133625  0.213591918  4.10784185E-02  0.583882213  0.671128035

  scale = (2.0, 0.7)
  print *, rexp(scale)
!single complex exponential random variate with real part of lambda=2.0;
!imagainary part of lambda=0.7

! (1.41435969,4.081114382E-02)

end program example_exponential_rvs

pdf_exp - 指数分布概率密度函数

状态

实验性

描述

单个实变量指数分布的概率密度函数 (pdf) 为

对于复数变量其中实部独立于虚部和虚部部分,联合概率密度函数是对应实部和虚部边际 pdf 的乘积:2

语法

result = pdf_exp (x, lambda)

类别

元素函数

参数

x: 具有intent(in),是类型为realcomplex的标量。

lambda: 具有intent(in),是类型为realcomplex的标量。如果lambdareal,则其值必须为正数。如果lambdacomplex,则实部和虚部都必须为正数。

所有参数必须具有相同的类型。

返回值

结果是一个标量或数组,形状与参数一致,与输入参数类型相同。如果lambda为非正数,则结果为NaN

示例

program example_exponential_pdf
  use stdlib_random, only: random_seed
  use stdlib_stats_distribution_exponential, only: exp_pdf => pdf_exp, &
                                                    rexp => rvs_exp

  implicit none
  real, dimension(2, 3, 4) :: x, lambda
  real :: xsum
  complex :: scale
  integer :: seed_put, seed_get, i

  seed_put = 1234567
  call random_seed(seed_put, seed_get)

  ! probability density at x=1.0 in standard exponential
  print *, exp_pdf(1.0, 1.0)
  ! 0.367879450

  ! probability density at x=2.0 with lambda=2.0
  print *, exp_pdf(2.0, 2.0) 
  ! 3.66312787E-02

  ! probability density at x=2.0 with lambda=-1.0 (out of range)
  print *, exp_pdf(2.0, -1.0) 
  ! NaN

  ! standard exponential random variates array  
  x = reshape(rexp(0.5, 24), [2, 3, 4])

  ! a rank-3 exponential probability density
  lambda(:, :, :) = 0.5
  print *, exp_pdf(x, lambda)
  ! 0.349295378      0.332413018     0.470253497     0.443498343      0.317152828
  ! 0.208242029      0.443112582     8.07073265E-02  0.245337561      0.436016470
  ! 7.14025944E-02   5.33841923E-02  0.322308093     0.264558554      0.212898195
  ! 0.100339092      0.226891592     0.444002301     9.91026312E-02   3.87373678E-02
  ! 3.11400592E-02   0.349431813     0.482774824     0.432669312     

  ! probability density array where lambda<=0.0 for certain elements 
  print *, exp_pdf([1.0, 1.0, 1.0], [1.0, 0.0, -1.0])
  ! 0.367879450  NaN NaN

  ! `pdf_exp` is pure and, thus, can be called concurrently 
  xsum = 0.0
  do concurrent (i=1:size(x,3))
    xsum = xsum + sum(exp_pdf(x(:,:,i), lambda(:,:,i)))
  end do
  print *, xsum
  ! 6.45566940

  ! complex exponential probability density function at (1.5,1.0) with real part
  ! of lambda=1.0 and imaginary part of lambda=2.0
  scale = (1.0, 2.)
  print *, exp_pdf((1.5, 1.0), scale)
  ! 6.03947677E-02

  ! As above, but with lambda%re < 0 
  scale = (-1.0, 2.)
  print *, exp_pdf((1.5, 1.0), scale)
  ! NaN

end program example_exponential_pdf

cdf_exp - 指数分布累积分布函数

状态

实验性

描述

单个实变量指数分布的累积分布函数 (cdf)

对于复数变量其中实部独立于虚部和虚部部分,联合累积分布函数是对应实部和虚部边际 cdf 的乘积:2

语法

result = cdf_exp (x, lambda)

类别

元素函数

参数

x: 具有intent(in),是类型为realcomplex的标量。

lambda: 具有intent(in),是类型为realcomplex的标量。如果lambdareal,则其值必须为正数。如果lambdacomplex,则实部和虚部都必须为正数。

所有参数必须具有相同的类型。

返回值

结果是一个标量或数组,形状与参数一致,与输入参数类型相同。如果lambda为非正数,则结果为NaN

示例

program example_exponential_cdf
  use stdlib_random, only: random_seed
  use stdlib_stats_distribution_exponential, only: exp_cdf => cdf_exp, &
                                                   rexp => rvs_exp

  implicit none
  real, dimension(2, 3, 4) :: x, lambda
  real :: xsum
  complex :: scale
  integer :: seed_put, seed_get, i

  seed_put = 1234567
  call random_seed(seed_put, seed_get)

  ! standard exponential cumulative distribution at x=1.0
  print *, exp_cdf(1.0, 1.0)
  ! 0.632120550

  ! cumulative distribution at x=2.0 with lambda=2
  print *, exp_cdf(2.0, 2.0)
  ! 0.981684387

  ! cumulative distribution at x=2.0 with lambda=-1.0 (out of range)
  print *, exp_cdf(2.0, -1.0) 
  ! NaN

   ! standard exponential random variates array
  x = reshape(rexp(0.5, 24), [2, 3, 4])

  ! a rank-3 exponential cumulative distribution
  lambda(:, :, :) = 0.5
  print *, exp_cdf(x, lambda)
  ! 0.301409245  0.335173965  5.94930053E-02  0.113003314
  ! 0.365694344  0.583515942  0.113774836     0.838585377
  ! 0.509324908  0.127967060  0.857194781     0.893231630
  ! 0.355383813  0.470882893  0.574203610     0.799321830
  ! 0.546216846  0.111995399  0.801794767     0.922525287
  ! 0.937719882  0.301136374  3.44503522E-02  0.134661376 

  ! cumulative distribution array where lambda<=0.0 for certain elements 
  print *, exp_cdf([1.0, 1.0, 1.0], [1.0, 0.0, -1.0])
  ! 0.632120550  NaN NaN

  ! `cdf_exp` is pure and, thus, can be called concurrently 
  xsum = 0.0
  do concurrent (i=1:size(x,3))
    xsum = xsum + sum(exp_cdf(x(:,:,i), lambda(:,:,i)))
  end do
  print *, xsum
  ! 11.0886612

  ! complex exponential cumulative distribution at (0.5,0.5) with real part of
  ! lambda=0.5 and imaginary part of lambda=1.0
  scale = (0.5, 1.0)
  print *, exp_cdf((0.5, 0.5), scale)
  ! 8.70351046E-02

  ! As above, but with lambda%im < 0 
  scale = (1.0, -2.0)
  print *, exp_cdf((1.5, 1.0), scale)
  ! NaN

end program example_exponential_cdf

  1. Marsaglia, George, and Wai Wan Tsang. "The ziggurat method for generating random variables." Journal of statistical software 5 (2000): 1-7. 

  2. Miller, Scott, and Donald Childers. Probability and random processes: With applications to signal processing and communications. Academic Press, 2012 (p. 197).