44
55module test_stdlib_math
66 use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
7- use stdlib_math, only: clip, is_close, all_close
7+ use stdlib_math, only: clip, arg, argd, argpi, arange, is_close, all_close
88 use stdlib_kinds, only: int8, int16, int32, int64, sp, dp, xdp, qp
99 implicit none
1010
1111 public :: collect_stdlib_math
12+
13+ #:for k1 in REAL_KINDS
14+ real(kind=${k1}$), parameter :: PI_${k1}$ = acos(-1.0_${k1}$)
15+ #:endfor
1216
1317contains
1418
@@ -33,6 +37,13 @@ contains
3337 new_unittest("clip-real-quad", test_clip_rqp), &
3438 new_unittest("clip-real-quad-bounds", test_clip_rqp_bounds) &
3539
40+ !> Tests for arg/argd/argpi
41+ #:for k1 in CMPLX_KINDS
42+ , new_unittest("arg-cmplx-${k1}$", test_arg_${k1}$) &
43+ , new_unittest("argd-cmplx-${k1}$", test_argd_${k1}$) &
44+ , new_unittest("argpi-cmplx-${k1}$", test_argpi_${k1}$) &
45+ #:endfor
46+
3647 !> Tests for `is_close` and `all_close`
3748 #:for k1 in REAL_KINDS
3849 , new_unittest("is_close-real-${k1}$", test_is_close_real_${k1}$) &
@@ -211,7 +222,66 @@ contains
211222#:endif
212223
213224 end subroutine test_clip_rqp_bounds
225+
226+ #:for k1 in CMPLX_KINDS
227+ subroutine test_arg_${k1}$(error)
228+ type(error_type), allocatable, intent(out) :: error
229+ real(${k1}$), parameter :: tol = sqrt(epsilon(1.0_${k1}$))
230+ real(${k1}$), allocatable :: theta(:)
231+
232+ #! For scalar
233+ call check(error, abs(arg(2*exp((0.0_${k1}$, 0.5_${k1}$))) - 0.5_${k1}$) < tol, &
234+ "test_nonzero_scalar")
235+ if (allocated(error)) return
236+ call check(error, abs(arg((0.0_${k1}$, 0.0_${k1}$)) - 0.0_${k1}$) < tol, &
237+ "test_zero_scalar")
238+
239+ #! and for array (180.0° see scalar version)
240+ theta = arange(-179.0_${k1}$, 179.0_${k1}$, 3.58_${k1}$)
241+ call check(error, all(abs(arg(exp(cmplx(0.0_${k1}$, theta/180*PI_${k1}$, ${k1}$))) - theta/180*PI_${k1}$) < tol), &
242+ "test_array")
243+
244+ end subroutine test_arg_${k1}$
245+
246+ subroutine test_argd_${k1}$(error)
247+ type(error_type), allocatable, intent(out) :: error
248+ real(${k1}$), parameter :: tol = sqrt(epsilon(1.0_${k1}$))
249+ real(${k1}$), allocatable :: theta(:)
250+
251+ #! For scalar
252+ call check(error, abs(argd((-1.0_${k1}$, 0.0_${k1}$)) - 180.0_${k1}$) < tol, &
253+ "test_nonzero_scalar")
254+ if (allocated(error)) return
255+ call check(error, abs(argd((0.0_${k1}$, 0.0_${k1}$)) - 0.0_${k1}$) < tol, &
256+ "test_zero_scalar")
257+
258+ #! and for array (180.0° see scalar version)
259+ theta = arange(-179.0_${k1}$, 179.0_${k1}$, 3.58_${k1}$)
260+ call check(error, all(abs(argd(exp(cmplx(0.0_${k1}$, theta/180*PI_${k1}$, ${k1}$))) - theta) < tol), &
261+ "test_array")
262+
263+ end subroutine test_argd_${k1}$
214264
265+ subroutine test_argpi_${k1}$(error)
266+ type(error_type), allocatable, intent(out) :: error
267+ real(${k1}$), parameter :: tol = sqrt(epsilon(1.0_${k1}$))
268+ real(${k1}$), allocatable :: theta(:)
269+
270+ #! For scalar
271+ call check(error, abs(argpi((-1.0_${k1}$, 0.0_${k1}$)) - 1.0_${k1}$) < tol, &
272+ "test_nonzero_scalar")
273+ if (allocated(error)) return
274+ call check(error, abs(argpi((0.0_${k1}$, 0.0_${k1}$)) - 0.0_${k1}$) < tol, &
275+ "test_zero_scalar")
276+
277+ #! and for array (180.0° see scalar version)
278+ theta = arange(-179.0_${k1}$, 179.0_${k1}$, 3.58_${k1}$)
279+ call check(error, all(abs(argpi(exp(cmplx(0.0_${k1}$, theta/180*PI_${k1}$, ${k1}$))) - theta/180) < tol), &
280+ "test_array")
281+
282+ end subroutine test_argpi_${k1}$
283+ #:endfor
284+
215285 #:for k1 in REAL_KINDS
216286 subroutine test_is_close_real_${k1}$(error)
217287 type(error_type), allocatable, intent(out) :: error
0 commit comments