summaryrefslogtreecommitdiff
path: root/gcd.f03
blob: f1f144fb2cf0013330a9e33157c43a38fce947ee (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
! SYNOPSIS:
!
! # gfortran -o gcd-f gcd.f03
! # ./gcd-f 11 22 33 121
!

program GCD
implicit none

integer, allocatable :: ns(:)
integer :: i, n
character*20 :: tmpstr

n = command_argument_count()

allocate(ns(n)) ! allocate memory for numbers given in command line

do i = 1, n
    call get_command_argument(i, tmpstr)
    ns(i) = str2int(tmpstr)
end do

print *,  gcdn(ns)

deallocate(ns)


! If we declare functions first,
! we have to specify its types within
! the `program' section.
! See http://en.wikibooks.org/wiki/Fortran/Fortran_procedures_and_functions
contains

pure integer function str2int (s)
    character*(*), intent(in) :: s
    read (s, *) str2int
end function

pure recursive integer function gcd2 (a, b) result(GCD)
    integer, intent(in) :: a, b
    if (b == 0) then
        GCD = a
    else
        GCD = gcd2(b, mod(a, b))
    end if
end function gcd2

pure integer function gcdn(n)
    integer, intent(in) :: n(:) ! n is an array
    integer :: i
    gcdn = n(1)
    do i = 2, size(n)
        gcdn = gcd2(gcdn, n(i))
    end do
end function

end program