Skip to content

Commit 5022e25

Browse files
committed
for all non-sp kinds, use max available precision
1 parent a12c18d commit 5022e25

File tree

2 files changed

+14
-10
lines changed

2 files changed

+14
-10
lines changed

src/stdlib_specialfunctions_gamma.fypp

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -219,7 +219,7 @@ contains
219219
#! gamma will use the next available more accurate KIND for the
220220
#! internal more accurate solver.
221221
#:for i, k1, t1, i1 in IDX_CMPLX_KINDS_TYPES[:-1]
222-
#:set k2 = CMPLX_KINDS[i + 1]
222+
#:set k2 = CMPLX_KINDS[i + 1] if k1 == "sp" else CMPLX_KINDS[-1]
223223
#:set t2 = "real({})".format(k2)
224224
impure elemental function gamma_${t1[0]}$${k1}$(z) result(res)
225225
${t1}$, intent(in) :: z
@@ -408,7 +408,7 @@ contains
408408
#! gamma will use the next available more accurate KIND for the
409409
#! internal more accurate solver.
410410
#:for i, k1, t1, i1 in IDX_CMPLX_KINDS_TYPES[:-1]
411-
#:set k2 = CMPLX_KINDS[i + 1]
411+
#:set k2 = CMPLX_KINDS[i + 1] if k1 == "sp" else CMPLX_KINDS[-1]
412412
#:set t2 = "real({})".format(k2)
413413
impure elemental function l_gamma_${t1[0]}$${k1}$(z) result (res)
414414
!
@@ -549,7 +549,7 @@ contains
549549
#! gamma will use the next available more accurate KIND for the
550550
#! internal more accurate solver.
551551
#:for i, k1, t1, i1 in IDX_REAL_KINDS_TYPES[:-1]
552-
#:set k2 = REAL_KINDS[i + 1]
552+
#:set k2 = REAL_KINDS[i + 1] if k1 == "sp" else REAL_KINDS[-1]
553553
#:set t2 = REAL_TYPES[i + 1]
554554
impure elemental function gpx_${t1[0]}$${k1}$(p, x) result(res)
555555
!

test/specialfunctions/test_specialfunctions_gamma.fypp

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -185,15 +185,14 @@ contains
185185

186186
do i = 1, n
187187

188-
err = state_type(STDLIB_VALUE_ERROR,'Complex ${k1}$ failed: x=',x(i),' gamma=',gamma(x(i)), &
189-
'expected=',ans(i),' tol=',tol_${k1}$)
188+
err = state_type(STDLIB_VALUE_ERROR,'Complex ${k1}$ failed: x=',x(i), &
189+
' gamma=',gamma(x(i)), &
190+
'expected=',ans(i), &
191+
' tol=',tol_${k1}$)
190192

191193
call check(error, gamma(x(i)), ans(i), err%print(),&
192194
thr = tol_${k1}$, rel = .true.)
193195

194-
!call check(error, gamma(x(i)), ans(i), "Complex kind ${k1}$ failed",&
195-
! thr = tol_${k1}$, rel = .true.)
196-
197196
end do
198197

199198
#:endif
@@ -257,8 +256,13 @@ contains
257256

258257
do i = 1, n
259258

260-
call check(error, log_gamma(x(i)), ans(i), "Complex kind ${k1}$ " &
261-
//"failed", thr = tol_${k1}$, rel = .true.)
259+
err = state_type(STDLIB_VALUE_ERROR,'Complex ${k1}$ failed: x=',x(i), &
260+
' log(gamma)=',log_gamma(x(i)), &
261+
'expected=',ans(i), &
262+
' tol=',tol_${k1}$)
263+
264+
call check(error, log_gamma(x(i)), ans(i), err%print(),&
265+
thr = tol_${k1}$, rel = .true.)
262266

263267
end do
264268

0 commit comments

Comments
 (0)