Skip to content

Commit c3d0bdd

Browse files
committed
Update stdlib_math.is_close, like python math.isclose
1 parent 9cebec7 commit c3d0bdd

File tree

4 files changed

+45
-40
lines changed

4 files changed

+45
-40
lines changed

doc/specs/stdlib_math.md

Lines changed: 15 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -348,22 +348,20 @@ end program demo_math_arange
348348

349349
#### Description
350350

351-
Returns a boolean scalar/array where two scalars/arrays are element-wise equal within a tolerance.
352-
353-
The tolerance values are positive, typically very small numbers. The relative difference `(rtol*abs(b))` and the absolute difference `atol` are added together to compare against the absolute difference between `a` and `b`.
351+
Returns a boolean scalar/array where two scalars/arrays are element-wise equal within a tolerance, behaves like `isclose` in Python stdlib.
354352

355353
```fortran
356354
!> For `real` type
357-
abs(a - b) <= rtol*abs(b) + atol
355+
is_close(a, b, rel_tol, abs_tol) = abs(a - b) <= max(rel_tol*(abs(a), abs(b)), abs_tol)
358356
359357
!> For `complex` type
360-
abs(a%re - b%re) <= rtol*abs(b%re) + atol
361-
abs(a%im - b%im) <= rtol*abs(b%im) + atol
358+
is_close(a, b, rel_tol, abs_tol) = is_close(a%re, b%re, rel_tol, abs_tol) .and. &
359+
is_close(a%im, b%im, rel_tol, abs_tol)
362360
```
363361

364362
#### Syntax
365363

366-
`bool = [[stdlib_math(module):is_close(interface)]] (a, b [, rtol, atol])`
364+
`bool = [[stdlib_math(module):is_close(interface)]] (a, b [, rel_tol, abs_tol])`
367365

368366
#### Status
369367

@@ -381,14 +379,15 @@ This argument is `intent(in)`.
381379
`b`: Shall be a `real/complex` scalar/array.
382380
This argument is `intent(in)`.
383381

384-
`rtol`: Shall be a `real` scalar.
385-
This argument is `intent(in)` and `optional`, which is `1.0e-5` by default.
382+
`rel_tol`: Shall be a `real` scalar.
383+
This argument is `intent(in)` and `optional`, which is `1.0e-9` by default.
386384

387-
`atol`: Shall be a `real` scalar.
388-
This argument is `intent(in)` and `optional`, which is `1.0e-8` by default.
385+
`abs_tol`: Shall be a `real` scalar.
386+
This argument is `intent(in)` and `optional`, which is `0.0` by default.
389387

390-
Note: All `real/complex` arguments must have same `kind`.
391-
If the value of `rtol/atol` is negative (not recommended), it will be corrected to `abs(rtol/atol)` by the internal process of `is_close`.
388+
Note: All `real/complex` arguments must have same `kind`.
389+
If the value of `rel_tol/abs_tol` is negative (not recommended),
390+
it will be corrected to `abs(rel_tol/abs_tol)` by the internal process of `is_close`.
392391

393392
#### Result value
394393

@@ -398,11 +397,11 @@ Returns a `logical` scalar/array.
398397

399398
```fortran
400399
program demo_math_is_close
401-
use stdlib_math, only: is_close
400+
use stdlib_math, only: is_close
402401
use stdlib_error, only: check
403402
real :: x(2) = [1, 2]
404-
print *, is_close(x,[real :: 1, 2.1]) !! [T, F]
405-
print *, is_close(2.0, 2.1, atol=0.1) !! T
403+
print *, is_close(x,[real :: 1, 2.1]) !! [T, F]
404+
print *, is_close(2.0, 2.1, abs_tol=0.1) !! T
406405
call check(all(is_close(x, [2.0, 2.0])), msg="all(is_close(x, [2.0, 2.0])) failed.", warn=.true.)
407406
!! all(is_close(x, [2.0, 2.0])) failed.
408407
end program demo_math_is_close

src/stdlib_math.fypp

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -286,10 +286,10 @@ module stdlib_math
286286
interface is_close
287287
#:set RC_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES
288288
#:for k1, t1 in RC_KINDS_TYPES
289-
elemental module function is_close_${t1[0]}$${k1}$(a, b, rtol, atol) result(result)
289+
elemental module function is_close_${t1[0]}$${k1}$(a, b, rel_tol, abs_tol) result(close)
290290
${t1}$, intent(in) :: a, b
291-
real(${k1}$), intent(in), optional :: rtol, atol
292-
logical :: result
291+
real(${k1}$), intent(in), optional :: rel_tol, abs_tol
292+
logical :: close
293293
end function is_close_${t1[0]}$${k1}$
294294
#:endfor
295295
end interface is_close

src/stdlib_math_is_close.fypp

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -7,25 +7,25 @@ contains
77
#! Determines whether the values of `a` and `b` are close.
88

99
#:for k1, t1 in REAL_KINDS_TYPES
10-
elemental module function is_close_${t1[0]}$${k1}$(a, b, rtol, atol) result(result)
10+
elemental module function is_close_${t1[0]}$${k1}$(a, b, rel_tol, abs_tol) result(close)
1111
${t1}$, intent(in) :: a, b
12-
real(${k1}$), intent(in), optional :: rtol, atol
13-
logical :: result
12+
real(${k1}$), intent(in), optional :: rel_tol, abs_tol
13+
logical :: close
1414

15-
result = abs(a - b) <= abs(optval(rtol, 1.0e-5_${k1}$)*b) + &
16-
abs(optval(atol, 1.0e-8_${k1}$))
15+
close = abs(a - b) <= max( abs(optval(rel_tol, 1.0e-9_${k1}$)*max(abs(a), abs(b))), &
16+
abs(optval(abs_tol, 0.0_${k1}$)) )
1717

1818
end function is_close_${t1[0]}$${k1}$
1919
#:endfor
2020

2121
#:for k1, t1 in CMPLX_KINDS_TYPES
22-
elemental module function is_close_${t1[0]}$${k1}$(a, b, rtol, atol) result(result)
22+
elemental module function is_close_${t1[0]}$${k1}$(a, b, rel_tol, abs_tol) result(close)
2323
${t1}$, intent(in) :: a, b
24-
real(${k1}$), intent(in), optional :: rtol, atol
25-
logical :: result
24+
real(${k1}$), intent(in), optional :: rel_tol, abs_tol
25+
logical :: close
2626

27-
result = is_close_r${k1}$(a%re, b%re, rtol, atol) .and. &
28-
is_close_r${k1}$(a%im, b%im, rtol, atol)
27+
close = is_close_r${k1}$(a%re, b%re, rel_tol, abs_tol) .and. &
28+
is_close_r${k1}$(a%im, b%im, rel_tol, abs_tol)
2929

3030
end function is_close_${t1[0]}$${k1}$
3131
#:endfor

src/tests/math/test_math_is_close.f90

Lines changed: 17 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -10,30 +10,36 @@ subroutine test_math_is_close_real
1010
use stdlib_math, only: is_close
1111
use stdlib_error, only: check
1212

13-
call check(is_close(2.5, 2.5, rtol=1.0e-5), msg="is_close(2.5, 2.5, rtol=1.0e-5) failed.")
14-
call check(all(is_close([2.5, 3.2], [2.5, 10.0], rtol=1.0e-5)), &
15-
msg="all(is_close([2.5, 3.2], [2.5, 10.0], rtol=1.0e-5)) failed (expected).", warn=.true.)
13+
call check(is_close(2.5, 2.5, rel_tol=1.0e-5), msg="is_close(2.5, 2.5, rel_tol=1.0e-5) failed.")
14+
call check(all(is_close([2.5, 3.2], [2.5, 10.0], rel_tol=1.0e-5)), &
15+
msg="all(is_close([2.5, 3.2], [2.5, 10.0], rel_tol=1.0e-5)) failed (expected).", warn=.true.)
1616
call check(all(is_close(reshape([2.5, 3.2, 2.2, 1.0], [2, 2]), reshape([2.5, 3.2001, 2.25, 1.1], [2, 2]), &
17-
atol=1.0e-5, rtol=0.1)), &
17+
abs_tol=1.0e-5, rel_tol=0.1)), &
1818
msg="all(is_close(reshape([2.5, 3.2, 2.2, 1.0],[2,2]), reshape([2.5, 3.2001, 2.25, 1.1],[2,2]), &
19-
&rtol=1.0e-5, atol=0.1)) failed.")
19+
&rel_tol=1.0e-5, abs_tol=0.1)) failed.")
20+
21+
!> Tests for zeros
22+
call check(is_close(0.0, -0.0), msg="is_close(0.0, -0.0) failed.")
2023

2124
end subroutine test_math_is_close_real
2225

2326
subroutine test_math_is_close_complex
2427
use stdlib_math, only: is_close
2528
use stdlib_error, only: check
2629

27-
call check(is_close((2.5,1.2), (2.5,1.2), rtol=1.0e-5), &
28-
msg="is_close((2.5,1.2), (2.5,1.2), rtol=1.0e-5) failed.")
29-
call check(all(is_close([(2.5,1.2), (3.2,1.2)], [(2.5,1.2), (10.0,1.2)], rtol=1.0e-5)), &
30-
msg="all(is_close([(2.5,1.2), (3.2,1.2)], [(2.5,1.2), (10.0,1.2)], rtol=1.0e-5)) failed (expected).", &
30+
call check(is_close((2.5,1.2), (2.5,1.2), rel_tol=1.0e-5), &
31+
msg="is_close((2.5,1.2), (2.5,1.2), rel_tol=1.0e-5) failed.")
32+
call check(all(is_close([(2.5,1.2), (3.2,1.2)], [(2.5,1.2), (10.0,1.2)], rel_tol=1.0e-5)), &
33+
msg="all(is_close([(2.5,1.2), (3.2,1.2)], [(2.5,1.2), (10.0,1.2)], rel_tol=1.0e-5)) failed (expected).", &
3134
warn=.true.)
3235
call check(all(is_close(reshape([(2.5,1.2009), (3.2,1.199999)], [1, 2]), reshape([(2.4,1.2009), (3.15,1.199999)], [1, 2]), &
33-
atol=1.0e-5, rtol=0.1)), &
36+
abs_tol=1.0e-5, rel_tol=0.1)), &
3437
msg="all(is_close(reshape([(2.5,1.2009), (3.2,1.199999)], [1, 2]), &
3538
&reshape([(2.4,1.2009), (3.15,1.199999)], [1, 2]), &
36-
&rtol=1.0e-5, atol=0.1)) failed.")
39+
&rel_tol=1.0e-5, abs_tol=0.1)) failed.")
40+
41+
!> Tests for zeros
42+
call check(is_close((0.0, -0.0), (-0.0, 0.0)), msg="is_close((0.0, -0.0), (-0.0, 0.0)) failed.")
3743

3844
end subroutine test_math_is_close_complex
3945

0 commit comments

Comments
 (0)