Skip to content

Commit b6f0ab1

Browse files
committed
Merge branch 'master' of https://github.com/fortran-lang/stdlib into add_diff
2 parents 2827e9a + 01b3fb9 commit b6f0ab1

File tree

5 files changed

+261
-6
lines changed

5 files changed

+261
-6
lines changed

CHANGELOG.md

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,10 @@ Features available from the latest git source
1717
[#581](https://github.com/fortran-lang/stdlib/pull/581)
1818
- new procedures `save_npy`, `load_npy`
1919
- update module `stdlib_math`
20+
- new procedures `is_close` and `all_close`
21+
[#488](https://github.com/fortran-lang/stdlib/pull/488)
22+
- new procedures `arg`, `argd` and `argpi`
23+
[#498](https://github.com/fortran-lang/stdlib/pull/498)
2024
- new procedure `diff`
2125

2226
Changes to existing modules

doc/specs/stdlib_math.md

Lines changed: 123 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -389,6 +389,129 @@ program demo_math_arange
389389
end program demo_math_arange
390390
```
391391

392+
### `arg` - Computes the phase angle in radian of a complex scalar
393+
394+
#### Status
395+
396+
Experimental
397+
398+
#### Class
399+
400+
Elemental function.
401+
402+
#### Description
403+
404+
`arg` computes the phase angle (radian version) of `complex` scalar in the interval (-π,π].
405+
The angles in `θ` are such that `z = abs(z)*exp((0.0, θ))`.
406+
407+
#### Syntax
408+
409+
`result = [[stdlib_math(module):arg(interface)]](z)`
410+
411+
#### Arguments
412+
413+
`z`: Shall be a `complex` scalar/array.
414+
This is an `intent(in)` argument.
415+
416+
#### Return value
417+
418+
Returns the `real` type phase angle (radian version) of the `complex` argument `z`.
419+
420+
Notes: Although the angle of the complex number `0` is undefined, `arg((0,0))` returns the value `0`.
421+
422+
#### Example
423+
424+
```fortran
425+
program demo_math_arg
426+
use stdlib_math, only: arg
427+
print *, arg((0.0, 0.0)) !! 0.0
428+
print *, arg((3.0, 4.0)) !! 0.927
429+
print *, arg(2.0*exp((0.0, 0.5))) !! 0.5
430+
end program demo_math_arg
431+
```
432+
433+
### `argd` - Computes the phase angle in degree of a complex scalar
434+
435+
#### Status
436+
437+
Experimental
438+
439+
#### Class
440+
441+
Elemental function.
442+
443+
#### Description
444+
445+
`argd` computes the phase angle (degree version) of `complex` scalar in the interval (-180.0,180.0].
446+
The angles in `θ` are such that `z = abs(z)*exp((0.0, θ*π/180.0))`.
447+
448+
#### Syntax
449+
450+
`result = [[stdlib_math(module):argd(interface)]](z)`
451+
452+
#### Arguments
453+
454+
`z`: Shall be a `complex` scalar/array.
455+
This is an `intent(in)` argument.
456+
457+
#### Return value
458+
459+
Returns the `real` type phase angle (degree version) of the `complex` argument `z`.
460+
461+
Notes: Although the angle of the complex number `0` is undefined, `argd((0,0))` returns the value `0`.
462+
463+
#### Example
464+
465+
```fortran
466+
program demo_math_argd
467+
use stdlib_math, only: argd
468+
print *, argd((0.0, 0.0)) !! 0.0
469+
print *, argd((3.0, 4.0)) !! 53.1°
470+
print *, argd(2.0*exp((0.0, 0.5))) !! 28.64°
471+
end program demo_math_argd
472+
```
473+
474+
### `argpi` - Computes the phase angle in circular of a complex scalar
475+
476+
#### Status
477+
478+
Experimental
479+
480+
#### Class
481+
482+
Elemental function.
483+
484+
#### Description
485+
486+
`argpi` computes the phase angle (IEEE circular version) of `complex` scalar in the interval (-1.0,1.0].
487+
The angles in `θ` are such that `z = abs(z)*exp((0.0, θ*π))`.
488+
489+
#### Syntax
490+
491+
`result = [[stdlib_math(module):argpi(interface)]](z)`
492+
493+
#### Arguments
494+
495+
`z`: Shall be a `complex` scalar/array.
496+
This is an `intent(in)` argument.
497+
498+
#### Return value
499+
500+
Returns the `real` type phase angle (circular version) of the `complex` argument `z`.
501+
502+
Notes: Although the angle of the complex number `0` is undefined, `argpi((0,0))` returns the value `0`.
503+
504+
#### Example
505+
506+
```fortran
507+
program demo_math_argpi
508+
use stdlib_math, only: argpi
509+
print *, argpi((0.0, 0.0)) !! 0.0
510+
print *, argpi((3.0, 4.0)) !! 0.295
511+
print *, argpi(2.0*exp((0.0, 0.5))) !! 0.159
512+
end program demo_math_argpi
513+
```
514+
392515
### `is_close`
393516

394517
#### Description
@@ -449,7 +572,6 @@ Returns a `logical` scalar/array.
449572
program demo_math_is_close
450573
451574
use stdlib_math, only: is_close
452-
use stdlib_error, only: check
453575
real :: x(2) = [1, 2], y, NAN
454576
455577
y = -3
@@ -514,7 +636,6 @@ Returns a `logical` scalar.
514636
program demo_math_all_close
515637
516638
use stdlib_math, only: all_close
517-
use stdlib_error, only: check
518639
real :: x(2) = [1, 2], y, NAN
519640
complex :: z(4, 4)
520641

src/stdlib_math.fypp

Lines changed: 63 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -14,8 +14,7 @@ module stdlib_math
1414
public :: EULERS_NUMBER_QP
1515
#:endif
1616
public :: DEFAULT_LINSPACE_LENGTH, DEFAULT_LOGSPACE_BASE, DEFAULT_LOGSPACE_LENGTH
17-
public :: arange, is_close, all_close
18-
public :: diff
17+
public :: arange, arg, argd, argpi, is_close, all_close, diff
1918

2019
integer, parameter :: DEFAULT_LINSPACE_LENGTH = 100
2120
integer, parameter :: DEFAULT_LOGSPACE_LENGTH = 50
@@ -28,6 +27,11 @@ module stdlib_math
2827
real(qp), parameter :: EULERS_NUMBER_QP = exp(1.0_qp)
2928
#:endif
3029

30+
!> Useful constants `PI` for `argd/argpi`
31+
#:for k1 in REAL_KINDS
32+
real(kind=${k1}$), parameter :: PI_${k1}$ = acos(-1.0_${k1}$)
33+
#:endfor
34+
3135
interface clip
3236
#:for k1, t1 in IR_KINDS_TYPES
3337
module procedure clip_${k1}$
@@ -297,6 +301,34 @@ module stdlib_math
297301

298302
!> Version: experimental
299303
!>
304+
!> `arg` computes the phase angle in the interval (-π,π].
305+
!> ([Specification](../page/specs/stdlib_math.html#arg))
306+
interface arg
307+
#:for k1 in CMPLX_KINDS
308+
procedure :: arg_${k1}$
309+
#:endfor
310+
end interface arg
311+
312+
!> Version: experimental
313+
!>
314+
!> `argd` computes the phase angle of degree version in the interval (-180.0,180.0].
315+
!> ([Specification](../page/specs/stdlib_math.html#argd))
316+
interface argd
317+
#:for k1 in CMPLX_KINDS
318+
procedure :: argd_${k1}$
319+
#:endfor
320+
end interface argd
321+
322+
!> Version: experimental
323+
!>
324+
!> `argpi` computes the phase angle of circular version in the interval (-1.0,1.0].
325+
!> ([Specification](../page/specs/stdlib_math.html#argpi))
326+
interface argpi
327+
#:for k1 in CMPLX_KINDS
328+
procedure :: argpi_${k1}$
329+
#:endfor
330+
end interface argpi
331+
300332
!> Returns a boolean scalar/array where two scalar/arrays are element-wise equal within a tolerance.
301333
!> ([Specification](../page/specs/stdlib_math.html#is_close))
302334
interface is_close
@@ -362,6 +394,34 @@ contains
362394

363395
#:endfor
364396

397+
#:for k1, t1 in CMPLX_KINDS_TYPES
398+
elemental function arg_${k1}$(z) result(result)
399+
${t1}$, intent(in) :: z
400+
real(${k1}$) :: result
401+
402+
result = merge(0.0_${k1}$, atan2(z%im, z%re), z == (0.0_${k1}$, 0.0_${k1}$))
403+
404+
end function arg_${k1}$
405+
406+
elemental function argd_${k1}$(z) result(result)
407+
${t1}$, intent(in) :: z
408+
real(${k1}$) :: result
409+
410+
result = merge(0.0_${k1}$, atan2(z%im, z%re), z == (0.0_${k1}$, 0.0_${k1}$)) &
411+
*180.0_${k1}$/PI_${k1}$
412+
413+
end function argd_${k1}$
414+
415+
elemental function argpi_${k1}$(z) result(result)
416+
${t1}$, intent(in) :: z
417+
real(${k1}$) :: result
418+
419+
result = merge(0.0_${k1}$, atan2(z%im, z%re), z == (0.0_${k1}$, 0.0_${k1}$)) &
420+
/PI_${k1}$
421+
422+
end function argpi_${k1}$
423+
#:endfor
424+
365425
#:for k1, t1 in INT_KINDS_TYPES
366426
!> Returns the greatest common divisor of two integers of kind ${k1}$
367427
!> using the Euclidean algorithm.
@@ -382,4 +442,5 @@ contains
382442
end function gcd_${k1}$
383443

384444
#:endfor
445+
385446
end module stdlib_math

src/tests/math/Makefile.manual

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -9,5 +9,4 @@ PROGS_SRC = test_linspace.f90 test_logspace.f90 \
99
$(SRCGEN): %.f90: %.fypp ../../common.fypp
1010
fypp -I../.. $(FYPPFLAGS) $< $@
1111

12-
1312
include ../Makefile.manual.test.mk

src/tests/math/test_stdlib_math.fypp

Lines changed: 71 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,11 +4,15 @@
44

55
module 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, diff
7+
use stdlib_math, only: clip, arg, argd, argpi, arange, is_close, all_close, diff
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

1317
contains
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}$) &
@@ -219,7 +230,66 @@ contains
219230
#:endif
220231

221232
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}$
222272

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+
223293
#:for k1 in REAL_KINDS
224294
subroutine test_is_close_real_${k1}$(error)
225295
type(error_type), allocatable, intent(out) :: error

0 commit comments

Comments
 (0)