Skip to content

Commit e7f423a

Browse files
Probability Distribution and Statistical Functions -- Uniform Distribution Module (fortran-lang#593)
* add pdf/cdf with corresponding precisions * correction for kinds * add description of variable loc for pdf/cdf
1 parent d58f77d commit e7f423a

File tree

3 files changed

+108
-51
lines changed

3 files changed

+108
-51
lines changed

doc/specs/stdlib_stats_distribution_uniform.md

+24-12
Original file line numberDiff line numberDiff line change
@@ -36,7 +36,7 @@ Return a randomized rank one array of the input type.
3636

3737
```fortran
3838
program demo_shuffle
39-
use stdlib_stats_distribution_PRNG, only : random_seed
39+
use stdlib_random, only : random_seed
4040
use stdlib_stats_distribution_uniform, only : shuffle
4141
implicit none
4242
integer :: seed_put, seed_get, i
@@ -79,14 +79,16 @@ Without argument the function returns a scalar standard uniformly distributed va
7979

8080
With single argument `scale` of `integer` type the function returns a scalar uniformly distributed variate of `integer` type on [0,scale]. This is the standard Rectangular distribution.
8181

82-
With single argument `scale` of `real` or `complex` type the function returns a scalar uniformly distributed variate of `real` or `complex` type on [0, scale].
82+
With single argument `scale` of `real` or `complex` type the function returns a scalar uniformly distributed variate of `real` type on [0, scale] or `complex` type on [(0, 0i), (scale, i(scale))].
8383

84-
With double arguments `loc` and `scale` the function returns a scalar uniformly distributed random variates of `integer`, `real` or `complex` type on [loc, loc + scale] dependent of input type.
84+
With double arguments `loc` and `scale` the function returns a scalar uniformly distributed random variates of `integer` or `real` type on [loc, loc + scale], or `complex` type on [(loc, i(loc)), ((loc + scale), i(loc + scale))], dependent of input type.
8585

8686
With triple arguments `loc`, `scale` and `array_size` the function returns a rank one array of uniformly distributed variates of `integer`, `real` or `complex` type with an array size of `array_size`.
8787

8888
For `complex` type, the real part and imaginary part are independent of each other.
8989

90+
Note: the algorithm used for generating uniform random variates is fundamentally limited to double precision.
91+
9092
### Syntax
9193

9294
`result = [[stdlib_stats_distribution_uniform(module):rvs_uniform(interface)]]([[loc,] scale] [[[,array_size]]])`
@@ -101,19 +103,19 @@ Elemental function (without the third argument).
101103

102104
`scale`: optional argument has `intent(in)` and is a scalar of type `integer`, `real` or `complex`.
103105

104-
`array_size`: optional argument has `intent(in)` and is a scalar of type `integer`.
106+
`array_size`: optional argument has `intent(in)` and is a scalar of type `integer` with default kind.
105107

106108
`loc` and `scale` must have the same type and kind when both are present.
107109

108110
### Return value
109111

110-
The result is a scalar or a rank one array, with size of `array_size`, of type `integer`, `real` or `complex` depending on the input type.
112+
The result is a scalar or a rank one array with size of `array_size`, of type `integer`, `real` or `complex` depending on the input type.
111113

112114
### Example
113115

114116
```fortran
115117
program demo_uniform_rvs
116-
use stdlib_stats_distribution_PRNG, only:random_seed
118+
use stdlib_random, only:random_seed
117119
use stdlib_stats_distribution_uniform, only:uni=> rvs_uniform
118120
119121
implicit none
@@ -193,15 +195,19 @@ program demo_uniform_rvs
193195
end program demo_uniform_rvs
194196
```
195197

196-
## `pdf_uniform` - Uniform probability density function
198+
## `pdf_uniform` - Uniform distribution probability density function
197199

198200
### Status
199201

200202
Experimental
201203

202204
### Description
203205

204-
The probability density function of the uniform distribution.
206+
The probability density function of the uniform distribution:
207+
208+
f(x) = 0 x < loc or x > loc + scale for all types uniform distributions
209+
210+
For random variable x in [loc, loc + scale]:
205211

206212
f(x) = 1 / (scale + 1); for discrete uniform distribution.
207213

@@ -235,7 +241,7 @@ The result is a scalar or an array, with a shape conformable to arguments, of ty
235241

236242
```fortran
237243
program demo_uniform_pdf
238-
use stdlib_stats_distribution_PRNG, only : random_seed
244+
use stdlib_random, only : random_seed
239245
use stdlib_stats_distribution_uniform, only : uni_pdf => pdf_uniform, &
240246
uni => rvs_uniform
241247
@@ -286,15 +292,21 @@ end program demo_uniform_pdf
286292
287293
```
288294

289-
## `cdf_uniform` - Uniform cumulative distribution function
295+
## `cdf_uniform` - Uniform distribution cumulative distribution function
290296

291297
### Status
292298

293299
Experimental
294300

295301
### Description
296302

297-
Cumulative distribution function of the uniform distribution
303+
Cumulative distribution function of the uniform distribution:
304+
305+
F(x) = 0 x < loc for all types uniform distributions
306+
307+
F(x) = 1 x > loc + scale for all types uniform distributions
308+
309+
For random variable x in [loc, loc + scale]:
298310

299311
F(x) = (x - loc + 1) / (scale + 1); for discrete uniform distribution.
300312

@@ -328,7 +340,7 @@ The result is a scalar or an array, with a shape conformable to arguments, of ty
328340

329341
```fortran
330342
program demo_uniform_cdf
331-
use stdlib_stats_distribution_PRNG, only : random_seed
343+
use stdlib_random, only : random_seed
332344
use stdlib_stats_distribution_uniform, only : uni_cdf => cdf_uniform, &
333345
uni => rvs_uniform
334346

src/stdlib_stats_distribution_uniform.fypp

+27-24
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@
22
#:set RC_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES
33
#:set ALL_KINDS_TYPES = INT_KINDS_TYPES + RC_KINDS_TYPES
44
module stdlib_stats_distribution_uniform
5-
use stdlib_kinds
5+
use stdlib_kinds, only : sp, dp, xdp, qp, int8, int16, int32, int64
66
use stdlib_error, only : error_stop
77
use stdlib_random, only : dist_rand
88

@@ -383,14 +383,15 @@ contains
383383
elemental function pdf_unif_${t1[0]}$${k1}$(x, loc, scale) result(res)
384384

385385
${t1}$, intent(in) :: x, loc, scale
386-
real :: res
386+
${t1}$ :: res
387+
${t1}$, parameter :: zero = 0.0_${k1}$, one = 1.0_${k1}$
387388

388-
if(scale == 0.0_${k1}$) then
389-
res = 0.0
389+
if(scale == zero) then
390+
res = zero
390391
else if(x < loc .or. x > (loc + scale)) then
391-
res = 0.0
392+
res = zero
392393
else
393-
res = 1.0 / scale
394+
res = one / scale
394395
end if
395396
end function pdf_unif_${t1[0]}$${k1}$
396397

@@ -402,17 +403,17 @@ contains
402403
elemental function pdf_unif_${t1[0]}$${k1}$(x, loc, scale) result(res)
403404

404405
${t1}$, intent(in) :: x, loc, scale
405-
real :: res
406-
real(${k1}$) :: tr, ti
406+
real(${k1}$) :: res, tr, ti
407+
real(${k1}$), parameter :: zero = 0.0_${k1}$, one = 1.0_${k1}$
407408

408409
tr = loc % re + scale % re; ti = loc % im + scale % im
409-
if(scale == (0.0_${k1}$,0.0_${k1}$)) then
410-
res = 0.0
410+
if(scale == (zero, zero)) then
411+
res = zero
411412
else if((x % re >= loc % re .and. x % re <= tr) .and. &
412413
(x % im >= loc % im .and. x % im <= ti)) then
413-
res = 1.0 / (scale % re * scale % im)
414+
res = one / (scale % re * scale % im)
414415
else
415-
res = 0.0
416+
res = zero
416417
end if
417418
end function pdf_unif_${t1[0]}$${k1}$
418419

@@ -445,16 +446,17 @@ contains
445446
elemental function cdf_unif_${t1[0]}$${k1}$(x, loc, scale) result(res)
446447

447448
${t1}$, intent(in) :: x, loc, scale
448-
real :: res
449+
${t1}$ :: res
450+
${t1}$, parameter :: zero = 0.0_${k1}$, one = 1.0_${k1}$
449451

450-
if(scale == 0.0_${k1}$) then
451-
res = 0.0
452+
if(scale == zero) then
453+
res = zero
452454
else if(x < loc) then
453-
res = 0.0
455+
res = zero
454456
else if(x >= loc .and. x <= (loc + scale)) then
455457
res = (x - loc) / scale
456458
else
457-
res = 1.0
459+
res = one
458460
end if
459461
end function cdf_unif_${t1[0]}$${k1}$
460462

@@ -466,29 +468,30 @@ contains
466468
elemental function cdf_unif_${t1[0]}$${k1}$(x, loc, scale) result(res)
467469

468470
${t1}$, intent(in) :: x, loc, scale
469-
real :: res
471+
real(${k1}$) :: res
472+
real(${k1}$), parameter :: zero = 0.0_${k1}$, one = 1.0_${k1}$
470473
logical :: r1, r2, i1, i2
471474

472-
if(scale == (0.0_${k1}$,0.0_${k1}$)) then
473-
res = 0.0
475+
if(scale == (zero, zero)) then
476+
res = zero
474477
return
475478
end if
476479
r1 = x % re < loc % re
477480
r2 = x % re > (loc % re + scale % re)
478481
i1 = x % im < loc % im
479482
i2 = x % im > (loc % im + scale % im)
480483
if(r1 .or. i1) then
481-
res = 0.0
484+
res = zero
482485
else if((.not. r1) .and. (.not. r2) .and. i2) then
483486
res = (x % re - loc % re) / scale % re
484487
else if((.not. i1) .and. (.not. i2) .and. r2) then
485488
res = (x % im - loc % im) / scale % im
486489
else if((.not. r1) .and. (.not. r2) .and. (.not. i1) .and. (.not. i2)) &
487490
then
488-
res = (x % re - loc % re) * (x % im - loc % im) / &
489-
(scale % re * scale % im)
491+
res = ((x % re - loc % re) / scale % re) * ((x % im - loc % im) / &
492+
scale % im)
490493
else if(r2 .and. i2)then
491-
res = 1.0
494+
res = one
492495
end if
493496
end function cdf_unif_${t1[0]}$${k1}$
494497

src/tests/stats/test_distribution_uniform.fypp

+57-15
Original file line numberDiff line numberDiff line change
@@ -207,16 +207,18 @@ contains
207207
subroutine test_uni_pdf_${t1[0]}$${k1}$
208208
${t1}$ :: x1, x2(3,4), loc, scale
209209
integer :: seed, get, i
210-
real :: res(3,5)
211210
#:if t1[0] == "i"
212211
#! for integer type
212+
real :: res(3, 5)
213213
real, parameter :: ans(15) = [(1.96078438E-02, i=1,15)]
214214
#:elif t1[0] == "r"
215215
#! for real type
216-
real, parameter :: ans(15) = [(0.5, i=1,15)]
216+
${t1}$ :: res(3, 5)
217+
${t1}$, parameter :: ans(15) = [(0.5_${k1}$, i=1,15)]
217218
#:else
218219
#! for complex type
219-
real, parameter :: ans(15) = [(1.0, i=1,15)]
220+
real(${k1}$) :: res(3, 5)
221+
real(${k1}$), parameter :: ans(15) = [(1.0_${k1}$, i=1,15)]
220222
#:endif
221223

222224
print *, "Test pdf_uniform_${t1[0]}$${k1}$"
@@ -236,8 +238,15 @@ contains
236238
x2 = reshape(uni_rvs(loc, scale, 12), [3,4])
237239
res(:,1) = uni_pdf(x1, loc, scale)
238240
res(:, 2:5) = uni_pdf(x2, loc, scale)
241+
#:if t1[0] == "i"
242+
#! for integer type
239243
call check(all(abs(res - reshape(ans,[3,5])) < sptol), &
240244
msg = "pdf_uniform_${t1[0]}$${k1}$ failed", warn=warn)
245+
#:else
246+
#! for real and complex types
247+
call check(all(abs(res - reshape(ans,[3,5])) < ${k1}$tol), &
248+
msg = "pdf_uniform_${t1[0]}$${k1}$ failed", warn=warn)
249+
#:endif
241250
end subroutine test_uni_pdf_${t1[0]}$${k1}$
242251

243252
#:endfor
@@ -247,47 +256,73 @@ contains
247256
#:for k1, t1 in ALL_KINDS_TYPES
248257
subroutine test_uni_cdf_${t1[0]}$${k1}$
249258
${t1}$ :: x1, x2(3,4), loc, scale
250-
real :: res(3,5)
251259
integer :: seed, get
252260
#:if k1 == "int8"
261+
real :: res(3,5)
253262
real, parameter :: ans(15) = [0.435643554, 0.435643554, 0.435643554, &
254263
0.702970326, 0.653465331, 0.485148519, &
255264
0.386138618, 0.386138618, 0.336633652, &
256265
0.277227730, 0.237623766, 0.524752498, &
257266
0.732673287, 0.534653485, 0.415841579]
258267
#:elif k1 == "int16"
268+
real :: res(3,5)
259269
real, parameter :: ans(15) = [0.178217828, 0.178217828, 0.178217828, &
260270
0.465346545, 0.673267305, 0.247524753, &
261271
0.158415839, 0.792079210, 0.742574275, &
262272
0.574257433, 0.881188095, 0.663366318, &
263273
0.524752498, 0.623762369, 0.178217828]
264274
#:elif k1 == "int32"
275+
real :: res(3,5)
265276
real, parameter :: ans(15) = [0.732673287, 0.732673287, 0.732673287, &
266277
0.722772300, 0.792079210, 5.94059415E-02,&
267278
0.841584146, 0.405940592, 0.960396051, &
268279
0.534653485, 0.782178223, 0.861386120, &
269280
0.564356446, 0.613861382, 0.306930691]
270281
#:elif k1 == "int64"
282+
real :: res(3,5)
271283
real, parameter :: ans(15) = [0.455445558, 0.455445558, 0.455445558, &
272284
0.277227730, 0.455445558, 0.930693090, &
273285
0.851485133, 0.623762369, 5.94059415E-02,&
274286
0.693069279, 0.544554472, 0.207920790, &
275287
0.306930691, 0.356435657, 0.128712878]
276288
#:elif t1[0] == "r"
277289
#! for real type
278-
real, parameter :: ans(15) = [0.170192942, 0.170192942, 0.170192942, &
279-
0.276106149, 0.754930079, 0.406620681, &
280-
0.187742814, 0.651605546, 0.934733927, &
281-
0.151271492, 0.987674534, 0.130533904, &
282-
0.106271908, 9.27578658E-02, 0.203399420]
290+
${t1}$ :: res(3,5)
291+
${t1}$, parameter :: ans(15) = &
292+
[0.170192944297557408050991512027394492_${k1}$, &
293+
0.170192944297557408050991512027394492_${k1}$, &
294+
0.170192944297557408050991512027394492_${k1}$, &
295+
0.276106146274646191418611351764411665_${k1}$, &
296+
0.754930097473875072466853453079238534_${k1}$, &
297+
0.406620682573118008562573777453508228_${k1}$, &
298+
0.187742819191801080247472555129206739_${k1}$, &
299+
0.651605526090507591874256831943057477_${k1}$, &
300+
0.934733949732104885121941606485052034_${k1}$, &
301+
0.151271491851613287815681019310432021_${k1}$, &
302+
0.987674522797719611766353864368284121_${k1}$, &
303+
0.130533899463404684526679488953959662_${k1}$, &
304+
0.106271905921876880229959283497009892_${k1}$, &
305+
9.27578652240113182836367400341259781E-0002_${k1}$, &
306+
0.203399426853420439709196898547816090_${k1}$]
283307
#:else
284308
#! for complex type
285-
real, parameter :: ans(15) = [4.69913185E-02, 4.69913185E-02, &
286-
4.69913185E-02, 0.306970179, 0.122334257,&
287-
0.141398594, 0.128925011, 9.85755492E-03,&
288-
8.16527531E-02, 0.163921610, &
289-
7.81712309E-02, 0.446415812, &
290-
5.31753292E-04, 0.101455867, 0.155276477]
309+
real(${k1}$) :: res(3,5)
310+
real(${k1}$), parameter :: ans(15) = &
311+
[4.69913179731340971083526490627998168E-0002_${k1}$, &
312+
4.69913179731340971083526490627998168E-0002_${k1}$, &
313+
4.69913179731340971083526490627998168E-0002_${k1}$, &
314+
0.306970191529817593217448363707416739_${k1}$, &
315+
0.122334258469188588238756489506609443_${k1}$, &
316+
0.141398599060326408705075175176932616_${k1}$, &
317+
0.128925006861443729884744412460848140_${k1}$, &
318+
9.85755512660026594506599410104817938E-0003_${k1}$, &
319+
8.16527497645585445208592050401597260E-0002_${k1}$, &
320+
0.163921605454974749736935624944263178_${k1}$, &
321+
7.81712317416218284294000447064256003E-0002_${k1}$, &
322+
0.446415807686727375005224206895756087_${k1}$, &
323+
5.31753272901435018841591264266743165E-0004_${k1}$, &
324+
0.101455865191097416942685556683943046_${k1}$, &
325+
0.155276470981788516449112374966730510_${k1}$]
291326
#:endif
292327

293328
print *, "Test cdf_uniform_${t1[0]}$${k1}$"
@@ -307,8 +342,15 @@ contains
307342
x2 = reshape(uni_rvs(loc, scale, 12), [3,4])
308343
res(:,1) = uni_cdf(x1, loc, scale)
309344
res(:, 2:5) = uni_cdf(x2, loc, scale)
345+
#:if t1[0] == "i"
346+
#! for integer type
310347
call check(all(abs(res - reshape(ans,[3,5])) < sptol), &
311348
msg = "cdf_uniform_${t1[0]}$${k1}$ failed", warn=warn)
349+
#:else
350+
#! for real and complex types
351+
call check(all(abs(res - reshape(ans,[3,5])) < ${k1}$tol), &
352+
msg = "cdf_uniform_${t1[0]}$${k1}$ failed", warn=warn)
353+
#:endif
312354
end subroutine test_uni_cdf_${t1[0]}$${k1}$
313355

314356
#:endfor

0 commit comments

Comments
 (0)