Skip to content

Commit f52ff12

Browse files
committed
Deploying to stdlib-fpm from @ 65b74f8 🚀
1 parent 124e627 commit f52ff12

File tree

2 files changed

+105
-2
lines changed

2 files changed

+105
-2
lines changed

src/stdlib_math.f90

Lines changed: 85 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ module stdlib_math
55

66
implicit none
77
private
8-
public :: clip, linspace, logspace
8+
public :: clip, gcd, linspace, logspace
99
public :: EULERS_NUMBER_SP, EULERS_NUMBER_DP, EULERS_NUMBER_QP
1010
public :: DEFAULT_LINSPACE_LENGTH, DEFAULT_LOGSPACE_BASE, DEFAULT_LOGSPACE_LENGTH
1111
public :: arange
@@ -29,6 +29,17 @@ module stdlib_math
2929
module procedure clip_qp
3030
end interface clip
3131

32+
!> Returns the greatest common divisor of two integers
33+
!> ([Specification](../page/specs/stdlib_math.html#gcd))
34+
!>
35+
!> Version: experimental
36+
interface gcd
37+
module procedure gcd_int8
38+
module procedure gcd_int16
39+
module procedure gcd_int32
40+
module procedure gcd_int64
41+
end interface gcd
42+
3243
interface linspace
3344
!! Version: Experimental
3445
!!
@@ -648,4 +659,77 @@ elemental function clip_qp(x, xmin, xmax) result(res)
648659
res = max(min(x, xmax), xmin)
649660
end function clip_qp
650661

662+
663+
!> Returns the greatest common divisor of two integers of kind int8
664+
!> using the Euclidean algorithm.
665+
elemental function gcd_int8(a, b) result(res)
666+
integer(int8), intent(in) :: a
667+
integer(int8), intent(in) :: b
668+
integer(int8) :: res
669+
670+
integer(int8) :: rem, tmp
671+
672+
rem = min(abs(a), abs(b))
673+
res = max(abs(a), abs(b))
674+
do while (rem /= 0_int8)
675+
tmp = rem
676+
rem = mod(res, rem)
677+
res = tmp
678+
end do
679+
end function gcd_int8
680+
681+
!> Returns the greatest common divisor of two integers of kind int16
682+
!> using the Euclidean algorithm.
683+
elemental function gcd_int16(a, b) result(res)
684+
integer(int16), intent(in) :: a
685+
integer(int16), intent(in) :: b
686+
integer(int16) :: res
687+
688+
integer(int16) :: rem, tmp
689+
690+
rem = min(abs(a), abs(b))
691+
res = max(abs(a), abs(b))
692+
do while (rem /= 0_int16)
693+
tmp = rem
694+
rem = mod(res, rem)
695+
res = tmp
696+
end do
697+
end function gcd_int16
698+
699+
!> Returns the greatest common divisor of two integers of kind int32
700+
!> using the Euclidean algorithm.
701+
elemental function gcd_int32(a, b) result(res)
702+
integer(int32), intent(in) :: a
703+
integer(int32), intent(in) :: b
704+
integer(int32) :: res
705+
706+
integer(int32) :: rem, tmp
707+
708+
rem = min(abs(a), abs(b))
709+
res = max(abs(a), abs(b))
710+
do while (rem /= 0_int32)
711+
tmp = rem
712+
rem = mod(res, rem)
713+
res = tmp
714+
end do
715+
end function gcd_int32
716+
717+
!> Returns the greatest common divisor of two integers of kind int64
718+
!> using the Euclidean algorithm.
719+
elemental function gcd_int64(a, b) result(res)
720+
integer(int64), intent(in) :: a
721+
integer(int64), intent(in) :: b
722+
integer(int64) :: res
723+
724+
integer(int64) :: rem, tmp
725+
726+
rem = min(abs(a), abs(b))
727+
res = max(abs(a), abs(b))
728+
do while (rem /= 0_int64)
729+
tmp = rem
730+
rem = mod(res, rem)
731+
res = tmp
732+
end do
733+
end function gcd_int64
734+
651735
end module stdlib_math

test/test_stdlib_math.f90

Lines changed: 20 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
! SPDX-Identifier: MIT
22

33
program test_stdlib_math
4-
use stdlib_math, only: clip
4+
use stdlib_math, only: clip, gcd
55
use stdlib_error, only: check
66
use stdlib_kinds, only: int8, int16, int32, int64, sp, dp, qp
77
implicit none
@@ -95,4 +95,23 @@ program test_stdlib_math
9595
call check(clip(-55891546.2_qp, -689712245.23_qp, -8958133457.23_qp) == -689712245.23_qp, &
9696
'clip_qp failed for invalid case', warn=.true.)
9797

98+
99+
! gcd function
100+
! testing format: check(gcd(a, b) == correct answer)
101+
call check(gcd(0, 0) == 0, 'gcd(0, 0) failed.', warn=.true.)
102+
call check(gcd(2, 0) == 2, 'gcd(2, 0) failed.', warn=.true.)
103+
call check(gcd(0, -2) == 2, 'gcd(0, -2) failed.', warn=.true.)
104+
call check(gcd(3, 3) == 3, 'gcd(3, 3) failed.', warn=.true.)
105+
call check(gcd(9, 6) == 3, 'gcd(9, 6) failed.', warn=.true.)
106+
call check(gcd(6, 9) == 3, 'gcd(6, 9) failed.', warn=.true.)
107+
call check(gcd(-9, 6) == 3, 'gcd(-9, 6) failed.', warn=.true.)
108+
call check(gcd(9, -6) == 3, 'gcd(9, -6) failed.', warn=.true.)
109+
call check(gcd(-9, -6) == 3, 'gcd(-9, -6) failed.', warn=.true.)
110+
call check(gcd(97, 91) == 1, 'gcd(97, 91) failed.', warn=.true.)
111+
112+
call check(gcd(48_int8, 18_int8) == 6_int8, 'gcd(48, 18) failed for int8.', warn=.true.)
113+
call check(gcd(48_int16, 18_int16) == 6_int16, 'gcd(48, 18) failed for int16', warn=.true.)
114+
call check(gcd(48_int32, 18_int32) == 6_int32, 'gcd(48, 18) failed for int32', warn=.true.)
115+
call check(gcd(48_int64, 18_int64) == 6_int64, 'gcd(48, 18) failed for int64', warn=.true.)
116+
98117
end program test_stdlib_math

0 commit comments

Comments
 (0)