stats_distribution_uniform

统计分布 -- 均匀分布模块

shuffle - 使用 Fisher-Yates 算法生成列表的随机排列

状态

实验性

描述

应用 Fisher-Yates 算法为任何内建数值数据类型的列表生成无偏排列。

语法

result = shuffle ( list )

类别

函数。

参数

list: 参数具有 intent(in) 属性,并且是一维数组,数据类型为 integerrealcomplex

返回值

返回一个输入类型的随机化一维数组。

示例

program example_shuffle
  use stdlib_random, only: random_seed
  use stdlib_stats_distribution_uniform, only: shuffle
  implicit none
  integer :: seed_put, seed_get, i
  real :: x(10)
  integer :: n(10)
  complex :: z(10)

  do i = 1, 10
    n(i) = i
    x(i) = real(i)
    z(i) = cmplx(real(i), real(i))
  end do
  seed_put = 32165498
  call random_seed(seed_put, seed_get)    ! set and get current value of seed
  print *, shuffle(n)                          ! get randomized n

!10   6   9   2   8   1   3   5   7   4

  print *, shuffle(x)                          ! get randomized x

!5.0   10.0   9.0   4.0   3.0   8.0   2.0   1.0   7.0   6.0

  print *, shuffle(z)                          ! get randomized z

!(8.0, 8.0)    (7.0, 7.0)    (4.0, 4.0)    (1.0, 1.0)    (5.0, 5.0)
!(9.0, 9.0)    (6.0, 6.0)    (3.0, 3.0)    (2.0, 2.0)    (10.0, 10.0)

end program example_shuffle

rvs_uniform - 均匀分布随机变量

状态

实验性

描述

无参数时,函数返回一个标量标准均匀分布变量 U(0,1),数据类型为 real,在 [0,1] 上具有单精度。

带单个参数 scale(数据类型为 integer)时,函数返回一个标量均匀分布变量,数据类型为 integer,在 [0,scale] 上。这是标准的矩形分布。

带单个参数 scale(数据类型为 realcomplex)时,函数返回一个标量均匀分布变量,数据类型为 real,在 [0, scale] 上,或数据类型为 complex,在 [(0, 0i), (scale, i(scale))] 上。

带双参数 locscale 时,函数返回一个标量均匀分布随机变量,数据类型为 integerreal,在 [loc, loc + scale] 上,或数据类型为 complex,在 [(loc, i(loc)), ((loc + scale), i(loc + scale))] 上,取决于输入类型。

带三参数 locscalearray_size 时,函数返回一个一维数组,包含均匀分布变量,数据类型为 integerrealcomplex,数组大小为 array_size

对于 complex 类型,实部和虚部相互独立。

注意:用于生成均匀随机变量的算法从根本上受限于双精度。

语法

result = rvs_uniform ([[loc,] scale] [[[,array_size]]])

类别

基本函数(不带第三个参数)。

参数

loc: 可选参数具有 intent(in) 属性,并且是标量,数据类型为 integerrealcomplex

scale: 可选参数具有 intent(in) 属性,并且是标量,数据类型为 integerrealcomplex

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

locscale 都存在时,它们必须具有相同的类型和种类。

返回值

结果是一个标量或一个一维数组,大小为 array_size,数据类型为 integerrealcomplex,取决于输入类型。

示例

program example_uniform_rvs
  use stdlib_random, only: random_seed
  use stdlib_stats_distribution_uniform, only: uni => rvs_uniform

  implicit none
  complex :: loc, scale
  real :: a(3, 4, 5), b(3, 4, 5)
  integer :: seed_put, seed_get

  seed_put = 1234567
  call random_seed(seed_put, seed_get)

  print *, uni()           !real standard uniform random variate in [0., 1.]
! 0.161520019

  print *, uni(3.0)         !an uniform random variate in [0., 3.]
! 1.65974522

  print *, uni(-0.5, 1.0)   !an uniform random variate in [-0.5, 0.5]
! 0.486900032

  print *, uni(-1.0, 2.0, 10)
!an array of 10 uniform random variates in [-1., 1.]

!0.884182811  -0.771520197  0.560377002  0.709313750  -7.12267756E-02
!-0.431066573  0.497536063  -0.396331906  -0.325983286  0.137686729

  print *, uni(20)          !a random integer variate in [0, 20]
! 17

  print *, uni(5, 13)        !a random integer variate in [5, 18]
! 15

  print *, uni(3, 19, 10)     !an array of 10 integer variates in [3,22]

!7  16  16  12  9  21  19  4  3  19

  loc = (-0.5, -0.5)
  scale = (1.0, 1.0)

  print *, uni(scale)       !a complex uniform random variate in unit square

!(0.139202669, 0.361759573)

  print *, uni(loc, scale)
!a complex uniform random variate in [(-0.5, -0.5), (0.5, 0.5)]

!(0.296536088,-0.143987954)

  print *, uni(loc, scale, 10)
!an array of 10 complex uniform random variate in [(-0.5, -0.5), (0.5, 0.5)]

!(-0.302334785,-0.401923567)    (0.281620383,9.534919262E-02)
! (-0.374348879,0.457528770)     (0.442990601,-0.240510434)
! (-0.421572685,0.279313922)     (-0.182090610,5.901372433E-02)
! (-7.864198089E-02,0.378484428)    (-0.423258364,-0.201292425)
! (0.193327367,-0.353985727)    (-0.397661150,0.355926156)

  a(:, :, :) = -0.5
  b(:, :, :) = 1.0

  print *, uni(a, b)
!a rank 3 array of random variates in [-0.5,0.5]

! -0.249188632   -0.199248433   -0.389813602   2.88307667E-03   0.238479793,
!  0.264856219   -0.205177426   -0.480921626   0.131218433   0.252170086,
! -0.303151041   -8.89462233E-02   -0.377370685   0.341802299   0.323204756,
! 0.358679056   -0.138909757   0.384329498   -0.109372199   0.132353067,
! 0.494320452   0.419343710   -0.103044361   0.461389005   0.403132677
! 0.121850729   0.403839290   -0.349389791   0.490482628   0.156600773
! 8.46788883E-02   -0.483680278   0.388107836   0.119698405   0.154214382
! 0.153113484   0.236523747   0.155937552   -0.135760903   0.219589531
! 0.394639254   6.30156994E-02   -0.342692465   -0.444846451   -0.215700030
! 0.204189956   -0.208748132   0.355063021   8.98272395E-02   -0.237928331
! 2.98077464E-02   -0.485149682   -8.06870461E-02   -0.372713923
! -0.178335011   0.283877611   -2.13934183E-02   -9.21690464E-03
! 4.56320047E-02   0.220112979

end program example_uniform_rvs

pdf_uniform - 均匀分布概率密度函数

状态

实验性

描述

均匀分布的概率密度函数

f(x) = 0 x < loc 或 x > loc + scale,适用于所有类型的均匀分布

对于随机变量 x 在 [loc, loc + scale] 中

f(x) = 1 / (scale + 1); 对于离散均匀分布。

f(x) = 1 / scale; 对于连续均匀分布。

f(x) = 1 / (scale%re * scale%im); 对于复数均匀分布。

语法

result = pdf_uniform (x, loc, scale)

类别

基本函数。

参数

x: 具有 intent(in) 属性,并且是标量,数据类型为 integerrealcomplex

loc: 具有 intent(in) 属性,并且是标量,数据类型为 integerrealcomplex

scale: 具有 intent(in) 属性,并且是标量,数据类型为 integerrealcomplex

所有三个参数必须具有相同的类型和种类。

返回值

结果是一个标量或数组,其形状与参数一致,数据类型为 real

示例

program example_uniform_pdf
  use stdlib_random, only: random_seed
  use stdlib_stats_distribution_uniform, only: uni_pdf => pdf_uniform, &
                                               uni => rvs_uniform

  implicit none
  complex :: loc, scale
  real :: a(3, 4, 5), b(3, 4, 5), x(3, 4, 5)
  integer :: seed_put, seed_get

  seed_put = 1234567
  call random_seed(seed_put, seed_get)

  print *, uni_pdf(3, 2, 10)       !probability density at 3 in range [2, 10]

! 9.09090936E-02

  print *, uni_pdf(0.5, 0.0, 1.0)    !a probability density at 0.5 in [0., 1.]

! 1.00000000

  print *, uni_pdf(0.7, -1.0, 2.0)   !a probability density at 0.7 in [-1., 1.]

! 0.500000000

  a(:, :, :) = 0.0
  b(:, :, :) = 2.0
  x = reshape(uni(0., 2., 60), [3, 4, 5])! uniform random variates array in [0., 2.]
  print *, uni_pdf(x, a, b)         ! probability density array in [0., 2.]

! 0.500000000  0.500000000  0.500000000  0.500000000  0.500000000  0.500000000
! 0.500000000  0.500000000  0.500000000  0.500000000  0.500000000  0.500000000
! 0.500000000  0.500000000  0.500000000  0.500000000  0.500000000  0.500000000
! 0.500000000  0.500000000  0.500000000  0.500000000  0.500000000  0.500000000
! 0.500000000  0.500000000  0.500000000  0.500000000  0.500000000  0.500000000
! 0.500000000  0.500000000  0.500000000  0.500000000  0.500000000  0.500000000
! 0.500000000  0.500000000  0.500000000  0.500000000  0.500000000  0.500000000
! 0.500000000  0.500000000  0.500000000  0.500000000  0.500000000  0.500000000
! 0.500000000  0.500000000  0.500000000  0.500000000  0.500000000  0.500000000
! 0.500000000  0.500000000  0.500000000  0.500000000  0.500000000  0.500000000

  loc = (-0.5, -0.5)
  scale = (1.0, 1.0)
  print *, uni_pdf((-0.1, 0.2), loc, scale)
! joint probability density at (-0.1,0.2) in [(-0.5, -0.5), (0.5, 0.5)]

! 1.00000000
end program example_uniform_pdf

cdf_uniform - 均匀分布累积分布函数

状态

实验性

描述

均匀分布的累积分布函数

F(x) = 0 x < loc,适用于所有类型的均匀分布

F(x) = 1 x > loc + scale,适用于所有类型的均匀分布

对于随机变量 x 在 [loc, loc + scale] 中

F(x) = (x - loc + 1) / (scale + 1); 对于离散均匀分布。

F(x) = (x - loc) / scale; 对于连续均匀分布。

F(x) = (x%re - loc%re)(x%im - loc%im) / (scale%re * scale%im); 对于复数均匀分布。

语法

result = cdf_uniform (x, loc, scale)

类别

基本函数。

参数

x: 具有 intent(in) 属性,并且是标量,数据类型为 integerrealcomplex

loc: 具有 intent(in) 属性,并且是标量,数据类型为 integerrealcomplex

scale: 具有 intent(in) 属性,并且是标量,数据类型为 integerrealcomplex

所有三个参数必须具有相同的类型和种类。

返回值

结果是一个标量或数组,其形状与参数一致,数据类型为 real

示例

program example_uniform_cdf
  use stdlib_random, only: random_seed
  use stdlib_stats_distribution_uniform, only: uni_cdf => cdf_uniform, &
                                               uni => rvs_uniform

  implicit none
  real :: x(3, 4, 5), a(3, 4, 5), b(3, 4, 5)
  complex :: loc, scale
  integer :: seed_put, seed_get

  seed_put = 1234567
  call random_seed(seed_put, seed_get)

  print *, uni_cdf(0.5, 0., 1.)      ! a cumulative at 0.5 in [0., 1.]

!0.500000000

  print *, uni_cdf(0.7, -1.0, 2.0)   ! a cumulative at 0.7 in [-1.0, 1.0]

! 0.850000024

  print *, uni_cdf(6, 2, 10)       ! a cumulative at 6 in [2, 10]

! 0.454545468

  a(:, :, :) = -1.0
  b(:, :, :) = 2.0
  x = reshape(uni(-1.0, 2.0, 60), [3, 4, 5]) ! uniform random variates array
  print *, uni_cdf(x, a, b)        ! cumulative array in [-1.0, 1.0]

!0.161520004  0.553248405  0.986900032  0.942091405  0.114239901  0.780188501
! 0.854656875  0.464386612  0.284466714  0.748768032  0.301834047  0.337008357
!0.568843365  0.596165061  0.180993259  0.614166319  0.214835495 7.98164606E-02
!0.641274095  0.607101977  0.701139212  0.230517209  1.97925568E-02 0.857982159
!0.712761045  0.139202654  0.361759573  0.796536088  0.356012046  0.197665215
!9.80764329E-02 0.781620383  0.595349193  0.125651121  0.957528770  0.942990601
!0.259489566  7.84273148E-02  0.779313922  0.317909390  0.559013724 0.421358019
!0.878484428  7.67416358E-02  0.298707575  0.693327367  0.146014273 0.102338850
!0.855926156  0.250811368  0.300751567  0.110186398  0.502883077  0.738479793
!0.764856219  0.294822574  1.90783739E-02 0.631218433 0.752170086  0.196848959

  loc = (0., 0.)
  scale = (2., 1.)
  print *, uni_cdf((1.2, 0.5), loc, scale)
! joint cumulative distribution at (1.2,0.5) in [(0.,0.), (2.,1.)]

! 0.300000012
end program example_uniform_cdf