@@ -12,16 +12,17 @@ module stdlib_stats_distribution_uniform
12
12
real(dp), parameter :: MESENNE_NUMBER = 1.0_dp / (2.0_dp ** 53 - 1.0_dp)
13
13
integer(int64), parameter :: INT_ONE = 1_int64
14
14
15
- public :: uniform_distribution_rvs
16
- public :: uniform_distribution_pdf
17
- public :: uniform_distribution_cdf
15
+ public :: rvs_uniform
16
+ public :: pdf_uniform
17
+ public :: cdf_uniform
18
18
public :: shuffle
19
19
20
20
21
- interface uniform_distribution_rvs
21
+ interface rvs_uniform
22
22
!! Version experimental
23
23
!!
24
24
!! Get uniformly distributed random variate for integer, real and complex
25
+ !! variables.
25
26
!! ([Specification](../page/specs/stdlib_stats_distribution_uniform.html#
26
27
!! description))
27
28
@@ -38,11 +39,11 @@ module stdlib_stats_distribution_uniform
38
39
#:for k1, t1 in ALL_KINDS_TYPES
39
40
module procedure unif_dist_rvs_array_${t1[0]}$${k1}$ ! 3 dummy variables
40
41
#:endfor
41
- end interface uniform_distribution_rvs
42
+ end interface rvs_uniform
42
43
43
44
44
- interface uniform_distribution_pdf
45
- !! Version experiment
45
+ interface pdf_uniform
46
+ !! Version experimental
46
47
!!
47
48
!! Get uniform distribution probability density (pdf) for integer, real and
48
49
!! complex variables.
@@ -52,10 +53,10 @@ module stdlib_stats_distribution_uniform
52
53
#:for k1, t1 in ALL_KINDS_TYPES
53
54
module procedure unif_dist_pdf_${t1[0]}$${k1}$
54
55
#:endfor
55
- end interface uniform_distribution_pdf
56
+ end interface pdf_uniform
56
57
57
58
58
- interface uniform_distribution_cdf
59
+ interface cdf_uniform
59
60
!! Version experimental
60
61
!!
61
62
!! Get uniform distribution cumulative distribution function (cdf) for integer,
@@ -66,14 +67,14 @@ module stdlib_stats_distribution_uniform
66
67
#:for k1, t1 in ALL_KINDS_TYPES
67
68
module procedure unif_dist_cdf_${t1[0]}$${k1}$
68
69
#:endfor
69
- end interface uniform_distribution_cdf
70
+ end interface cdf_uniform
70
71
71
72
72
73
interface shuffle
73
74
!! Version experimental
74
75
!!
75
76
!! Fisher-Yates shuffle algorithm for a rank one array of integer, real and
76
- !! complex variables
77
+ !! complex variables.
77
78
!! ([Specification](../page/specs/stdlib_stats_distribution_uniform.html#
78
79
!! description))
79
80
!!
@@ -85,6 +86,8 @@ module stdlib_stats_distribution_uniform
85
86
86
87
87
88
89
+
90
+
88
91
contains
89
92
90
93
@@ -101,8 +104,8 @@ contains
101
104
${t1}$ :: res, u, mask
102
105
integer :: zeros, bits_left, bits
103
106
104
- if(scale <= 0_${k1}$) call error_stop("Error(unif_dist_rvs_1): Uniform" &
105
- //" distribution scale parameter must be positive")
107
+ if(scale <= 0_${k1}$) call error_stop("Error(unif_dist_rvs_1): Uniform"&
108
+ //" distribution scale parameter must be positive")
106
109
zeros = leadz(scale)
107
110
bits = bit_size(scale) - zeros
108
111
mask = shiftr(not(0_${k1}$), zeros)
@@ -126,16 +129,16 @@ contains
126
129
127
130
128
131
#:for k1, t1 in INT_KINDS_TYPES
129
- impure elemental function unif_dist_rvs_${t1[0]}$${k1}$(loc, scale) &
132
+ impure elemental function unif_dist_rvs_${t1[0]}$${k1}$(loc, scale) &
130
133
result( res )
131
134
!
132
135
! Uniformly distributed integer in [loc, loc + scale]
133
136
!
134
137
${t1}$, intent(in) :: loc, scale
135
138
${t1}$ :: res
136
139
137
- if(scale <= 0_${k1}$) call error_stop("Error(unif_dist_rvs): Uniform" &
138
- //" distribution scale parameter must be positive")
140
+ if(scale <= 0_${k1}$) call error_stop("Error(unif_dist_rvs): Uniform" &
141
+ //" distribution scale parameter must be positive")
139
142
res = loc + unif_dist_rvs_1_${t1[0]}$${k1}$(scale)
140
143
end function unif_dist_rvs_${t1[0]}$${k1}$
141
144
@@ -170,8 +173,8 @@ contains
170
173
${t1}$, intent(in) :: scale
171
174
${t1}$ :: res
172
175
173
- if(scale == 0._${k1}$) call error_stop("Error(unif_dist_rvs_1): " &
174
- //"Uniform distribution scale parameter must be non-zero")
176
+ if(scale == 0._${k1}$) call error_stop("Error(unif_dist_rvs_1): " &
177
+ //"Uniform distribution scale parameter must be non-zero")
175
178
res = scale * unif_dist_rvs_0_${t1[0]}$${k1}$( )
176
179
end function unif_dist_rvs_1_${t1[0]}$${k1}$
177
180
@@ -180,16 +183,16 @@ contains
180
183
181
184
182
185
#:for k1, t1 in REAL_KINDS_TYPES
183
- impure elemental function unif_dist_rvs_${t1[0]}$${k1}$(loc, scale) &
186
+ impure elemental function unif_dist_rvs_${t1[0]}$${k1}$(loc, scale) &
184
187
result(res)
185
188
!
186
189
! Uniformly distributed float in [loc, loc + scale]
187
190
!
188
191
${t1}$, intent(in) :: loc, scale
189
192
${t1}$ :: res
190
193
191
- if(scale == 0._${k1}$) call error_stop("Error(unif_dist_rvs): " &
192
- //"Uniform distribution scale parameter must be non-zero")
194
+ if(scale == 0._${k1}$) call error_stop("Error(unif_dist_rvs): " &
195
+ //"Uniform distribution scale parameter must be non-zero")
193
196
res = loc + scale * unif_dist_rvs_0_${t1[0]}$${k1}$( )
194
197
end function unif_dist_rvs_${t1[0]}$${k1}$
195
198
@@ -198,7 +201,8 @@ contains
198
201
199
202
200
203
#:for k1, t1 in CMPLX_KINDS_TYPES
201
- impure elemental function unif_dist_rvs_1_${t1[0]}$${k1}$(scale) result(res)
204
+ impure elemental function unif_dist_rvs_1_${t1[0]}$${k1}$(scale) &
205
+ result(res)
202
206
!
203
207
! Uniformly distributed complex in [(0,0i), (scale, i(scale))]
204
208
! The real part and imaginary part are independent of each other, so that
@@ -208,8 +212,8 @@ contains
208
212
${t1}$ :: res
209
213
real(${k1}$) :: r1, tr, ti
210
214
211
- if(scale == (0.0_${k1}$, 0.0_${k1}$)) call error_stop("Error(uni_dist_" &
212
- //"rvs_1): Uniform distribution scale parameter must be non-zero")
215
+ if(scale == (0.0_${k1}$, 0.0_${k1}$)) call error_stop("Error(uni_dist_"&
216
+ //"rvs_1): Uniform distribution scale parameter must be non-zero")
213
217
r1 = unif_dist_rvs_0_r${k1}$( )
214
218
if(scale % re == 0.0_${k1}$) then
215
219
ti = scale % im * r1
@@ -230,10 +234,11 @@ contains
230
234
231
235
232
236
#:for k1, t1 in CMPLX_KINDS_TYPES
233
- impure elemental function unif_dist_rvs_${t1[0]}$${k1}$(loc, scale) &
237
+ impure elemental function unif_dist_rvs_${t1[0]}$${k1}$(loc, scale) &
234
238
result(res)
235
239
!
236
- ! Uniformly distributed complex in [(loc,iloc), (loc + scale, i(loc + scale))]
240
+ ! Uniformly distributed complex in [(loc,iloc), (loc + scale, i(loc +
241
+ ! scale))].
237
242
! The real part and imaginary part are independent of each other, so that
238
243
! the joint distribution is on an unit square [(loc,iloc), (loc + scale,
239
244
! i(loc + scale))]
@@ -242,8 +247,8 @@ contains
242
247
${t1}$ :: res
243
248
real(${k1}$) :: r1, tr, ti
244
249
245
- if(scale == (0.0_${k1}$, 0.0_${k1}$)) call error_stop("Error(uni_dist_" &
246
- //"rvs): Uniform distribution scale parameter must be non-zero")
250
+ if(scale == (0.0_${k1}$, 0.0_${k1}$)) call error_stop("Error(uni_dist_"&
251
+ //"rvs): Uniform distribution scale parameter must be non-zero")
247
252
r1 = unif_dist_rvs_0_r${k1}$( )
248
253
if(scale % re == 0.0_${k1}$) then
249
254
tr = loc % re
@@ -264,7 +269,7 @@ contains
264
269
265
270
266
271
#:for k1, t1 in INT_KINDS_TYPES
267
- function unif_dist_rvs_array_${t1[0]}$${k1}$(loc, scale, array_size) &
272
+ function unif_dist_rvs_array_${t1[0]}$${k1}$(loc, scale, array_size) &
268
273
result(res)
269
274
270
275
integer, intent(in) :: array_size
@@ -273,8 +278,8 @@ contains
273
278
${t1}$ :: u, mask, nn
274
279
integer :: i, zeros, bits_left, bits
275
280
276
- if(scale == 0_${k1}$) call error_stop("Error(unif_dist_rvs_array): Uniform" &
277
- //" distribution scale parameter must be non-zero")
281
+ if(scale == 0_${k1}$) call error_stop("Error(unif_dist_rvs_array): " &
282
+ //"Uniform distribution scale parameter must be non-zero")
278
283
zeros = leadz(scale)
279
284
bits = bit_size(scale) - zeros
280
285
mask = shiftr(not(0_${k1}$), zeros)
@@ -301,7 +306,7 @@ contains
301
306
302
307
303
308
#:for k1, t1 in REAL_KINDS_TYPES
304
- function unif_dist_rvs_array_${t1[0]}$${k1}$(loc, scale, array_size) &
309
+ function unif_dist_rvs_array_${t1[0]}$${k1}$(loc, scale, array_size) &
305
310
result(res)
306
311
307
312
integer, intent(in) :: array_size
@@ -312,8 +317,8 @@ contains
312
317
integer :: i
313
318
314
319
315
- if(scale == 0._${k1}$) call error_stop("Error(unif_dist_rvs_array):" &
316
- //" Uniform distribution scale parameter must be non-zero")
320
+ if(scale == 0._${k1}$) call error_stop("Error(unif_dist_rvs_array):" &
321
+ //" Uniform distribution scale parameter must be non-zero")
317
322
do i = 1, array_size
318
323
tmp = shiftr(dist_rand(INT_ONE), 11)
319
324
t = real(tmp * MESENNE_NUMBER, kind = ${k1}$)
@@ -326,7 +331,7 @@ contains
326
331
327
332
328
333
#:for k1, t1 in CMPLX_KINDS_TYPES
329
- function unif_dist_rvs_array_${t1[0]}$${k1}$(loc, scale, array_size) &
334
+ function unif_dist_rvs_array_${t1[0]}$${k1}$(loc, scale, array_size) &
330
335
result(res)
331
336
332
337
integer, intent(in) :: array_size
@@ -337,8 +342,9 @@ contains
337
342
integer :: i
338
343
339
344
340
- if(scale == (0.0_${k1}$, 0.0_${k1}$)) call error_stop("Error(unif_dist_"&
341
- //"rvs_array): Uniform distribution scale parameter must be non-zero")
345
+ if(scale == (0.0_${k1}$, 0.0_${k1}$)) call error_stop("Error(unif_dist"&
346
+ //"_rvs_array): Uniform distribution scale parameter must be " &
347
+ //"non-zero")
342
348
do i = 1, array_size
343
349
tmp = shiftr(dist_rand(INT_ONE), 11)
344
350
r1 = real(tmp * MESENNE_NUMBER, kind = ${k1}$)
@@ -389,7 +395,7 @@ contains
389
395
390
396
if(scale == 0.0_${k1}$) then
391
397
res = 0.0
392
- elseif(x <= loc .or. x >= (loc + scale)) then
398
+ elseif(x < loc .or. x > (loc + scale)) then
393
399
res = 0.0
394
400
else
395
401
res = 1.0 / scale
@@ -410,8 +416,8 @@ contains
410
416
tr = loc % re + scale % re; ti = loc % im + scale % im
411
417
if(scale == (0.0_${k1}$,0.0_${k1}$)) then
412
418
res = 0.0
413
- elseif((x % re >= loc % re .and. x % re <= tr) .and. &
414
- (x % im >= loc % im .and. x % im <= ti)) then
419
+ elseif((x % re > loc % re .and. x % re < tr) .and. &
420
+ (x % im > loc % im .and. x % im < ti)) then
415
421
res = 1.0 / (scale % re * scale % im)
416
422
else
417
423
res = 0.0
@@ -485,9 +491,9 @@ contains
485
491
res = (x % re - loc % re) / scale % re
486
492
elseif((.not. i1) .and. (.not. i2) .and. r2) then
487
493
res = (x % im - loc % im) / scale % im
488
- elseif((.not. r1) .and. (.not. r2) .and. (.not. i1) .and. (.not. i2)) &
494
+ elseif((.not. r1) .and. (.not. r2) .and. (.not. i1) .and. (.not. i2)) &
489
495
then
490
- res = (x % re - loc % re) * (x % im - loc % im) / &
496
+ res = (x % re - loc % re) * (x % im - loc % im) / &
491
497
(scale % re * scale % im)
492
498
elseif(r2 .and. i2)then
493
499
res = 1.0
@@ -509,7 +515,7 @@ contains
509
515
n = size(list)
510
516
res = list
511
517
do i = 1, n - 1
512
- j = uniform_distribution_rvs (n - i) + i
518
+ j = rvs_uniform (n - i) + i
513
519
tmp = res(i)
514
520
res(i) = res(j)
515
521
res(j) = tmp
0 commit comments