4
4
5
5
module test_stdlib_math
6
6
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
7
- use stdlib_math, only: clip, is_close, all_close, diff
7
+ use stdlib_math, only: clip, arg, argd, argpi, arange, is_close, all_close, diff
8
8
use stdlib_kinds, only: int8, int16, int32, int64, sp, dp, xdp, qp
9
9
implicit none
10
10
11
11
public :: collect_stdlib_math
12
+
13
+ #:for k1 in REAL_KINDS
14
+ real(kind=${k1}$), parameter :: PI_${k1}$ = acos(-1.0_${k1}$)
15
+ #:endfor
12
16
13
17
contains
14
18
@@ -33,6 +37,13 @@ contains
33
37
new_unittest("clip-real-quad", test_clip_rqp), &
34
38
new_unittest("clip-real-quad-bounds", test_clip_rqp_bounds) &
35
39
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
+
36
47
!> Tests for `is_close` and `all_close`
37
48
#:for k1 in REAL_KINDS
38
49
, new_unittest("is_close-real-${k1}$", test_is_close_real_${k1}$) &
@@ -219,7 +230,66 @@ contains
219
230
#:endif
220
231
221
232
end subroutine test_clip_rqp_bounds
233
+
234
+ #:for k1 in CMPLX_KINDS
235
+ subroutine test_arg_${k1}$(error)
236
+ type(error_type), allocatable, intent(out) :: error
237
+ real(${k1}$), parameter :: tol = sqrt(epsilon(1.0_${k1}$))
238
+ real(${k1}$), allocatable :: theta(:)
239
+
240
+ #! For scalar
241
+ call check(error, abs(arg(2*exp((0.0_${k1}$, 0.5_${k1}$))) - 0.5_${k1}$) < tol, &
242
+ "test_nonzero_scalar")
243
+ if (allocated(error)) return
244
+ call check(error, abs(arg((0.0_${k1}$, 0.0_${k1}$)) - 0.0_${k1}$) < tol, &
245
+ "test_zero_scalar")
246
+
247
+ #! and for array (180.0° see scalar version)
248
+ theta = arange(-179.0_${k1}$, 179.0_${k1}$, 3.58_${k1}$)
249
+ call check(error, all(abs(arg(exp(cmplx(0.0_${k1}$, theta/180*PI_${k1}$, ${k1}$))) - theta/180*PI_${k1}$) < tol), &
250
+ "test_array")
251
+
252
+ end subroutine test_arg_${k1}$
253
+
254
+ subroutine test_argd_${k1}$(error)
255
+ type(error_type), allocatable, intent(out) :: error
256
+ real(${k1}$), parameter :: tol = sqrt(epsilon(1.0_${k1}$))
257
+ real(${k1}$), allocatable :: theta(:)
258
+
259
+ #! For scalar
260
+ call check(error, abs(argd((-1.0_${k1}$, 0.0_${k1}$)) - 180.0_${k1}$) < tol, &
261
+ "test_nonzero_scalar")
262
+ if (allocated(error)) return
263
+ call check(error, abs(argd((0.0_${k1}$, 0.0_${k1}$)) - 0.0_${k1}$) < tol, &
264
+ "test_zero_scalar")
265
+
266
+ #! and for array (180.0° see scalar version)
267
+ theta = arange(-179.0_${k1}$, 179.0_${k1}$, 3.58_${k1}$)
268
+ call check(error, all(abs(argd(exp(cmplx(0.0_${k1}$, theta/180*PI_${k1}$, ${k1}$))) - theta) < tol), &
269
+ "test_array")
270
+
271
+ end subroutine test_argd_${k1}$
222
272
273
+ subroutine test_argpi_${k1}$(error)
274
+ type(error_type), allocatable, intent(out) :: error
275
+ real(${k1}$), parameter :: tol = sqrt(epsilon(1.0_${k1}$))
276
+ real(${k1}$), allocatable :: theta(:)
277
+
278
+ #! For scalar
279
+ call check(error, abs(argpi((-1.0_${k1}$, 0.0_${k1}$)) - 1.0_${k1}$) < tol, &
280
+ "test_nonzero_scalar")
281
+ if (allocated(error)) return
282
+ call check(error, abs(argpi((0.0_${k1}$, 0.0_${k1}$)) - 0.0_${k1}$) < tol, &
283
+ "test_zero_scalar")
284
+
285
+ #! and for array (180.0° see scalar version)
286
+ theta = arange(-179.0_${k1}$, 179.0_${k1}$, 3.58_${k1}$)
287
+ call check(error, all(abs(argpi(exp(cmplx(0.0_${k1}$, theta/180*PI_${k1}$, ${k1}$))) - theta/180) < tol), &
288
+ "test_array")
289
+
290
+ end subroutine test_argpi_${k1}$
291
+ #:endfor
292
+
223
293
#:for k1 in REAL_KINDS
224
294
subroutine test_is_close_real_${k1}$(error)
225
295
type(error_type), allocatable, intent(out) :: error
0 commit comments