Skip to content

Commit 615ac95

Browse files
Update stdlib_stats_distribution_uniform.fypp
1 parent d2117de commit 615ac95

File tree

1 file changed

+34
-34
lines changed

1 file changed

+34
-34
lines changed

src/stdlib_stats_distribution_uniform.fypp

Lines changed: 34 additions & 34 deletions
Original file line numberDiff line numberDiff line change
@@ -185,16 +185,16 @@ module stdlib_stats_distribution_uniform
185185
if(scale == (0.0_${k1}$, 0.0_${k1}$)) call error_stop("Error(uni_dist_" &
186186
//"rvs_1): Uniform distribution scale parameter must be non-zero")
187187
r1 = unif_dist_rvs_0_r${k1}$( )
188-
if(real(scale) == 0.0_${k1}$) then
189-
ti = aimag(scale) * r1
188+
if(scale % re == 0.0_${k1}$) then
189+
ti = scale % im * r1
190190
tr = 0.0_${k1}$
191-
elseif(aimag(scale) == 0.0_${k1}$) then
192-
tr = real(scale) * r1
191+
elseif(scale % im == 0.0_${k1}$) then
192+
tr = scale % re * r1
193193
ti = 0.0_${k1}$
194194
else
195195
r2 = unif_dist_rvs_0_r${k1}$( )
196-
tr = real(scale) * r1
197-
ti = aimag(scale) * r2
196+
tr = scale % re * r1
197+
ti = scale % im * r2
198198
endif
199199
res = cmplx(tr, ti, kind=${k1}$)
200200
end function unif_dist_rvs_1_${t1[0]}$${k1}$
@@ -216,16 +216,16 @@ module stdlib_stats_distribution_uniform
216216
if(scale == (0.0_${k1}$, 0.0_${k1}$)) call error_stop("Error(uni_dist_" &
217217
//"rvs): Uniform distribution scale parameter must be non-zero")
218218
r1 = unif_dist_rvs_0_r${k1}$( )
219-
if(real(scale) == 0.0_${k1}$) then
220-
tr = real(loc)
221-
ti = aimag(loc) + aimag(scale) * r1
222-
elseif(aimag(scale) == 0.0_${k1}$) then
223-
tr = real(loc) + real(scale) * r1
224-
ti = aimag(loc)
219+
if(scale % re == 0.0_${k1}$) then
220+
tr = loc % re
221+
ti = loc % im + scale % im * r1
222+
elseif(scale % im == 0.0_${k1}$) then
223+
tr = loc % re + scale % re * r1
224+
ti = loc % im
225225
else
226226
r2 = unif_dist_rvs_0_r${k1}$( )
227-
tr = real(loc) + real(scale) * r1
228-
ti = aimag(loc) + aimag(scale) * r2
227+
tr = loc % re + scale % re * r1
228+
ti = loc % im + scale % im * r2
229229
endif
230230
res = cmplx(tr, ti, kind=${k1}$)
231231
end function unif_dist_rvs_${t1[0]}$${k1}$
@@ -305,17 +305,17 @@ module stdlib_stats_distribution_uniform
305305
do i = 1, array_size
306306
tmp = shiftr(dist_rand(INT_ONE), 11)
307307
r1 = real(tmp * MESENNE_NUMBER, kind = ${k1}$)
308-
if(real(scale) == 0.0_${k1}$) then
309-
tr = real(loc)
310-
ti = aimag(loc) + aimag(scale) * r1
311-
elseif(aimag(scale) == 0.0_${k1}$) then
312-
tr = real(loc) + real(scale) * r1
313-
ti = aimag(loc)
308+
if(scale % re == 0.0_${k1}$) then
309+
tr = loc % re
310+
ti = loc % im + scale % im * r1
311+
elseif(scale % im == 0.0_${k1}$) then
312+
tr = loc % re + scale % re * r1
313+
ti = loc % im
314314
else
315315
tmp = shiftr(dist_rand(INT_ONE), 11)
316316
r2 = real(tmp * MESENNE_NUMBER, kind = ${k1}$)
317-
tr = real(loc) + real(scale) * r1
318-
ti = aimag(loc) + aimag(scale) * r2
317+
tr = loc % re + scale % re * r1
318+
ti = loc % im + scale % im * r2
319319
endif
320320
res(i) = cmplx(tr, ti, kind=${k1}$)
321321
end do
@@ -361,12 +361,12 @@ module stdlib_stats_distribution_uniform
361361
real :: res
362362
real(${k1}$) :: tr, ti
363363

364-
tr = real(loc) + real(scale); ti = aimag(loc) + aimag(scale)
364+
tr = loc % re + scale % re; ti = loc % im + scale % im
365365
if(scale == (0.0_${k1}$,0.0_${k1}$)) then
366366
res = 0.0
367-
elseif((real(x) >= real(loc) .and. real(x) <= tr) .and. &
368-
(aimag(x) >= aimag(loc) .and. aimag(x) <= ti)) then
369-
res = 1.0 / (real(scale) * aimag(scale))
367+
elseif((x % re >= loc % re .and. x % re <= tr) .and. &
368+
(x % im >= loc % im .and. x % im <= ti)) then
369+
res = 1.0 / (scale % re * scale % im)
370370
else
371371
res = 0.0
372372
end if
@@ -420,20 +420,20 @@ module stdlib_stats_distribution_uniform
420420
res = 0.0
421421
return
422422
endif
423-
r1 = real(x) < real(loc)
424-
r2 = real(x) > (real(loc) + real(scale))
425-
i1 = aimag(x) < aimag(loc)
426-
i2 = aimag(x) > (aimag(loc) + aimag(scale))
423+
r1 = x % re < loc % re
424+
r2 = x % re > (loc % re + scale % re)
425+
i1 = x % im < loc % im
426+
i2 = x % im > (loc % im + scale % im)
427427
if(r1 .or. i1) then
428428
res = 0.0
429429
elseif((.not. r1) .and. (.not. r2) .and. i2) then
430-
res = (real(x) - real(loc)) / real(scale)
430+
res = (x % re - loc % re) / scale % re
431431
elseif((.not. i1) .and. (.not. i2) .and. r2) then
432-
res = (aimag(x) - aimag(loc)) / aimag(scale)
432+
res = (x % im - loc % im) / scale % im
433433
elseif((.not. r1) .and. (.not. r2) .and. (.not. i1) .and. (.not. i2)) &
434434
then
435-
res = (real(x) - real(loc)) * (aimag(x) - aimag(loc)) / &
436-
(real(scale) * aimag(scale))
435+
res = (x % re - loc % re) * (x % im - loc % im) / &
436+
(scale % re * scale % im)
437437
elseif(r2 .and. i2)then
438438
res = 1.0
439439
end if

0 commit comments

Comments
 (0)