@@ -21,7 +21,7 @@ Module stdlib_stats_distribution_expon
21
21
!! Version experimental
22
22
!!
23
23
!! Exponential Distribution Random Variates
24
- !!([Specification](../page/specs/stdlib_stats_distribution_expon .html#
24
+ !!([Specification](../page/specs/stdlib_stats_distribution_exponential .html#
25
25
!! description))
26
26
!!
27
27
module procedure exp_dist_rvs_0_rsp !0 dummy variable
@@ -39,7 +39,7 @@ Module stdlib_stats_distribution_expon
39
39
!! Version experimental
40
40
!!
41
41
!! Exponential Distribution Probability Density Function
42
- !!([Specification](../page/specs/stdlib_stats_distribution_expon .html#
42
+ !!([Specification](../page/specs/stdlib_stats_distribution_exponential .html#
43
43
!! description))
44
44
!!
45
45
#:for k1, t1 in RC_KINDS_TYPES
@@ -51,7 +51,7 @@ Module stdlib_stats_distribution_expon
51
51
!! Version experimental
52
52
!!
53
53
!! Exponential Distribution Cumulative Distribution Function
54
- !! ([Specification](../page/specs/stdlib_stats_distribution_expon .html#
54
+ !! ([Specification](../page/specs/stdlib_stats_distribution_exponential .html#
55
55
!! description))
56
56
!!
57
57
#:for k1, t1 in RC_KINDS_TYPES
@@ -77,6 +77,8 @@ Module stdlib_stats_distribution_expon
77
77
! unsigned integers in Fortran.
78
78
!
79
79
! Latest version - 1 January 2001
80
+ !
81
+ ! Fotran 90 program translated from C by Jim-215-Fisher
80
82
!
81
83
real(dp), parameter :: M2 = 2147483648.0_dp
82
84
real(dp) :: de = 7.697117470131487_dp, te, &
@@ -115,25 +117,25 @@ Module stdlib_stats_distribution_expon
115
117
116
118
! Original algorithm use 32bit
117
119
iz = 0
118
- jz = dist_rand(iz )
120
+ jz = dist_rand(1_int32 )
119
121
120
122
iz = iand( jz, 255 )
121
123
if( abs( jz ) < ke(iz) ) then
122
124
res = abs(jz) * we(iz)
123
125
else
124
126
L1: do
125
127
if( iz == 0 ) then
126
- res = r - log( uni( ) )
128
+ res = r - log( uni(1.0_${k1}$ ) )
127
129
exit L1
128
130
end if
129
131
x = abs( jz ) * we(iz)
130
- if( fe(iz) + uni( ) * (fe(iz-1) - fe(iz)) < exp( -x ) ) then
132
+ if(fe(iz) + uni(1.0_${k1}$ ) * (fe(iz-1) - fe(iz)) < exp(-x) ) then
131
133
res = x
132
134
exit L1
133
135
end if
134
136
135
137
!original algorithm use 32bit
136
- jz = dist_rand(iz )
138
+ jz = dist_rand(1_int32 )
137
139
iz = iand( jz, 255 )
138
140
if( abs( jz ) < ke(iz) ) then
139
141
res = abs( jz ) * we(iz)
@@ -161,25 +163,25 @@ Module stdlib_stats_distribution_expon
161
163
162
164
! Original algorithm use 32bit
163
165
iz = 0
164
- jz = dist_rand(iz )
166
+ jz = dist_rand(1_int32 )
165
167
166
168
iz = iand( jz, 255 )
167
169
if( abs( jz ) < ke(iz) ) then
168
170
res = abs(jz) * we(iz)
169
171
else
170
172
L1: do
171
173
if( iz == 0 ) then
172
- res = r - log( uni( ) )
174
+ res = r - log( uni(1.0_${k1}$ ) )
173
175
exit L1
174
176
end if
175
177
x = abs( jz ) * we(iz)
176
- if( fe(iz) + uni( ) * (fe(iz-1) - fe(iz)) < exp( -x ) ) then
178
+ if(fe(iz) + uni(1.0_${k1}$ ) * (fe(iz-1) - fe(iz)) < exp(-x) ) then
177
179
res = x
178
180
exit L1
179
181
end if
180
182
181
183
!original algorithm use 32bit
182
- jz = dist_rand(iz )
184
+ jz = dist_rand(1_int32 )
183
185
iz = iand( jz, 255 )
184
186
if( abs( jz ) < ke(iz) ) then
185
187
res = abs( jz ) * we(iz)
@@ -201,7 +203,7 @@ Module stdlib_stats_distribution_expon
201
203
202
204
tr = exp_dist_rvs_r${k1}$(real(lamda))
203
205
ti = exp_dist_rvs_r${k1}$(aimag(lamda))
204
- res = cmplx(tr, ti)
206
+ res = cmplx(tr, ti, kind=${k1}$ )
205
207
return
206
208
end function exp_dist_rvs_${t1[0]}$${k1}$
207
209
@@ -223,25 +225,25 @@ Module stdlib_stats_distribution_expon
223
225
do i =1, array_size
224
226
! Original algorithm use 32bit
225
227
iz = 0
226
- jz = dist_rand(iz )
228
+ jz = dist_rand(1_int32 )
227
229
228
230
iz = iand( jz, 255 )
229
231
if( abs( jz ) < ke(iz) ) then
230
232
re = abs(jz) * we(iz)
231
233
else
232
234
L1: do
233
235
if( iz == 0 ) then
234
- re = r - log( uni( ) )
236
+ re = r - log( uni(1.0_${k1}$ ) )
235
237
exit L1
236
238
end if
237
239
x = abs( jz ) * we(iz)
238
- if( fe(iz) + uni( ) * (fe(iz-1) - fe(iz)) < exp( -x ) ) then
240
+ if(fe(iz) + uni(1.0_${k1}$)* (fe(iz-1)- fe(iz)) < exp(-x) ) then
239
241
re = x
240
242
exit L1
241
243
end if
242
244
243
245
!original algorithm use 32bit
244
- jz = dist_rand(iz )
246
+ jz = dist_rand(1_int32 )
245
247
iz = iand( jz, 255 )
246
248
if( abs( jz ) < ke(iz) ) then
247
249
re = abs( jz ) * we(iz)
@@ -268,7 +270,7 @@ Module stdlib_stats_distribution_expon
268
270
do i = 1, array_size
269
271
tr = exp_dist_rvs_r${k1}$(real(lamda))
270
272
ti = exp_dist_rvs_r${k1}$(aimag(lamda))
271
- res(i) = cmplx(tr, ti)
273
+ res(i) = cmplx(tr, ti, kind=${k1}$ )
272
274
end do
273
275
return
274
276
end function exp_dist_rvs_array_${t1[0]}$${k1}$
@@ -284,6 +286,8 @@ Module stdlib_stats_distribution_expon
284
286
285
287
if(lamda <= 0.0_${k1}$) call error_stop("Error: Exponential" &
286
288
//" distribution lamda parameter must be greaeter than zero")
289
+ if(x < 0.0_${k1}$) call error_stop("Error: Exponential distribution" &
290
+ //" variate x must be non-negative")
287
291
res = exp(- x * lamda) * lamda
288
292
return
289
293
end function exp_dist_pdf_${t1[0]}$${k1}$
@@ -311,6 +315,8 @@ Module stdlib_stats_distribution_expon
311
315
312
316
if(lamda <= 0.0_${k1}$) call error_stop("Error: Exponential" &
313
317
//" distribution lamda parameter must be greaeter than zero")
318
+ if(x < 0.0_${k1}$) call error_stop("Error: Exponential distribution" &
319
+ //" variate x must be non-negative")
314
320
res = (1.0 - exp(- x * lamda))
315
321
return
316
322
end function exp_dist_cdf_${t1[0]}$${k1}$
0 commit comments