@@ -17,6 +17,7 @@ module stdlib_stats_distribution_uniform
17
17
public :: uniform_distribution_cdf
18
18
public :: shuffle
19
19
20
+
20
21
interface uniform_distribution_rvs
21
22
!! Version experimental
22
23
!!
@@ -39,10 +40,12 @@ module stdlib_stats_distribution_uniform
39
40
#:endfor
40
41
end interface uniform_distribution_rvs
41
42
43
+
42
44
interface uniform_distribution_pdf
43
45
!! Version experiment
44
46
!!
45
- !! Get uniform distribution probability density (pdf) for integer, real and complex variables
47
+ !! Get uniform distribution probability density (pdf) for integer, real and
48
+ !! complex variables.
46
49
!! ([Specification](../page/specs/stdlib_stats_distribution_uniform.html#
47
50
!! description))
48
51
@@ -51,10 +54,12 @@ module stdlib_stats_distribution_uniform
51
54
#:endfor
52
55
end interface uniform_distribution_pdf
53
56
57
+
54
58
interface uniform_distribution_cdf
55
59
!! Version experimental
56
60
!!
57
- !! Get uniform distribution cumulative distribution function (cdf) for integer, real and complex variables
61
+ !! Get uniform distribution cumulative distribution function (cdf) for integer,
62
+ !! real and complex variables.
58
63
!! ([Specification](../page/specs/stdlib_stats_distribution_uniform.html#
59
64
!! description))
60
65
!!
@@ -63,10 +68,12 @@ module stdlib_stats_distribution_uniform
63
68
#:endfor
64
69
end interface uniform_distribution_cdf
65
70
71
+
66
72
interface shuffle
67
73
!! Version experimental
68
74
!!
69
- !! Fisher-Yates shuffle algorithm for a rank one array of integer, real and complex variables
75
+ !! Fisher-Yates shuffle algorithm for a rank one array of integer, real and
76
+ !! complex variables
70
77
!! ([Specification](../page/specs/stdlib_stats_distribution_uniform.html#
71
78
!! description))
72
79
!!
@@ -76,20 +83,25 @@ module stdlib_stats_distribution_uniform
76
83
end interface shuffle
77
84
78
85
79
- contains
86
+
87
+
88
+ contains
89
+
80
90
81
91
#:for k1, t1 in INT_KINDS_TYPES
82
92
impure elemental function unif_dist_rvs_1_${t1[0]}$${k1}$(scale) result(res)
93
+ !
83
94
! Uniformly distributed integer in [0, scale]
84
95
! Bitmask with rejection
85
96
! https://www.pcg-random.org/posts/bounded-rands.html
86
97
!
87
98
! Fortran 90 translated from c by Jim-215-fisher
99
+ !
88
100
${t1}$, intent(in) :: scale
89
101
${t1}$ :: res, u, mask
90
102
integer :: zeros, bits_left, bits
91
103
92
- if(scale <= 0_${k1}$) call error_stop("Error(unif_dist_rvs_1): Uniform" &
104
+ if(scale <= 0_${k1}$) call error_stop("Error(unif_dist_rvs_1): Uniform" &
93
105
//" distribution scale parameter must be positive")
94
106
zeros = leadz(scale)
95
107
bits = bit_size(scale) - zeros
@@ -111,9 +123,12 @@ module stdlib_stats_distribution_uniform
111
123
112
124
#:endfor
113
125
126
+
127
+
114
128
#:for k1, t1 in INT_KINDS_TYPES
115
129
impure elemental function unif_dist_rvs_${t1[0]}$${k1}$(loc, scale) &
116
- result( res )
130
+ result( res )
131
+ !
117
132
! Uniformly distributed integer in [loc, loc + scale]
118
133
!
119
134
${t1}$, intent(in) :: loc, scale
@@ -126,8 +141,11 @@ module stdlib_stats_distribution_uniform
126
141
127
142
#:endfor
128
143
144
+
145
+
129
146
#:for k1, t1 in REAL_KINDS_TYPES
130
147
impure elemental function unif_dist_rvs_0_${t1[0]}$${k1}$( ) result(res)
148
+ !
131
149
! Uniformly distributed float in [0,1]
132
150
! Based on the paper by Frederic Goualard, "Generating Random Floating-
133
151
! Point Numbers By Dividing Integers: a Case Study", Proceedings of
@@ -142,8 +160,11 @@ module stdlib_stats_distribution_uniform
142
160
143
161
#:endfor
144
162
163
+
164
+
145
165
#:for k1, t1 in REAL_KINDS_TYPES
146
166
impure elemental function unif_dist_rvs_1_${t1[0]}$${k1}$(scale) result(res)
167
+ !
147
168
! Uniformly distributed float in [0, scale]
148
169
!
149
170
${t1}$, intent(in) :: scale
@@ -156,9 +177,12 @@ module stdlib_stats_distribution_uniform
156
177
157
178
#:endfor
158
179
180
+
181
+
159
182
#:for k1, t1 in REAL_KINDS_TYPES
160
183
impure elemental function unif_dist_rvs_${t1[0]}$${k1}$(loc, scale) &
161
- result(res)
184
+ result(res)
185
+ !
162
186
! Uniformly distributed float in [loc, loc + scale]
163
187
!
164
188
${t1}$, intent(in) :: loc, scale
@@ -171,11 +195,14 @@ module stdlib_stats_distribution_uniform
171
195
172
196
#:endfor
173
197
198
+
199
+
174
200
#:for k1, t1 in CMPLX_KINDS_TYPES
175
201
impure elemental function unif_dist_rvs_1_${t1[0]}$${k1}$(scale) result(res)
176
- ! Uniformly distributed complex in [(0,0i), (scale, i(scale)]
202
+ !
203
+ ! Uniformly distributed complex in [(0,0i), (scale, i(scale))]
177
204
! The real part and imaginary part are independent of each other, so that
178
- ! the joint distribution is on an unit square [(0,0i), scale,i(scale)]
205
+ ! the joint distribution is on an unit square [(0,0i), ( scale,i(scale) )]
179
206
!
180
207
${t1}$, intent(in) :: scale
181
208
${t1}$ :: res
@@ -191,7 +218,7 @@ module stdlib_stats_distribution_uniform
191
218
tr = scale % re * r1
192
219
ti = 0.0_${k1}$
193
220
else
194
- tr = scale % re * r1
221
+ tr = scale % re * r1
195
222
r1 = unif_dist_rvs_0_r${k1}$( )
196
223
ti = scale % im * r1
197
224
endif
@@ -200,9 +227,12 @@ module stdlib_stats_distribution_uniform
200
227
201
228
#:endfor
202
229
230
+
231
+
203
232
#:for k1, t1 in CMPLX_KINDS_TYPES
204
233
impure elemental function unif_dist_rvs_${t1[0]}$${k1}$(loc, scale) &
205
- result(res)
234
+ result(res)
235
+ !
206
236
! Uniformly distributed complex in [(loc,iloc), (loc + scale, i(loc + scale))]
207
237
! The real part and imaginary part are independent of each other, so that
208
238
! the joint distribution is on an unit square [(loc,iloc), (loc + scale,
@@ -231,9 +261,12 @@ module stdlib_stats_distribution_uniform
231
261
232
262
#:endfor
233
263
264
+
265
+
234
266
#:for k1, t1 in INT_KINDS_TYPES
235
267
function unif_dist_rvs_array_${t1[0]}$${k1}$(loc, scale, array_size) &
236
- result(res)
268
+ result(res)
269
+
237
270
integer, intent(in) :: array_size
238
271
${t1}$, intent(in) :: loc, scale
239
272
${t1}$ :: res(array_size)
@@ -265,9 +298,12 @@ module stdlib_stats_distribution_uniform
265
298
266
299
#:endfor
267
300
301
+
302
+
268
303
#:for k1, t1 in REAL_KINDS_TYPES
269
304
function unif_dist_rvs_array_${t1[0]}$${k1}$(loc, scale, array_size) &
270
- result(res)
305
+ result(res)
306
+
271
307
integer, intent(in) :: array_size
272
308
${t1}$, intent(in) :: loc, scale
273
309
${t1}$ :: res(array_size)
@@ -287,9 +323,12 @@ module stdlib_stats_distribution_uniform
287
323
288
324
#:endfor
289
325
326
+
327
+
290
328
#:for k1, t1 in CMPLX_KINDS_TYPES
291
329
function unif_dist_rvs_array_${t1[0]}$${k1}$(loc, scale, array_size) &
292
- result(res)
330
+ result(res)
331
+
293
332
integer, intent(in) :: array_size
294
333
${t1}$, intent(in) :: loc, scale
295
334
${t1}$ :: res(array_size)
@@ -321,8 +360,11 @@ module stdlib_stats_distribution_uniform
321
360
322
361
#:endfor
323
362
363
+
364
+
324
365
#:for k1, t1 in INT_KINDS_TYPES
325
366
elemental function unif_dist_pdf_${t1[0]}$${k1}$(x, loc, scale) result(res)
367
+
326
368
${t1}$, intent(in) :: x, loc, scale
327
369
real :: res
328
370
@@ -337,8 +379,11 @@ module stdlib_stats_distribution_uniform
337
379
338
380
#:endfor
339
381
382
+
383
+
340
384
#:for k1, t1 in REAL_KINDS_TYPES
341
385
elemental function unif_dist_pdf_${t1[0]}$${k1}$(x, loc, scale) result(res)
386
+
342
387
${t1}$, intent(in) :: x, loc, scale
343
388
real :: res
344
389
@@ -353,8 +398,11 @@ module stdlib_stats_distribution_uniform
353
398
354
399
#:endfor
355
400
401
+
402
+
356
403
#:for k1, t1 in CMPLX_KINDS_TYPES
357
404
elemental function unif_dist_pdf_${t1[0]}$${k1}$(x, loc, scale) result(res)
405
+
358
406
${t1}$, intent(in) :: x, loc, scale
359
407
real :: res
360
408
real(${k1}$) :: tr, ti
@@ -372,8 +420,11 @@ module stdlib_stats_distribution_uniform
372
420
373
421
#:endfor
374
422
423
+
424
+
375
425
#:for k1, t1 in INT_KINDS_TYPES
376
426
elemental function unif_dist_cdf_${t1[0]}$${k1}$(x, loc, scale) result(res)
427
+
377
428
${t1}$, intent(in) :: x, loc, scale
378
429
real :: res
379
430
@@ -390,8 +441,11 @@ module stdlib_stats_distribution_uniform
390
441
391
442
#:endfor
392
443
444
+
445
+
393
446
#:for k1, t1 in REAL_KINDS_TYPES
394
447
elemental function unif_dist_cdf_${t1[0]}$${k1}$(x, loc, scale) result(res)
448
+
395
449
${t1}$, intent(in) :: x, loc, scale
396
450
real :: res
397
451
@@ -408,8 +462,11 @@ module stdlib_stats_distribution_uniform
408
462
409
463
#:endfor
410
464
465
+
466
+
411
467
#:for k1, t1 in CMPLX_KINDS_TYPES
412
468
elemental function unif_dist_cdf_${t1[0]}$${k1}$(x, loc, scale) result(res)
469
+
413
470
${t1}$, intent(in) :: x, loc, scale
414
471
real :: res
415
472
logical :: r1, r2, i1, i2
@@ -430,7 +487,7 @@ module stdlib_stats_distribution_uniform
430
487
res = (x % im - loc % im) / scale % im
431
488
elseif((.not. r1) .and. (.not. r2) .and. (.not. i1) .and. (.not. i2)) &
432
489
then
433
- res = (x % re - loc % re) * (x % im - loc % im) / &
490
+ res = (x % re - loc % re) * (x % im - loc % im) / &
434
491
(scale % re * scale % im)
435
492
elseif(r2 .and. i2)then
436
493
res = 1.0
@@ -439,8 +496,11 @@ module stdlib_stats_distribution_uniform
439
496
440
497
#:endfor
441
498
499
+
500
+
442
501
#:for k1, t1 in ALL_KINDS_TYPES
443
502
function shuffle_${t1[0]}$${k1}$( list ) result(res)
503
+
444
504
${t1}$, intent(in) :: list(:)
445
505
${t1}$ :: res(size(list))
446
506
${t1}$ :: tmp
0 commit comments