Skip to content

Commit 374c4b9

Browse files
chn. complex number with kinds
1 parent 86f4f3a commit 374c4b9

File tree

2 files changed

+26
-26
lines changed

2 files changed

+26
-26
lines changed

src/stdlib_stats_distribution_normal.fypp

Lines changed: 18 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -114,7 +114,7 @@ Module stdlib_stats_distribution_normal
114114
if( .not. zig_norm_initialized ) call zigset
115115
iz = 0
116116
! original algorithm use 32bit
117-
hz = dist_rand(iz)
117+
hz = dist_rand(1_int32)
118118

119119
iz = iand( hz, 127 )
120120
if( abs( hz ) < kn(iz) ) then
@@ -123,23 +123,23 @@ Module stdlib_stats_distribution_normal
123123
L1: do
124124
L2: if( iz == 0 ) then
125125
do
126-
x = -log( uni( ) ) * rr
127-
y = -log( uni( ) )
126+
x = -log( uni(1.0_${k1}$) ) * rr
127+
y = -log( uni(1.0_${k1}$) )
128128
if( y + y >= x * x ) exit
129129
end do
130130
res = r + x
131131
if( hz <= 0 ) res = -res
132132
exit L1
133133
end if L2
134134
x = hz * wn(iz)
135-
if( fn(iz) + uni( ) * (fn(iz-1) - fn(iz)) < &
135+
if( fn(iz) + uni(1.0_${k1}$) * (fn(iz-1) - fn(iz)) < &
136136
exp(-HALF * x * x) ) then
137137
res = x
138138
exit L1
139139
end if
140140

141141
!original algorithm use 32bit
142-
hz = dist_rand(iz)
142+
hz = dist_rand(1_int32)
143143
iz = iand( hz, 127 )
144144
if( abs( hz ) < kn(iz) ) then
145145
res = hz * wn(iz)
@@ -168,7 +168,7 @@ Module stdlib_stats_distribution_normal
168168
if( .not. zig_norm_initialized ) call zigset
169169
iz = 0
170170
! original algorithm use 32bit
171-
hz = dist_rand(iz)
171+
hz = dist_rand(1_int32)
172172

173173
iz = iand( hz, 127 )
174174
if( abs( hz ) < kn(iz) ) then
@@ -177,23 +177,23 @@ Module stdlib_stats_distribution_normal
177177
L1: do
178178
L2: if( iz == 0 ) then
179179
do
180-
x = -log( uni( ) ) * rr
181-
y = -log( uni( ) )
180+
x = -log( uni(1.0_${k1}$) ) * rr
181+
y = -log( uni(1.0_${k1}$) )
182182
if( y + y >= x * x ) exit
183183
end do
184184
res = r + x
185185
if( hz <= 0 ) res = -res
186186
exit L1
187187
end if L2
188188
x = hz * wn(iz)
189-
if( fn(iz) + uni( ) * (fn(iz-1) - fn(iz)) < &
189+
if( fn(iz) + uni(1.0_${k1}$) * (fn(iz-1) - fn(iz)) < &
190190
exp(-HALF * x * x) ) then
191191
res = x
192192
exit L1
193193
end if
194194

195195
!original algorithm use 32bit
196-
hz = dist_rand(iz)
196+
hz = dist_rand(1_int32)
197197
iz = iand( hz, 127 )
198198
if( abs( hz ) < kn(iz) ) then
199199
res = hz * wn(iz)
@@ -219,7 +219,7 @@ Module stdlib_stats_distribution_normal
219219

220220
tr = norm_dist_rvs_r${k1}$(real(loc), real(scale))
221221
ti = norm_dist_rvs_r${k1}$(aimag(loc), aimag(scale))
222-
res = cmplx(tr, ti)
222+
res = cmplx(tr, ti, kind=${k1}$)
223223
return
224224
end function norm_dist_rvs_${t1[0]}$${k1}$
225225

@@ -242,7 +242,7 @@ Module stdlib_stats_distribution_normal
242242
do i = 1, array_size
243243
iz = 0
244244
! original algorithm use 32bit
245-
hz = dist_rand(iz)
245+
hz = dist_rand(1_int32)
246246

247247
iz = iand( hz, 127 )
248248
if( abs( hz ) < kn(iz) ) then
@@ -251,23 +251,23 @@ Module stdlib_stats_distribution_normal
251251
L1: do
252252
L2: if( iz == 0 ) then
253253
do
254-
x = -log( uni( ) ) * rr
255-
y = -log( uni( ) )
254+
x = -log( uni(1.0_${k1}$) ) * rr
255+
y = -log( uni(1.0_${k1}$) )
256256
if( y + y >= x * x ) exit
257257
end do
258258
re = r + x
259259
if( hz <= 0 ) re = -re
260260
exit L1
261261
end if L2
262262
x = hz * wn(iz)
263-
if( fn(iz) + uni( ) * (fn(iz-1) - fn(iz)) < &
263+
if( fn(iz) + uni(1.0_${k1}$) * (fn(iz-1) - fn(iz)) < &
264264
exp(-HALF * x * x) ) then
265265
re = x
266266
exit L1
267267
end if
268268

269269
!original algorithm use 32bit
270-
hz = dist_rand(iz)
270+
hz = dist_rand(1_int32)
271271
iz = iand( hz, 127 )
272272
if( abs( hz ) < kn(iz) ) then
273273
re = hz * wn(iz)
@@ -295,7 +295,7 @@ Module stdlib_stats_distribution_normal
295295
do i = 1, array_size
296296
tr = norm_dist_rvs_r${k1}$(real(loc), real(scale))
297297
ti = norm_dist_rvs_r${k1}$(aimag(loc), aimag(scale))
298-
res(i) = cmplx(tr, ti)
298+
res(i) = cmplx(tr, ti, kind=${k1}$)
299299
end do
300300
return
301301
end function norm_dist_rvs_array_${t1[0]}$${k1}$
@@ -363,4 +363,4 @@ Module stdlib_stats_distribution_normal
363363

364364
#:endfor
365365

366-
end module stdlib_stats_distribution_normal
366+
end module stdlib_stats_distribution_normal

src/stdlib_stats_distribution_uniform.fypp

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -134,7 +134,7 @@ Module stdlib_stats_distribution_uniform
134134
! Uniformly distributed float in [0,1]
135135
! Based on the paper by Frederic Goualard, "Generating Random Floating-
136136
! Point Numbers By Dividing Integers: a Case Study", Proceedings of
137-
! ICCS 2020, June 20202, Amsterdam, Netherlands
137+
! ICCS 2020, June 2020, Amsterdam, Netherlands
138138
!
139139
${t1}$ :: res
140140
integer(int64) :: tmp
@@ -201,7 +201,7 @@ Module stdlib_stats_distribution_uniform
201201
tr = real(scale) * r1
202202
ti = aimag(scale) * r2
203203
endif
204-
res = cmplx(tr, ti)
204+
res = cmplx(tr, ti, kind=${k1}$)
205205
return
206206
end function unif_dist_rvs_1_${t1[0]}$${k1}$
207207

@@ -233,7 +233,7 @@ Module stdlib_stats_distribution_uniform
233233
tr = real(loc) + real(scale) * r1
234234
ti = aimag(loc) + aimag(scale) * r2
235235
endif
236-
res = cmplx(tr, ti)
236+
res = cmplx(tr, ti, kind=${k1}$)
237237
return
238238
end function unif_dist_rvs_${t1[0]}$${k1}$
239239

@@ -329,7 +329,7 @@ Module stdlib_stats_distribution_uniform
329329
tr = real(loc) + real(scale) * r1
330330
ti = aimag(loc) + aimag(scale) * r2
331331
endif
332-
res(i) = cmplx(tr, ti)
332+
res(i) = cmplx(tr, ti, kind=${k1}$)
333333
enddo
334334
return
335335
end function unif_dist_rvs_array_${t1[0]}$${k1}$
@@ -343,10 +343,10 @@ Module stdlib_stats_distribution_uniform
343343

344344
if(scale == 0) then
345345
res = 0.0
346-
elseif(x < loc .or. x >loc + scale) then
346+
elseif(x < loc .or. x > (loc + scale)) then
347347
res = 0.0
348348
else
349-
res = 1. / (scale + 1)
349+
res = 1. / (scale + 1_${k1}$)
350350
end if
351351
return
352352
end function unif_dist_pdf_${t1[0]}$${k1}$
@@ -400,7 +400,7 @@ Module stdlib_stats_distribution_uniform
400400
elseif(x < loc) then
401401
res = 0.0
402402
elseif(x >= loc .and. x <= (loc + scale)) then
403-
res = real((x - loc + 1)) / real((scale + 1))
403+
res = real((x - loc + 1_${k1}$)) / real((scale + 1_${k1}$))
404404
else
405405
res = 1.0
406406
end if
@@ -479,4 +479,4 @@ Module stdlib_stats_distribution_uniform
479479
end function shuffle_${t1[0]}$${k1}$
480480

481481
#:endfor
482-
end module stdlib_stats_distribution_uniform
482+
end module stdlib_stats_distribution_uniform

0 commit comments

Comments
 (0)