source: LMDZ5/branches/testing/tools/Max_diff_nc_with_lib/Jumble/Numerical/get_divisors.f90 @ 1795

Last change on this file since 1795 was 1795, checked in by Ehouarn Millour, 11 years ago

Version testing basee sur la r1794


Testing release based on r1794

File size: 1.2 KB
Line 
1module get_divisors_m
2
3  implicit none
4
5contains
6
7  subroutine get_divisors(n, div)
8
9    ! Find all the divisors of a given integer.
10
11    integer, intent(in):: n
12    integer, pointer:: div(:)
13
14    ! Variables local to the procedure:
15
16    integer i, i_max
17    integer n_div ! number of divisors of "n"
18    integer work(n) ! temporary array to hold divisors
19
20    !------------------------
21
22    if (n <= 0) then
23       print *, "get_divisors: n = ", n
24       stop 1
25    end if
26   
27    if (n == 1) then
28       work(1) = 1
29       n_div = 1
30    else
31       ! n >= 2, there are at least two divisors: 1 and "n"
32       work(1) = 1
33       work(2) = n
34       n_div = 2
35
36       i_max = int(sqrt(real(n)))
37
38       do i = 2, i_max - 1
39          if (mod(n, i) == 0) then
40             work(n_div+1) = i
41             work(n_div+2) = n / i
42             n_div = n_div + 2
43          end if
44       end do
45
46       if (i_max >= 2 .and. mod(n, i_max) == 0) then
47          work(n_div+1) = i_max
48          n_div = n_div + 1
49          if (i_max**2 /= n) then
50             work(n_div+1) = n / i_max
51             n_div = n_div + 1
52          end if
53       end if
54    end if
55
56    allocate(div(n_div))
57    div = work(:n_div)
58
59  end subroutine get_divisors
60
61end module get_divisors_m
Note: See TracBrowser for help on using the repository browser.