Skip to content

Commit 09f8fd2

Browse files
author
Jim-215-Fisher
committed
add precisions for pdf and cdf
1 parent 7194bfd commit 09f8fd2

File tree

2 files changed

+72
-29
lines changed

2 files changed

+72
-29
lines changed

src/stdlib_stats_distribution_normal.fypp

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
#:include "common.fypp"
22
#:set RC_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES
33
module stdlib_stats_distribution_normal
4-
use stdlib_kinds
4+
use stdlib_kinds, only :: sp, dp, xdp, qp, int32
55
use stdlib_error, only : error_stop
66
use stdlib_random, only : dist_rand
77
use stdlib_stats_distribution_uniform, only : uni=>rvs_uniform
@@ -274,7 +274,7 @@ contains
274274
! Normal distribution probability density function
275275
!
276276
${t1}$, intent(in) :: x, loc, scale
277-
real :: res
277+
${t1}$ :: res
278278
${t1}$, parameter :: sqrt_2_pi = sqrt(2.0_${k1}$ * acos(-1.0_${k1}$))
279279

280280
if(scale == 0._${k1}$) call error_stop("Error(pdf_norm): Normal" &
@@ -290,7 +290,7 @@ contains
290290
#:for k1, t1 in CMPLX_KINDS_TYPES
291291
impure elemental function pdf_norm_${t1[0]}$${k1}$(x, loc, scale) result(res)
292292
${t1}$, intent(in) :: x, loc, scale
293-
real :: res
293+
real(${k1}$) :: res
294294

295295
res = pdf_norm_r${k1}$(x % re, loc % re, scale % re)
296296
res = res * pdf_norm_r${k1}$(x % im, loc % im, scale % im)
@@ -306,12 +306,12 @@ contains
306306
! Normal distribution cumulative distribution function
307307
!
308308
${t1}$, intent(in) :: x, loc, scale
309-
real :: res
309+
${t1}$ :: res
310310
${t1}$, parameter :: sqrt_2 = sqrt(2.0_${k1}$)
311311

312312
if(scale == 0._${k1}$) call error_stop("Error(cdf_norm): Normal" &
313313
//"distribution scale parameter must be non-zero")
314-
res = (1.0_${k1}$ + erf((x - loc) / (scale * sqrt_2))) / 2.0_${k1}$
314+
res = erfc(- (x - loc) / (scale * sqrt_2)) / 2.0_${k1}$
315315
end function cdf_norm_${t1[0]}$${k1}$
316316

317317
#:endfor
@@ -321,7 +321,7 @@ contains
321321
#:for k1, t1 in CMPLX_KINDS_TYPES
322322
impure elemental function cdf_norm_${t1[0]}$${k1}$(x, loc, scale) result(res)
323323
${t1}$, intent(in) :: x, loc, scale
324-
real :: res
324+
real(${k1}$) :: res
325325

326326
res = cdf_norm_r${k1}$(x % re, loc % re, scale % re)
327327
res = res * cdf_norm_r${k1}$(x % im, loc % im, scale % im)

src/tests/stats/test_distribution_normal.fypp

Lines changed: 66 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -146,21 +146,43 @@ contains
146146
${t1}$ :: x1, x2(3,4), loc, scale
147147
integer, parameter :: k = 5
148148
integer :: i, n, seed, get
149-
real :: res(3,5)
149+
real(${k1}$) :: res(3,5)
150150
#:if t1[0] == "r"
151151
#! for real type
152-
real, parameter :: ans(15) = &
153-
[0.215050772, 0.215050772, 0.215050772, 0.200537622, &
154-
5.66161536E-02, 0.238986954, 0.265935957,0.262147546,&
155-
0.249866411, 3.98721099E-02, 0.265902370,0.161311597,&
156-
0.249177739, 0.237427220, 0.155696079]
152+
real(${k1}$), parameter :: ans(15) = &
153+
[0.215050766989949083210785218076278553_${k1}$, &
154+
0.215050766989949083210785218076278553_${k1}$, &
155+
0.215050766989949083210785218076278553_${k1}$, &
156+
0.200537626692880596839299818454439236_${k1}$, &
157+
5.66161527403268434368575024104022496E-0002_${k1}$, &
158+
0.238986957612021514867582359518579138_${k1}$, &
159+
0.265935969411942911029638292783132425_${k1}$, &
160+
0.262147558654079961109031890374902943_${k1}$, &
161+
0.249866408914952245533320687656894701_${k1}$, &
162+
3.98721117498705317877792757313696510E-0002_${k1}$, &
163+
0.265902369803533466897906694845094995_${k1}$, &
164+
0.161311603170650092038944290133124635_${k1}$, &
165+
0.249177740354276111998717092437037695_${k1}$, &
166+
0.237427217242213206474603807278971527_${k1}$, &
167+
0.155696086384122017518186260628090478_${k1}$]
157168
#:else
158169
#! for complex type
159-
real, parameter :: ans(15) = &
160-
[0.129377320, 0.129377320,0.129377320,4.05915640E-02, &
161-
0.209143385,2.98881028E-02, 0.128679410, 0.177484736,&
162-
3.82205322E-02, 7.09915683E-02, 4.56126593E-02, &
163-
6.57454133E-02,0.165161043,3.86104807E-02,0.196922958]
170+
real(${k1}$), parameter :: ans(15) = &
171+
[0.129377311291944176372137325120411497_${k1}$, &
172+
0.129377311291944176372137325120411497_${k1}$, &
173+
0.129377311291944176372137325120411497_${k1}$, &
174+
4.05915662853246811934977653001971736E-0002_${k1}$, &
175+
0.209143395418940756076861773161637924_${k1}$, &
176+
2.98881041363874672676853084975547667E-0002_${k1}$, &
177+
0.128679412679649127469385460133445161_${k1}$, &
178+
0.177484732473055532384223611956177231_${k1}$, &
179+
3.82205306942578982084957100753849738E-0002_${k1}$, &
180+
7.09915714309796034515515428785324918E-0002_${k1}$, &
181+
4.56126582912124629544443072483362352E-0002_${k1}$, &
182+
6.57454133967021123696499056531595921E-0002_${k1}$, &
183+
0.165161039915667041643464172210282279_${k1}$, &
184+
3.86104822953520989775015755966798359E-0002_${k1}$, &
185+
0.196922947431391188040943672442575686_${k1}$]
164186
#:endif
165187

166188
print *, "Test normal_distribution_pdf_${t1[0]}$${k1}$"
@@ -193,22 +215,43 @@ contains
193215
${t1}$ :: x1, x2(3,4), loc, scale
194216
integer :: i, n
195217
integer :: seed, get
196-
real :: res(3,5)
218+
real(${k1}$) :: res(3,5)
197219
#:if t1[0] == "r"
198220
#!for real type
199-
real, parameter :: ans(15) = &
200-
[7.50826299E-02, 7.50826299E-02, 7.50826299E-02, &
201-
0.143119827, 0.241425425, 0.284345865, 0.233239830, &
202-
0.341059506,0.353156865,6.81066737E-02,4.38792333E-02,&
203-
0.763679624, 0.363722175, 0.868187129, 0.626506805]
221+
real(${k1}$), parameter :: ans(15) = &
222+
[7.50826305038441048487991102776953948E-0002_${k1}$, &
223+
7.50826305038441048487991102776953948E-0002_${k1}$, &
224+
7.50826305038441048487991102776953948E-0002_${k1}$, &
225+
0.143119834108717983250834016885129863_${k1}$, &
226+
0.241425421525703182028420560765471735_${k1}$, &
227+
0.284345878626039240974266199229875972_${k1}$, &
228+
0.233239836366015928845367994433532757_${k1}$, &
229+
0.341059506137219171082517155967522896_${k1}$, &
230+
0.353156850199835111081038166086606192_${k1}$, &
231+
6.81066766396638231790017005897813244E-0002_${k1}$, &
232+
4.38792331441682923984716366123285346E-0002_${k1}$, &
233+
0.763679637882860826030745070304416929_${k1}$, &
234+
0.363722187587355040667876190724308059_${k1}$, &
235+
0.868187114884980488672309198087692444_${k1}$, &
236+
0.626506799809652872401992867475200722_${k1}$]
204237
#:else
205238
#! for complex type
206-
real, parameter :: ans(15) = &
207-
[1.07458131E-02, 1.07458131E-02, 1.07458131E-02, &
208-
6.86483234E-02, 7.95486644E-02, 2.40523387E-02, &
209-
3.35096754E-02,0.315778911,0.446311295, 0.102010213, &
210-
7.66918957E-02, 0.564691007, 0.708769500, &
211-
6.40553832E-02, 5.39999157E-02]
239+
real(${k1}$), parameter :: ans(15) = &
240+
[1.07458136221563368133842063954746170E-0002_${k1}$, &
241+
1.07458136221563368133842063954746170E-0002_${k1}$, &
242+
1.07458136221563368133842063954746170E-0002_${k1}$, &
243+
6.86483236063879585051085536740820057E-0002_${k1}$, &
244+
7.95486634025192048896990048539218724E-0002_${k1}$, &
245+
2.40523393996423661445007940057223384E-0002_${k1}$, &
246+
3.35096768781160662250307446207445131E-0002_${k1}$, &
247+
0.315778916661119434962814841317323376_${k1}$, &
248+
0.446311293878359175362094845206410428_${k1}$, &
249+
0.102010220821382542292905161748120877_${k1}$, &
250+
7.66919007012121545175655727052974512E-0002_${k1}$, &
251+
0.564690968410069125818268877247699603_${k1}$, &
252+
0.708769523556518785240723539383512333_${k1}$, &
253+
6.40553790808161720088070925562830659E-0002_${k1}$, &
254+
5.39999153072107729358158443133850711E-0002_${k1}$]
212255
#:endif
213256

214257
print *, "Test normal_distribution_cdf_${t1[0]}$${k1}$"

0 commit comments

Comments
 (0)