source: LMDZ5/branches/testing/tools/Max_diff_nc_with_lib/NR_util/arth.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: 2.6 KB
Line 
1MODULE arth_m
2
3  IMPLICIT NONE
4
5  INTEGER, PARAMETER, private:: NPAR_ARTH=16, NPAR2_ARTH=8
6
7  INTERFACE arth
8     ! Returns an arithmetic progression, given a first term "first", an
9     ! increment and a number of terms "n".
10
11     MODULE PROCEDURE arth_r, arth_d, arth_i
12     ! The difference between the procedures is the kind and type of
13     ! arguments first and increment and of function result.
14  END INTERFACE
15
16  private arth_r, arth_d, arth_i
17
18CONTAINS
19
20  pure FUNCTION arth_r(first,increment,n)
21
22
23    REAL, INTENT(IN) :: first,increment
24    INTEGER, INTENT(IN) :: n
25    REAL, DIMENSION(n) :: arth_r
26
27    ! Variables local to the procedure:
28
29    INTEGER :: k,k2
30    REAL :: temp
31
32    !---------------------------------------
33
34    if (n > 0) arth_r(1)=first
35    if (n <= NPAR_ARTH) then
36       do k=2,n
37          arth_r(k)=arth_r(k-1)+increment
38       end do
39    else
40       do k=2,NPAR2_ARTH
41          arth_r(k)=arth_r(k-1)+increment
42       end do
43       temp=increment*NPAR2_ARTH
44       k=NPAR2_ARTH
45       do
46          if (k >= n) exit
47          k2=k+k
48          arth_r(k+1:min(k2,n)) = temp + arth_r(1:min(k,n-k))
49          temp=temp+temp
50          k=k2
51       end do
52    end if
53  END FUNCTION arth_r
54
55  !*************************************
56
57  pure FUNCTION arth_d(first,increment,n)
58    DOUBLE PRECISION, INTENT(IN) :: first,increment
59    INTEGER, INTENT(IN) :: n
60    DOUBLE PRECISION, DIMENSION(n) :: arth_d
61    INTEGER :: k,k2
62    DOUBLE PRECISION :: temp
63    if (n > 0) arth_d(1)=first
64    if (n <= NPAR_ARTH) then
65       do k=2,n
66          arth_d(k)=arth_d(k-1)+increment
67       end do
68    else
69       do k=2,NPAR2_ARTH
70          arth_d(k)=arth_d(k-1)+increment
71       end do
72       temp=increment*NPAR2_ARTH
73       k=NPAR2_ARTH
74       do
75          if (k >= n) exit
76          k2=k+k
77          arth_d(k+1:min(k2,n))=temp+arth_d(1:min(k,n-k))
78          temp=temp+temp
79          k=k2
80       end do
81    end if
82  END FUNCTION arth_d
83
84  !*************************************
85
86  pure FUNCTION arth_i(first,increment,n)
87    INTEGER, INTENT(IN) :: first,increment,n
88    INTEGER, DIMENSION(n) :: arth_i
89    INTEGER :: k,k2,temp
90    if (n > 0) arth_i(1)=first
91    if (n <= NPAR_ARTH) then
92       do k=2,n
93          arth_i(k)=arth_i(k-1)+increment
94       end do
95    else
96       do k=2,NPAR2_ARTH
97          arth_i(k)=arth_i(k-1)+increment
98       end do
99       temp=increment*NPAR2_ARTH
100       k=NPAR2_ARTH
101       do
102          if (k >= n) exit
103          k2=k+k
104          arth_i(k+1:min(k2,n))=temp+arth_i(1:min(k,n-k))
105          temp=temp+temp
106          k=k2
107       end do
108    end if
109  END FUNCTION arth_i
110
111END MODULE arth_m
Note: See TracBrowser for help on using the repository browser.