@@ -12,16 +12,17 @@ module stdlib_stats_distribution_uniform
1212 real(dp), parameter :: MESENNE_NUMBER = 1.0_dp / (2.0_dp ** 53 - 1.0_dp)
1313 integer(int64), parameter :: INT_ONE = 1_int64
1414
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
1818 public :: shuffle
1919
2020
21- interface uniform_distribution_rvs
21+ interface rvs_uniform
2222 !! Version experimental
2323 !!
2424 !! Get uniformly distributed random variate for integer, real and complex
25+ !! variables.
2526 !! ([Specification](../page/specs/stdlib_stats_distribution_uniform.html#
2627 !! description))
2728
@@ -38,11 +39,11 @@ module stdlib_stats_distribution_uniform
3839 #:for k1, t1 in ALL_KINDS_TYPES
3940 module procedure unif_dist_rvs_array_${t1[0]}$${k1}$ ! 3 dummy variables
4041 #:endfor
41- end interface uniform_distribution_rvs
42+ end interface rvs_uniform
4243
4344
44- interface uniform_distribution_pdf
45- !! Version experiment
45+ interface pdf_uniform
46+ !! Version experimental
4647 !!
4748 !! Get uniform distribution probability density (pdf) for integer, real and
4849 !! complex variables.
@@ -52,10 +53,10 @@ module stdlib_stats_distribution_uniform
5253 #:for k1, t1 in ALL_KINDS_TYPES
5354 module procedure unif_dist_pdf_${t1[0]}$${k1}$
5455 #:endfor
55- end interface uniform_distribution_pdf
56+ end interface pdf_uniform
5657
5758
58- interface uniform_distribution_cdf
59+ interface cdf_uniform
5960 !! Version experimental
6061 !!
6162 !! Get uniform distribution cumulative distribution function (cdf) for integer,
@@ -66,14 +67,14 @@ module stdlib_stats_distribution_uniform
6667 #:for k1, t1 in ALL_KINDS_TYPES
6768 module procedure unif_dist_cdf_${t1[0]}$${k1}$
6869 #:endfor
69- end interface uniform_distribution_cdf
70+ end interface cdf_uniform
7071
7172
7273 interface shuffle
7374 !! Version experimental
7475 !!
7576 !! Fisher-Yates shuffle algorithm for a rank one array of integer, real and
76- !! complex variables
77+ !! complex variables.
7778 !! ([Specification](../page/specs/stdlib_stats_distribution_uniform.html#
7879 !! description))
7980 !!
@@ -85,6 +86,8 @@ module stdlib_stats_distribution_uniform
8586
8687
8788
89+
90+
8891contains
8992
9093
@@ -101,8 +104,8 @@ contains
101104 ${t1}$ :: res, u, mask
102105 integer :: zeros, bits_left, bits
103106
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")
106109 zeros = leadz(scale)
107110 bits = bit_size(scale) - zeros
108111 mask = shiftr(not(0_${k1}$), zeros)
@@ -126,16 +129,16 @@ contains
126129
127130
128131 #: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) &
130133 result( res )
131134 !
132135 ! Uniformly distributed integer in [loc, loc + scale]
133136 !
134137 ${t1}$, intent(in) :: loc, scale
135138 ${t1}$ :: res
136139
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")
139142 res = loc + unif_dist_rvs_1_${t1[0]}$${k1}$(scale)
140143 end function unif_dist_rvs_${t1[0]}$${k1}$
141144
@@ -170,8 +173,8 @@ contains
170173 ${t1}$, intent(in) :: scale
171174 ${t1}$ :: res
172175
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")
175178 res = scale * unif_dist_rvs_0_${t1[0]}$${k1}$( )
176179 end function unif_dist_rvs_1_${t1[0]}$${k1}$
177180
@@ -180,16 +183,16 @@ contains
180183
181184
182185 #: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) &
184187 result(res)
185188 !
186189 ! Uniformly distributed float in [loc, loc + scale]
187190 !
188191 ${t1}$, intent(in) :: loc, scale
189192 ${t1}$ :: res
190193
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")
193196 res = loc + scale * unif_dist_rvs_0_${t1[0]}$${k1}$( )
194197 end function unif_dist_rvs_${t1[0]}$${k1}$
195198
@@ -198,7 +201,8 @@ contains
198201
199202
200203 #: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)
202206 !
203207 ! Uniformly distributed complex in [(0,0i), (scale, i(scale))]
204208 ! The real part and imaginary part are independent of each other, so that
@@ -208,8 +212,8 @@ contains
208212 ${t1}$ :: res
209213 real(${k1}$) :: r1, tr, ti
210214
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")
213217 r1 = unif_dist_rvs_0_r${k1}$( )
214218 if(scale % re == 0.0_${k1}$) then
215219 ti = scale % im * r1
@@ -230,10 +234,11 @@ contains
230234
231235
232236 #: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) &
234238 result(res)
235239 !
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))].
237242 ! The real part and imaginary part are independent of each other, so that
238243 ! the joint distribution is on an unit square [(loc,iloc), (loc + scale,
239244 ! i(loc + scale))]
@@ -242,8 +247,8 @@ contains
242247 ${t1}$ :: res
243248 real(${k1}$) :: r1, tr, ti
244249
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")
247252 r1 = unif_dist_rvs_0_r${k1}$( )
248253 if(scale % re == 0.0_${k1}$) then
249254 tr = loc % re
@@ -264,7 +269,7 @@ contains
264269
265270
266271 #: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) &
268273 result(res)
269274
270275 integer, intent(in) :: array_size
@@ -273,8 +278,8 @@ contains
273278 ${t1}$ :: u, mask, nn
274279 integer :: i, zeros, bits_left, bits
275280
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")
278283 zeros = leadz(scale)
279284 bits = bit_size(scale) - zeros
280285 mask = shiftr(not(0_${k1}$), zeros)
@@ -301,7 +306,7 @@ contains
301306
302307
303308 #: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) &
305310 result(res)
306311
307312 integer, intent(in) :: array_size
@@ -312,8 +317,8 @@ contains
312317 integer :: i
313318
314319
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")
317322 do i = 1, array_size
318323 tmp = shiftr(dist_rand(INT_ONE), 11)
319324 t = real(tmp * MESENNE_NUMBER, kind = ${k1}$)
@@ -326,7 +331,7 @@ contains
326331
327332
328333 #: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) &
330335 result(res)
331336
332337 integer, intent(in) :: array_size
@@ -337,8 +342,9 @@ contains
337342 integer :: i
338343
339344
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")
342348 do i = 1, array_size
343349 tmp = shiftr(dist_rand(INT_ONE), 11)
344350 r1 = real(tmp * MESENNE_NUMBER, kind = ${k1}$)
@@ -389,7 +395,7 @@ contains
389395
390396 if(scale == 0.0_${k1}$) then
391397 res = 0.0
392- elseif(x <= loc .or. x >= (loc + scale)) then
398+ elseif(x < loc .or. x > (loc + scale)) then
393399 res = 0.0
394400 else
395401 res = 1.0 / scale
@@ -410,8 +416,8 @@ contains
410416 tr = loc % re + scale % re; ti = loc % im + scale % im
411417 if(scale == (0.0_${k1}$,0.0_${k1}$)) then
412418 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
415421 res = 1.0 / (scale % re * scale % im)
416422 else
417423 res = 0.0
@@ -485,9 +491,9 @@ contains
485491 res = (x % re - loc % re) / scale % re
486492 elseif((.not. i1) .and. (.not. i2) .and. r2) then
487493 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)) &
489495 then
490- res = (x % re - loc % re) * (x % im - loc % im) / &
496+ res = (x % re - loc % re) * (x % im - loc % im) / &
491497 (scale % re * scale % im)
492498 elseif(r2 .and. i2)then
493499 res = 1.0
@@ -509,7 +515,7 @@ contains
509515 n = size(list)
510516 res = list
511517 do i = 1, n - 1
512- j = uniform_distribution_rvs (n - i) + i
518+ j = rvs_uniform (n - i) + i
513519 tmp = res(i)
514520 res(i) = res(j)
515521 res(j) = tmp
0 commit comments