Skip to content

Commit fd9fe6a

Browse files
committed
Deploying to stdlib-fpm from @ 01b3fb9 🚀
1 parent 08d0d07 commit fd9fe6a

File tree

1 file changed

+82
-1
lines changed

1 file changed

+82
-1
lines changed

src/stdlib_math.f90

Lines changed: 82 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ module stdlib_math
88
public :: clip, gcd, linspace, logspace
99
public :: EULERS_NUMBER_SP, EULERS_NUMBER_DP
1010
public :: DEFAULT_LINSPACE_LENGTH, DEFAULT_LOGSPACE_BASE, DEFAULT_LOGSPACE_LENGTH
11-
public :: arange, is_close, all_close
11+
public :: arange, arg, argd, argpi, is_close, all_close
1212

1313
integer, parameter :: DEFAULT_LINSPACE_LENGTH = 100
1414
integer, parameter :: DEFAULT_LOGSPACE_LENGTH = 50
@@ -18,6 +18,10 @@ module stdlib_math
1818
real(sp), parameter :: EULERS_NUMBER_SP = exp(1.0_sp)
1919
real(dp), parameter :: EULERS_NUMBER_DP = exp(1.0_dp)
2020

21+
!> Useful constants `PI` for `argd/argpi`
22+
real(kind=sp), parameter :: PI_sp = acos(-1.0_sp)
23+
real(kind=dp), parameter :: PI_dp = acos(-1.0_dp)
24+
2125
interface clip
2226
module procedure clip_int8
2327
module procedure clip_int16
@@ -456,6 +460,31 @@ end function arange_i_int64
456460

457461
!> Version: experimental
458462
!>
463+
!> `arg` computes the phase angle in the interval (-π,π].
464+
!> ([Specification](../page/specs/stdlib_math.html#arg))
465+
interface arg
466+
procedure :: arg_sp
467+
procedure :: arg_dp
468+
end interface arg
469+
470+
!> Version: experimental
471+
!>
472+
!> `argd` computes the phase angle of degree version in the interval (-180.0,180.0].
473+
!> ([Specification](../page/specs/stdlib_math.html#argd))
474+
interface argd
475+
procedure :: argd_sp
476+
procedure :: argd_dp
477+
end interface argd
478+
479+
!> Version: experimental
480+
!>
481+
!> `argpi` computes the phase angle of circular version in the interval (-1.0,1.0].
482+
!> ([Specification](../page/specs/stdlib_math.html#argpi))
483+
interface argpi
484+
procedure :: argpi_sp
485+
procedure :: argpi_dp
486+
end interface argpi
487+
459488
!> Returns a boolean scalar/array where two scalar/arrays are element-wise equal within a tolerance.
460489
!> ([Specification](../page/specs/stdlib_math.html#is_close))
461490
interface is_close
@@ -625,6 +654,57 @@ elemental function clip_dp(x, xmin, xmax) result(res)
625654
end function clip_dp
626655

627656

657+
elemental function arg_sp(z) result(result)
658+
complex(sp), intent(in) :: z
659+
real(sp) :: result
660+
661+
result = merge(0.0_sp, atan2(z%im, z%re), z == (0.0_sp, 0.0_sp))
662+
663+
end function arg_sp
664+
665+
elemental function argd_sp(z) result(result)
666+
complex(sp), intent(in) :: z
667+
real(sp) :: result
668+
669+
result = merge(0.0_sp, atan2(z%im, z%re), z == (0.0_sp, 0.0_sp)) &
670+
*180.0_sp/PI_sp
671+
672+
end function argd_sp
673+
674+
elemental function argpi_sp(z) result(result)
675+
complex(sp), intent(in) :: z
676+
real(sp) :: result
677+
678+
result = merge(0.0_sp, atan2(z%im, z%re), z == (0.0_sp, 0.0_sp)) &
679+
/PI_sp
680+
681+
end function argpi_sp
682+
elemental function arg_dp(z) result(result)
683+
complex(dp), intent(in) :: z
684+
real(dp) :: result
685+
686+
result = merge(0.0_dp, atan2(z%im, z%re), z == (0.0_dp, 0.0_dp))
687+
688+
end function arg_dp
689+
690+
elemental function argd_dp(z) result(result)
691+
complex(dp), intent(in) :: z
692+
real(dp) :: result
693+
694+
result = merge(0.0_dp, atan2(z%im, z%re), z == (0.0_dp, 0.0_dp)) &
695+
*180.0_dp/PI_dp
696+
697+
end function argd_dp
698+
699+
elemental function argpi_dp(z) result(result)
700+
complex(dp), intent(in) :: z
701+
real(dp) :: result
702+
703+
result = merge(0.0_dp, atan2(z%im, z%re), z == (0.0_dp, 0.0_dp)) &
704+
/PI_dp
705+
706+
end function argpi_dp
707+
628708
!> Returns the greatest common divisor of two integers of kind int8
629709
!> using the Euclidean algorithm.
630710
elemental function gcd_int8(a, b) result(res)
@@ -697,4 +777,5 @@ elemental function gcd_int64(a, b) result(res)
697777
end do
698778
end function gcd_int64
699779

780+
700781
end module stdlib_math

0 commit comments

Comments
 (0)