Skip to content

Commit c119735

Browse files
committed
refactor as per suggested changes
1 parent b2ff4be commit c119735

File tree

2 files changed

+20
-64
lines changed

2 files changed

+20
-64
lines changed

src/stdlib_stats_distribution_normal.fypp

Lines changed: 19 additions & 63 deletions
Original file line numberDiff line numberDiff line change
@@ -33,9 +33,6 @@ module stdlib_stats_distribution_normal
3333

3434
#:for k1, t1 in RC_KINDS_TYPES
3535
module procedure rvs_norm_array_${t1[0]}$${k1}$ !3 dummy variables
36-
#:endfor
37-
38-
#:for k1, t1 in RC_KINDS_TYPES
3936
module procedure rvs_norm_array_default_${t1[0]}$${k1}$ !2 dummy variables (mold, array_size)
4037
#:endfor
4138
end interface rvs_normal
@@ -243,96 +240,55 @@ contains
243240
#:endfor
244241

245242
#:for k1, t1 in REAL_KINDS_TYPES
246-
impure function rvs_norm_array_default_${t1[0]}$${k1}$ (mold, array_size) result(res)
243+
impure function rvs_norm_array_default_${t1[0]}$${k1}$ (array_size, mold) result(res)
247244
!
248245
! Standard normal array random variate with default loc=0, scale=1
249246
! The mold argument is used only to determine the type and is not referenced
250247
!
251-
${t1}$, intent(in) :: mold
252248
integer, intent(in) :: array_size
249+
${t1}$, intent(in) :: mold
253250
${t1}$ :: res(array_size)
254-
${t1}$, parameter :: r = 3.442619855899_${k1}$, rr = 1.0_${k1}$/r
255-
${t1}$ :: x, y, re
256-
integer :: hz, iz, i
257251

258-
if (.not. zig_norm_initialized) call zigset
252+
res = rvs_norm_array_${t1[0]}$${k1}$ (0.0_${k1}$, 1.0_${k1}$, array_size)
259253

260-
do i = 1, array_size
261-
iz = 0
262-
hz = dist_rand(1_int32)
263-
iz = iand(hz, 127)
264-
if (abs(hz) < kn(iz)) then
265-
re = hz*wn(iz)
266-
else
267-
L1: do
268-
L2: if (iz == 0) then
269-
do
270-
x = -log(uni(1.0_${k1}$))*rr
271-
y = -log(uni(1.0_${k1}$))
272-
if (y + y >= x*x) exit
273-
end do
274-
re = r + x
275-
if (hz <= 0) re = -re
276-
exit L1
277-
end if L2
278-
x = hz*wn(iz)
279-
if (fn(iz) + uni(1.0_${k1}$)*(fn(iz - 1) - fn(iz)) < &
280-
exp(-HALF*x*x)) then
281-
re = x
282-
exit L1
283-
end if
284-
285-
hz = dist_rand(1_int32)
286-
iz = iand(hz, 127)
287-
if (abs(hz) < kn(iz)) then
288-
re = hz*wn(iz)
289-
exit L1
290-
end if
291-
end do L1
292-
end if
293-
res(i) = re ! Default: loc=0, scale=1, so re*1 + 0 = re
294-
end do
295254
end function rvs_norm_array_default_${t1[0]}$${k1}$
296255

297256
#:endfor
298257

299258
#:for k1, t1 in CMPLX_KINDS_TYPES
300-
impure function rvs_norm_array_default_${t1[0]}$${k1}$ (mold, array_size) result(res)
301-
!
302-
! Standard normal complex array random variate with default loc=0, scale=1
303-
! The mold argument is used only to determine the type and is not referenced
304-
!
305-
${t1}$, intent(in) :: mold
259+
impure function rvs_norm_array_${t1[0]}$${k1}$ (loc, scale, array_size) result(res)
260+
${t1}$, intent(in) :: loc, scale
306261
integer, intent(in) :: array_size
307262
integer :: i
308263
${t1}$ :: res(array_size)
309264
real(${k1}$) :: tr, ti
310265

311266
do i = 1, array_size
312-
tr = rvs_norm_0_r${k1}$ ()
313-
ti = rvs_norm_0_r${k1}$ ()
267+
tr = rvs_norm_r${k1}$ (loc%re, scale%re)
268+
ti = rvs_norm_r${k1}$ (loc%im, scale%im)
314269
res(i) = cmplx(tr, ti, kind=${k1}$)
315270
end do
316271

317-
end function rvs_norm_array_default_${t1[0]}$${k1}$
272+
end function rvs_norm_array_${t1[0]}$${k1}$
318273

319274
#:endfor
320275

321276
#:for k1, t1 in CMPLX_KINDS_TYPES
322-
impure function rvs_norm_array_${t1[0]}$${k1}$ (loc, scale, array_size) result(res)
323-
${t1}$, intent(in) :: loc, scale
277+
impure function rvs_norm_array_default_${t1[0]}$${k1}$ (array_size, mold) result(res)
278+
!
279+
! Standard normal complex array random variate with default loc=0, scale=1
280+
! The mold argument is used only to determine the type and is not referenced
281+
!
324282
integer, intent(in) :: array_size
325-
integer :: i
283+
${t1}$, intent(in) :: mold
326284
${t1}$ :: res(array_size)
327-
real(${k1}$) :: tr, ti
328285

329-
do i = 1, array_size
330-
tr = rvs_norm_r${k1}$ (loc%re, scale%re)
331-
ti = rvs_norm_r${k1}$ (loc%im, scale%im)
332-
res(i) = cmplx(tr, ti, kind=${k1}$)
333-
end do
286+
! Call the full procedure with default loc=(0,0), scale=(1,1)
287+
res = rvs_norm_array_${t1[0]}$${k1}$ (cmplx(0.0_${k1}$, 0.0_${k1}$, kind=${k1}$), &
288+
cmplx(1.0_${k1}$, 1.0_${k1}$, kind=${k1}$), &
289+
array_size)
334290

335-
end function rvs_norm_array_${t1[0]}$${k1}$
291+
end function rvs_norm_array_default_${t1[0]}$${k1}$
336292

337293
#:endfor
338294

test/stats/test_distribution_normal.fypp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -170,7 +170,7 @@ contains
170170
mold = (0.0_${k1}$, 0.0_${k1}$)
171171
#:endif
172172

173-
a2 = nor_rvs(mold, 10)
173+
a2 = nor_rvs(10, mold)
174174

175175
call check(all(a1 == a2), msg="normal_distribution_rvs_default_${t1[0]}$${k1}$ failed", warn=warn)
176176
end subroutine test_nor_rvs_default_${t1[0]}$${k1}$

0 commit comments

Comments
 (0)