Skip to content
Prev Previous commit
Next Next commit
arg**: aimag(log(..)) -> atan2(..),
update tests.
  • Loading branch information
zoziha committed Dec 14, 2021
commit c37c0b2b75c5d0f485c83d9b753629c0b592d02c
26 changes: 10 additions & 16 deletions doc/specs/stdlib_math.md
Original file line number Diff line number Diff line change
Expand Up @@ -389,7 +389,7 @@ program demo_math_arange
end program demo_math_arange
```

## `arg`
## `arg` - Computes the phase angle in radian of a complex scalar

### Status

Expand All @@ -402,7 +402,7 @@ Elemental function.
### Description

`arg` computes the phase angle (radian version) of `complex` scalar in the interval (-π,π].
The angles in `theta` are such that `z = abs(z)*exp((0.0, theta))`.
The angles in `θ` are such that `z = abs(z)*exp((0.0, θ))`.

### Syntax

Expand All @@ -417,9 +417,7 @@ This is an `intent(in)` argument.

Returns the `real` type phase angle (radian version) of the `complex` argument `z`.

#### Notes

Although the angle of the complex number `0` is undefined, `arg((0,0))` returns the value `0`.
Notes: Although the angle of the complex number `0` is undefined, `arg((0,0))` returns the value `0`.

### Example

Expand All @@ -432,7 +430,7 @@ program demo_math_arg
end program demo_math_arg
```

## `argd`
## `argd` - Computes the phase angle in degree of a complex scalar

### Status

Expand All @@ -445,7 +443,7 @@ Elemental function.
### Description

`argd` computes the phase angle (degree version) of `complex` scalar in the interval (-180.0,180.0].
The angles in `theta` are such that `z = abs(z)*exp((0.0, theta*π/180.0))`.
The angles in `θ` are such that `z = abs(z)*exp((0.0, θ*π/180.0))`.

### Syntax

Expand All @@ -460,9 +458,7 @@ This is an `intent(in)` argument.

Returns the `real` type phase angle (degree version) of the `complex` argument `z`.

#### Notes

Although the angle of the complex number `0` is undefined, `argd((0,0))` returns the value `0`.
Notes: Although the angle of the complex number `0` is undefined, `argd((0,0))` returns the value `0`.

### Example

Expand All @@ -475,7 +471,7 @@ program demo_math_argd
end program demo_math_argd
```

## `argpi`
## `argpi` - Computes the phase angle in circular of a complex scalar

### Status

Expand All @@ -487,8 +483,8 @@ Elemental function.

### Description

`argpi` computes the phase angle (circular version) of `complex` scalar in the interval (-1.0,1.0].
The angles in `theta` are such that `z = abs(z)*exp((0.0, theta*π))`.
`argpi` computes the phase angle (IEEE circular version) of `complex` scalar in the interval (-1.0,1.0].
The angles in `θ` are such that `z = abs(z)*exp((0.0, θ*π))`.

### Syntax

Expand All @@ -503,9 +499,7 @@ This is an `intent(in)` argument.

Returns the `real` type phase angle (circular version) of the `complex` argument `z`.

#### Notes

Although the angle of the complex number `0` is undefined, `argpi((0,0))` returns the value `0`.
Notes: Although the angle of the complex number `0` is undefined, `argpi((0,0))` returns the value `0`.

### Example

Expand Down
12 changes: 7 additions & 5 deletions src/stdlib_math.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ module stdlib_math

!> Useful constants `PI` for `argd/argpi`
#:for k1 in REAL_KINDS
real(kind=${k1}$), parameter :: PI_${k1}$ = 4.0_${k1}$*atan(1.0_${k1}$)
real(kind=${k1}$), parameter :: PI_${k1}$ = acos(-1.0_${k1}$)
#:endfor

interface clip
Expand Down Expand Up @@ -321,7 +321,7 @@ module stdlib_math

!> Version: experimental
!>
!> `argpi` computes the phase angle of IEEE circular version in the interval (-1.0,1.0].
!> `argpi` computes the phase angle of circular version in the interval (-1.0,1.0].
!> ([Specification](../page/specs/stdlib_math.html#argpi))
interface argpi
#:for k1 in CMPLX_KINDS
Expand All @@ -348,23 +348,25 @@ contains
${t1}$, intent(in) :: z
real(${k1}$) :: result

result = aimag(log(z))
result = merge(0.0_${k1}$, atan2(z%im, z%re), z == (0.0_${k1}$, 0.0_${k1}$))

end function arg_${k1}$

elemental function argd_${k1}$(z) result(result)
${t1}$, intent(in) :: z
real(${k1}$) :: result

result = aimag(log(z))*180.0_${k1}$/PI_${k1}$
result = merge(0.0_${k1}$, atan2(z%im, z%re), z == (0.0_${k1}$, 0.0_${k1}$)) &
*180.0_${k1}$/PI_${k1}$

end function argd_${k1}$

elemental function argpi_${k1}$(z) result(result)
${t1}$, intent(in) :: z
real(${k1}$) :: result

result = aimag(log(z))/PI_${k1}$
result = merge(0.0_${k1}$, atan2(z%im, z%re), z == (0.0_${k1}$, 0.0_${k1}$)) &
/PI_${k1}$

end function argpi_${k1}$
#:endfor
Expand Down
45 changes: 23 additions & 22 deletions src/tests/math/test_stdlib_math.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,15 @@

module test_stdlib_math
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
use stdlib_math, only: clip, arg, argd, argpi
use stdlib_math, only: clip, arg, argd, argpi, arange
use stdlib_kinds, only: int8, int16, int32, int64, sp, dp, xdp, qp
implicit none

public :: collect_stdlib_math

#:for k1 in REAL_KINDS
real(kind=${k1}$), parameter :: PI_${k1}$ = acos(-1.0_${k1}$)
#:endfor

contains

Expand Down Expand Up @@ -214,7 +218,8 @@ contains
#:for k1 in CMPLX_KINDS
subroutine test_arg_${k1}$(error)
type(error_type), allocatable, intent(out) :: error
real(${k1}$), parameter :: tol = epsilon(1.0_${k1}$)
real(${k1}$), parameter :: tol = sqrt(epsilon(1.0_${k1}$))
real(${k1}$), allocatable :: theta(:)

#! For scalar
call check(error, abs(arg(2*exp((0.0_${k1}$, 0.5_${k1}$))) - 0.5_${k1}$) < tol, &
Expand All @@ -223,18 +228,17 @@ contains
call check(error, abs(arg((0.0_${k1}$, 0.0_${k1}$)) - 0.0_${k1}$) < tol, &
"test_zero_scalar")

#! and for array
call check(error, all(abs(arg([2*exp((0.0_${k1}$, 0.5_${k1}$))]) - [0.5_${k1}$]) < [tol]), &
"test_nonzero_array")
if (allocated(error)) return
call check(error, all(abs(arg([(0.0_${k1}$, 0.0_${k1}$)]) - [0.0_${k1}$]) < [tol]), &
"test_zero_array")
#! and for array (180.0° see scalar version)
theta = arange(-179.0_${k1}$, 179.0_${k1}$, 3.58_${k1}$)
call check(error, all(abs(arg(exp(cmplx(0.0_${k1}$, theta/180*PI_${k1}$, ${k1}$))) - theta/180*PI_${k1}$) < tol), &
"test_array")

end subroutine test_arg_${k1}$

subroutine test_argd_${k1}$(error)
type(error_type), allocatable, intent(out) :: error
real(${k1}$), parameter :: tol = epsilon(1.0_${k1}$)
real(${k1}$), parameter :: tol = sqrt(epsilon(1.0_${k1}$))
real(${k1}$), allocatable :: theta(:)

#! For scalar
call check(error, abs(argd((-1.0_${k1}$, 0.0_${k1}$)) - 180.0_${k1}$) < tol, &
Expand All @@ -243,18 +247,17 @@ contains
call check(error, abs(argd((0.0_${k1}$, 0.0_${k1}$)) - 0.0_${k1}$) < tol, &
"test_zero_scalar")

#! and for array
call check(error, all(abs(argd([(-1.0_${k1}$, 0.0_${k1}$)]) - [180.0_${k1}$]) < [tol]), &
"test_nonzero_array")
if (allocated(error)) return
call check(error, all(abs(argd([(0.0_${k1}$, 0.0_${k1}$)]) - [0.0_${k1}$]) < [tol]), &
"test_zero_array")
#! and for array (180.0° see scalar version)
theta = arange(-179.0_${k1}$, 179.0_${k1}$, 3.58_${k1}$)
call check(error, all(abs(argd(exp(cmplx(0.0_${k1}$, theta/180*PI_${k1}$, ${k1}$))) - theta) < tol), &
"test_array")

end subroutine test_argd_${k1}$

subroutine test_argpi_${k1}$(error)
type(error_type), allocatable, intent(out) :: error
real(${k1}$), parameter :: tol = epsilon(1.0_${k1}$)
real(${k1}$), parameter :: tol = sqrt(epsilon(1.0_${k1}$))
real(${k1}$), allocatable :: theta(:)

#! For scalar
call check(error, abs(argpi((-1.0_${k1}$, 0.0_${k1}$)) - 1.0_${k1}$) < tol, &
Expand All @@ -263,12 +266,10 @@ contains
call check(error, abs(argpi((0.0_${k1}$, 0.0_${k1}$)) - 0.0_${k1}$) < tol, &
"test_zero_scalar")

#! and for array
call check(error, all(abs(argpi([(-1.0_${k1}$, 0.0_${k1}$)]) - [1.0_${k1}$]) < [tol]), &
"test_nonzero_array")
if (allocated(error)) return
call check(error, all(abs(argpi([(0.0_${k1}$, 0.0_${k1}$)]) - [0.0_${k1}$]) < [tol]), &
"test_zero_array")
#! and for array (180.0° see scalar version)
theta = arange(-179.0_${k1}$, 179.0_${k1}$, 3.58_${k1}$)
call check(error, all(abs(argpi(exp(cmplx(0.0_${k1}$, theta/180*PI_${k1}$, ${k1}$))) - theta/180) < tol), &
"test_array")

end subroutine test_argpi_${k1}$
#:endfor
Expand Down