Skip to content

Commit 2e30c5a

Browse files
committed
Add tests for conversion function degree to radia.
1 parent 1a2b1d8 commit 2e30c5a

File tree

1 file changed

+23
-1
lines changed

1 file changed

+23
-1
lines changed

test/math/test_stdlib_math.fypp

Lines changed: 23 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@
55
module test_stdlib_math
66
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
77
use stdlib_math, only: clip, arg, argd, argpi, arange, is_close, all_close, diff, &
8-
arange
8+
arange, deg2rad, rad2deg
99
use stdlib_kinds, only: int8, int16, int32, int64, sp, dp, xdp, qp
1010
implicit none
1111

@@ -45,6 +45,12 @@ contains
4545
, new_unittest("argpi-cmplx-${k1}$", test_argpi_${k1}$) &
4646
#:endfor
4747

48+
!> Tests for deg2rad/rad2deg
49+
#:for k1 in REAL_KINDS
50+
, new_unittest("deg2rad-${k1}$", test_deg2rad_${k1}$) &
51+
, new_unittest("rad2deg-${k1}$", test_rad2deg_${k1}$) &
52+
#:endfor
53+
4854
!> Tests for `is_close` and `all_close`
4955
#:for k1 in REAL_KINDS
5056
, new_unittest("is_close-real-${k1}$", test_is_close_real_${k1}$) &
@@ -301,6 +307,22 @@ contains
301307

302308
end subroutine test_argpi_${k1}$
303309
#:endfor
310+
311+
#:for k1 in REAL_KINDS
312+
subroutine test_deg2rad_${k1}$(error)
313+
type(error_type), allocatable, intent(out) :: error
314+
real(${k1}$), parameter :: tol = sqrt(epsilon(1.0_${k1}$))
315+
call check(error, PI_${k1}$, deg2rad(180.0_${k1}$), thr=tol)
316+
if (allocated(error)) return
317+
end subroutine test_deg2rad_${k1}$
318+
319+
subroutine test_rad2deg_${k1}$(error)
320+
type(error_type), allocatable, intent(out) :: error
321+
real(${k1}$), parameter :: tol = sqrt(epsilon(1.0_${k1}$))
322+
call check(error, 180.0_${k1}$, rad2deg(PI_${k1}$))
323+
if (allocated(error)) return
324+
end subroutine test_rad2deg_${k1}$
325+
#:endfor
304326

305327
#:for k1 in REAL_KINDS
306328
subroutine test_is_close_real_${k1}$(error)

0 commit comments

Comments
 (0)