Skip to content

Commit 59509b1

Browse files
authored
Merge pull request #845 from MilanSkocic/master
Conversion functions from degrees to radians and vice-versa.
2 parents 70d34a4 + 5476cdc commit 59509b1

File tree

6 files changed

+147
-2
lines changed

6 files changed

+147
-2
lines changed

Diff for: doc/specs/stdlib_math.md

+64
Original file line numberDiff line numberDiff line change
@@ -382,6 +382,70 @@ Notes: Although the angle of the complex number `0` is undefined, `argpi((0,0))`
382382
{!example/math/example_math_argpi.f90!}
383383
```
384384

385+
### `deg2rad`
386+
387+
#### Status
388+
389+
Experimental
390+
391+
#### Class
392+
393+
Elemenal function.
394+
395+
### Description
396+
397+
`deg2rad` converts phase angles from degrees to radians.
398+
399+
#### Syntax
400+
401+
`result = ` [[stdlib_math(module):deg2rad(interface)]] `(theta)`
402+
403+
#### Arguments
404+
405+
`theta`: Shall be a `real` scalar/array.
406+
407+
#### Return value
408+
409+
Returns the `real` phase angle in radians.
410+
411+
#### Example
412+
413+
```fortran
414+
{!example/math/example_math_deg2rad.f90!}
415+
```
416+
417+
### `rad2deg`
418+
419+
#### Status
420+
421+
Experimental
422+
423+
#### Class
424+
425+
Elemenal function.
426+
427+
### Description
428+
429+
`rad2deg` converts phase angles from radians to degrees.
430+
431+
#### Syntax
432+
433+
`result = ` [[stdlib_math(module):rad2deg(interface)]] `(theta)`
434+
435+
#### Arguments
436+
437+
`theta`: Shall be a `real` scalar/array.
438+
439+
#### Return value
440+
441+
Returns the `real` phase angle in degrees.
442+
443+
#### Example
444+
445+
```fortran
446+
{!example/math/example_math_rad2deg.f90!}
447+
```
448+
385449
### `is_close` function
386450

387451
#### Description

Diff for: example/math/CMakeLists.txt

+2
Original file line numberDiff line numberDiff line change
@@ -12,5 +12,7 @@ ADD_EXAMPLE(math_arange)
1212
ADD_EXAMPLE(math_argd)
1313
ADD_EXAMPLE(math_arg)
1414
ADD_EXAMPLE(math_argpi)
15+
ADD_EXAMPLE(math_deg2rad)
16+
ADD_EXAMPLE(math_rad2deg)
1517
ADD_EXAMPLE(math_is_close)
1618
ADD_EXAMPLE(meshgrid)

Diff for: example/math/example_math_deg2rad.f90

+8
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
program example_math_deg2rad
2+
use stdlib_math, only: deg2rad
3+
implicit none
4+
print *, deg2rad(0.0) ! 0.0
5+
print *, deg2rad(90.0) ! 1.57508
6+
print *, deg2rad(-180.0) ! -3.1416
7+
8+
end program example_math_deg2rad

Diff for: example/math/example_math_rad2deg.f90

+9
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
program example_math_rad2deg
2+
use stdlib_math, only: rad2deg
3+
use stdlib_constants, only: PI_sp
4+
implicit none
5+
print *, rad2deg(0.0) ! 0.0
6+
print *, rad2deg(PI_sp / 2.0) ! 90.0
7+
print *, rad2deg(-PI_sp) ! -3.1416
8+
9+
end program example_math_rad2deg

Diff for: src/stdlib_math.fypp

+37-1
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ module stdlib_math
1515
#:endif
1616
public :: DEFAULT_LINSPACE_LENGTH, DEFAULT_LOGSPACE_BASE, DEFAULT_LOGSPACE_LENGTH
1717
public :: stdlib_meshgrid_ij, stdlib_meshgrid_xy
18-
public :: arange, arg, argd, argpi, is_close, all_close, diff, meshgrid
18+
public :: arange, arg, argd, argpi, deg2rad, rad2deg, is_close, all_close, diff, meshgrid
1919

2020
integer, parameter :: DEFAULT_LINSPACE_LENGTH = 100
2121
integer, parameter :: DEFAULT_LOGSPACE_LENGTH = 50
@@ -332,6 +332,26 @@ module stdlib_math
332332
procedure :: argpi_${k1}$
333333
#:endfor
334334
end interface argpi
335+
336+
!> Version: experimental
337+
!>
338+
!> `deg2rad` converts phase angles from degrees to radians.
339+
!> ([Specification](../page/specs/stdlib_math.html#deg2rad-function))
340+
interface deg2rad
341+
#:for k1 in REAL_KINDS
342+
procedure :: deg2rad_${k1}$
343+
#:endfor
344+
end interface deg2rad
345+
346+
!> Version: experimental
347+
!>
348+
!> `rad2deg` converts phase angles from radians to degrees.
349+
!> ([Specification](../page/specs/stdlib_math.html#rad2deg-function))
350+
interface rad2deg
351+
#:for k1 in REAL_KINDS
352+
procedure :: rad2deg_${k1}$
353+
#:endfor
354+
end interface rad2deg
335355

336356
!> Returns a boolean scalar/array where two scalar/arrays are element-wise equal within a tolerance.
337357
!> ([Specification](../page/specs/stdlib_math.html#is_close-function))
@@ -453,6 +473,22 @@ contains
453473
end function argpi_${k1}$
454474
#:endfor
455475

476+
#:for k1, t1 in REAL_KINDS_TYPES
477+
elemental function deg2rad_${k1}$(theta) result(result)
478+
${t1}$, intent(in) :: theta
479+
${t1}$ :: result
480+
result = theta * PI_${k1}$ / 180.0_${k1}$
481+
482+
end function deg2rad_${k1}$
483+
484+
elemental function rad2deg_${k1}$(theta) result(result)
485+
${t1}$, intent(in) :: theta
486+
${t1}$ :: result
487+
result = theta * 180.0_${k1}$ / PI_${k1}$
488+
489+
end function rad2deg_${k1}$
490+
#:endfor
491+
456492
#:for k1, t1 in INT_KINDS_TYPES
457493
!> Returns the greatest common divisor of two integers of kind ${k1}$
458494
!> using the Euclidean algorithm.

Diff for: test/math/test_stdlib_math.fypp

+27-1
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@
55
module test_stdlib_math
66
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
77
use stdlib_math, only: clip, arg, argd, argpi, arange, is_close, all_close, diff, &
8-
arange
8+
arange, deg2rad, rad2deg
99
use stdlib_kinds, only: int8, int16, int32, int64, sp, dp, xdp, qp
1010
implicit none
1111

@@ -45,6 +45,12 @@ contains
4545
, new_unittest("argpi-cmplx-${k1}$", test_argpi_${k1}$) &
4646
#:endfor
4747

48+
!> Tests for deg2rad/rad2deg
49+
#:for k1 in REAL_KINDS
50+
, new_unittest("deg2rad-real-${k1}$", test_deg2rad_${k1}$) &
51+
, new_unittest("rad2deg-real-${k1}$", test_rad2deg_${k1}$) &
52+
#:endfor
53+
4854
!> Tests for `is_close` and `all_close`
4955
#:for k1 in REAL_KINDS
5056
, new_unittest("is_close-real-${k1}$", test_is_close_real_${k1}$) &
@@ -301,6 +307,26 @@ contains
301307

302308
end subroutine test_argpi_${k1}$
303309
#:endfor
310+
311+
#:for k1 in REAL_KINDS
312+
subroutine test_deg2rad_${k1}$(error)
313+
type(error_type), allocatable, intent(out) :: error
314+
real(${k1}$), parameter :: tol = sqrt(epsilon(1.0_${k1}$))
315+
316+
call check(error, PI_${k1}$, deg2rad(180.0_${k1}$), thr=tol)
317+
if (allocated(error)) return
318+
319+
end subroutine test_deg2rad_${k1}$
320+
321+
subroutine test_rad2deg_${k1}$(error)
322+
type(error_type), allocatable, intent(out) :: error
323+
real(${k1}$), parameter :: tol = sqrt(epsilon(1.0_${k1}$))
324+
325+
call check(error, 180.0_${k1}$, rad2deg(PI_${k1}$), thr=tol)
326+
if (allocated(error)) return
327+
328+
end subroutine test_rad2deg_${k1}$
329+
#:endfor
304330

305331
#:for k1 in REAL_KINDS
306332
subroutine test_is_close_real_${k1}$(error)

0 commit comments

Comments
 (0)