/[lmdze]/trunk/Sources/filtrez/inifilr.f
ViewVC logotype

Contents of /trunk/Sources/filtrez/inifilr.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 154 - (show annotations)
Tue Jul 7 17:49:23 2015 UTC (8 years, 10 months ago) by guez
File size: 8606 byte(s)
Removed argument dtphys of physiq. Use it directly from comconst in
physiq instead.

Donwgraded variables eignfnu, eignfnv of module inifgn_m to dummy
arguments of SUBROUTINE inifgn. They were not used elsewhere than in
the calling procedure inifilr. Renamed argument dv of inifgn to eignval_v.

Made alboc and alboc_cd independent of the size of arguments. Now we
can call them only at indices knindex in interfsurf_hq, where we need
them. Fixed a bug in alboc_cd: rmu0 was modified, and the
corresponding actual argument in interfsurf_hq is an intent(in)
argument of interfsurf_hq.

Variables of size knon instead of klon in interfsur_lim and interfsurf_hq.

Removed argument alb_new of interfsurf_hq because it was the same than
alblw. Simplified test on cycle_diurne, following LMDZ.

Moved tests on nbapp_rad from physiq to read_clesphys2. No need for
separate counter itaprad, we can use itap. Define lmt_pas and radpas
from integer input parameters instead of real-type computed values.

1 module inifilr_m
2
3 IMPLICIT NONE
4
5 INTEGER jfiltnu, jfiltsu, jfiltnv, jfiltsv
6 ! jfiltn index of the last scalar line filtered in NH
7 ! jfilts index of the first line filtered in SH
8
9 ! North:
10 real, allocatable:: matriceun(:, :, :), matrinvn(:, :, :)
11 ! (iim, iim, 2:jfiltnu)
12
13 real, allocatable:: matricevn(:, :, :) ! (iim, iim, jfiltnv)
14
15 ! South:
16 real, allocatable:: matriceus(:, :, :), matrinvs(:, :, :)
17 ! (iim, iim, jfiltsu:jjm)
18
19 real, allocatable:: matricevs(:, :, :) ! (iim, iim, jfiltsv:jjm)
20
21 contains
22
23 SUBROUTINE inifilr
24
25 ! From filtrez/inifilr.F, version 1.1.1.1 2004/05/19 12:53:09
26 ! H. Upadhyaya, O. Sharma
27
28 ! This routine computes the eigenfunctions of the laplacian on the
29 ! stretched grid, and the filtering coefficients. The modes are
30 ! filtered from modfrst to iim.
31
32 USE dimens_m, ONLY : iim, jjm
33 USE dynetat0_m, ONLY : rlatu, rlatv, xprimu, grossismx
34 use inifgn_m, only: inifgn
35 use jumble, only: new_unit
36 use nr_util, only: pi
37
38 ! Local:
39 REAL dlatu(jjm)
40 REAL rlamda(2: iim)
41 real eignvl(iim) ! eigenvalues sorted in descending order
42 REAL cof
43 INTEGER i, j, k, unit
44 REAL colat0 ! > 0
45 REAL eignft(iim, iim), coff
46
47 real eignfnu(iim, iim), eignfnv(iim, iim)
48 ! eigenfunctions of the discrete laplacian
49
50 ! Filtering coefficients (lamda_max * cos(rlat) / lamda):
51 real coefilu(iim, jjm), coefilv(iim, jjm)
52 real coefilu2(iim, jjm), coefilv2(iim, jjm)
53
54 ! Index of the mode from where modes are filtered:
55 integer, allocatable:: modfrstnu(:), modfrstsu(:)
56 integer, allocatable:: modfrstnv(:), modfrstsv(:)
57
58 !-----------------------------------------------------------
59
60 print *, "Call sequence information: inifilr"
61
62 CALL inifgn(eignvl, eignfnu, eignfnv)
63
64 ! compute eigenvalues and eigenfunctions
65 ! compute the filtering coefficients for scalar lines and
66 ! meridional wind v-lines
67 ! we filter all those latitude lines where coefil < 1
68 ! NO FILTERING AT POLES
69 ! colat0 is to be used when alpha (stretching coefficient)
70 ! is set equal to zero for the regular grid case
71
72 ! Calcul de colat0
73 forall (j = 1:jjm) dlatu(j) = rlatu(j) - rlatu(j + 1)
74 colat0 = min(0.5, minval(dlatu) / minval(xprimu(:iim)))
75 PRINT *, 'colat0 = ', colat0
76
77 rlamda = iim / (pi * colat0 / grossismx) / sqrt(abs(eignvl(2: iim)))
78
79 ! Determination de jfiltnu, jfiltsu, jfiltnv, jfiltsv
80
81 jfiltnu = (jjm + 1) / 2
82 do while (cos(rlatu(jfiltnu)) >= colat0 &
83 .or. rlamda(iim) * cos(rlatu(jfiltnu)) >= 1.)
84 jfiltnu = jfiltnu - 1
85 end do
86
87 jfiltsu = jjm / 2 + 2
88 do while (cos(rlatu(jfiltsu)) >= colat0 &
89 .or. rlamda(iim) * cos(rlatu(jfiltsu)) >= 1.)
90 jfiltsu = jfiltsu + 1
91 end do
92
93 jfiltnv = jjm / 2
94 do while ((cos(rlatv(jfiltnv)) >= colat0 &
95 .or. rlamda(iim) * cos(rlatv(jfiltnv)) >= 1.) .and. jfiltnv >= 2)
96 jfiltnv = jfiltnv - 1
97 end do
98
99 if (cos(rlatv(jfiltnv)) >= colat0 &
100 .or. rlamda(iim) * cos(rlatv(jfiltnv)) >= 1.) then
101 ! {jfiltnv == 1}
102 PRINT *, 'Could not find jfiltnv.'
103 STOP 1
104 END IF
105
106 jfiltsv = (jjm + 1)/ 2 + 1
107 do while ((cos(rlatv(jfiltsv)) >= colat0 &
108 .or. rlamda(iim) * cos(rlatv(jfiltsv)) >= 1.) .and. jfiltsv <= jjm - 1)
109 jfiltsv = jfiltsv + 1
110 end do
111
112 IF (cos(rlatv(jfiltsv)) >= colat0 &
113 .or. rlamda(iim) * cos(rlatv(jfiltsv)) >= 1.) THEN
114 ! {jfiltsv == jjm}
115 PRINT *, 'Could not find jfiltsv.'
116 STOP 1
117 END IF
118
119 PRINT *, 'jfiltnu =', jfiltnu
120 PRINT *, 'jfiltsu =', jfiltsu
121 PRINT *, 'jfiltnv =', jfiltnv
122 PRINT *, 'jfiltsv =', jfiltsv
123
124 ! Determination de coefilu, coefilv, modfrst[ns][uv]:
125
126 allocate(modfrstnu(2:jfiltnu), modfrstsu(jfiltsu:jjm))
127 allocate(modfrstnv(jfiltnv), modfrstsv(jfiltsv:jjm))
128 coefilu = 0.
129 coefilv = 0.
130 coefilu2 = 0.
131 coefilv2 = 0.
132
133 DO j = 2, jfiltnu
134 modfrstnu(j) = 2
135 do while (rlamda(modfrstnu(j)) * cos(rlatu(j)) >= 1. &
136 .and. modfrstnu(j) <= iim - 1)
137 modfrstnu(j) = modfrstnu(j) + 1
138 end do
139
140 if (rlamda(modfrstnu(j)) * cos(rlatu(j)) < 1.) then
141 DO k = modfrstnu(j), iim
142 cof = rlamda(k) * cos(rlatu(j))
143 coefilu(k, j) = cof - 1.
144 coefilu2(k, j) = cof**2 - 1.
145 end DO
146 end if
147 END DO
148
149 DO j = 1, jfiltnv
150 modfrstnv(j) = 2
151 do while (rlamda(modfrstnv(j)) * cos(rlatv(j)) >= 1. &
152 .and. modfrstnv(j) <= iim - 1)
153 modfrstnv(j) = modfrstnv(j) + 1
154 end do
155
156 if (rlamda(modfrstnv(j)) * cos(rlatv(j)) < 1.) then
157 DO k = modfrstnv(j), iim
158 cof = rlamda(k) * cos(rlatv(j))
159 coefilv(k, j) = cof - 1.
160 coefilv2(k, j) = cof**2 - 1.
161 end DO
162 end if
163 end DO
164
165 DO j = jfiltsu, jjm
166 modfrstsu(j) = 2
167 do while (rlamda(modfrstsu(j)) * cos(rlatu(j)) >= 1. &
168 .and. modfrstsu(j) <= iim - 1)
169 modfrstsu(j) = modfrstsu(j) + 1
170 end do
171
172 if (rlamda(modfrstsu(j)) * cos(rlatu(j)) < 1.) then
173 DO k = modfrstsu(j), iim
174 cof = rlamda(k) * cos(rlatu(j))
175 coefilu(k, j) = cof - 1.
176 coefilu2(k, j) = cof**2 - 1.
177 end DO
178 end if
179 end DO
180
181 DO j = jfiltsv, jjm
182 modfrstsv(j) = 2
183 do while (rlamda(modfrstsv(j)) * cos(rlatv(j)) >= 1. &
184 .and. modfrstsv(j) <= iim - 1)
185 modfrstsv(j) = modfrstsv(j) + 1
186 end do
187
188 if (rlamda(modfrstsv(j)) * cos(rlatv(j)) < 1.) then
189 DO k = modfrstsv(j), iim
190 cof = rlamda(k) * cos(rlatv(j))
191 coefilv(k, j) = cof - 1.
192 coefilv2(k, j) = cof**2 - 1.
193 end DO
194 end if
195 END DO
196
197 call new_unit(unit)
198 open(unit, file = "inifilr_out.txt", status = "replace", action = "write")
199 write(unit, fmt = *) '"EIGNVL"', eignvl
200 write(unit, fmt = *) '"modfrstnu"', modfrstnu
201 write(unit, fmt = *) '"modfrstsu"', modfrstsu
202 write(unit, fmt = *) '"modfrstnv"', modfrstnv
203 write(unit, fmt = *) '"modfrstsv"', modfrstsv
204 close(unit)
205
206 allocate(matriceun(iim, iim, 2:jfiltnu), matrinvn(iim, iim, 2:jfiltnu))
207 allocate(matricevn(iim, iim, jfiltnv))
208 allocate(matricevs(iim, iim, jfiltsv:jjm))
209 allocate(matriceus(iim, iim, jfiltsu:jjm), matrinvs(iim, iim, jfiltsu:jjm))
210
211 ! Calcul de la matrice filtre 'matriceu' pour les champs situes
212 ! sur la grille scalaire
213
214 DO j = 2, jfiltnu
215 DO i = 1, iim
216 IF (i < modfrstnu(j)) then
217 coff = 0.
218 else
219 coff = coefilu(i, j)
220 end IF
221 eignft(i, :) = eignfnv(:, i) * coff
222 END DO
223 matriceun(:, :, j) = matmul(eignfnv, eignft)
224 END DO
225
226 DO j = jfiltsu, jjm
227 DO i = 1, iim
228 IF (i < modfrstsu(j)) then
229 coff = 0.
230 else
231 coff = coefilu(i, j)
232 end IF
233 eignft(i, :) = eignfnv(:, i) * coff
234 END DO
235 matriceus(:, :, j) = matmul(eignfnv, eignft)
236 END DO
237
238 ! Calcul de la matrice filtre 'matricev' pour les champs situes
239 ! sur la grille de V ou de Z
240
241 DO j = 1, jfiltnv
242 DO i = 1, iim
243 IF (i < modfrstnv(j)) then
244 coff = 0.
245 else
246 coff = coefilv(i, j)
247 end IF
248 eignft(i, :) = eignfnu(:, i) * coff
249 END DO
250 matricevn(:, :, j) = matmul(eignfnu, eignft)
251 END DO
252
253 DO j = jfiltsv, jjm
254 DO i = 1, iim
255 IF (i < modfrstsv(j)) then
256 coff = 0.
257 else
258 coff = coefilv(i, j)
259 end IF
260 eignft(i, :) = eignfnu(:, i) * coff
261 END DO
262 matricevs(:, :, j) = matmul(eignfnu, eignft)
263 END DO
264
265 ! Calcul de la matrice filtre 'matrinv' pour les champs situes
266 ! sur la grille scalaire , pour le filtre inverse
267
268 DO j = 2, jfiltnu
269 DO i = 1, iim
270 IF (i < modfrstnu(j)) then
271 coff = 0.
272 else
273 coff = coefilu(i, j) / (1. + coefilu(i, j))
274 end IF
275 eignft(i, :) = eignfnv(:, i) * coff
276 END DO
277 matrinvn(:, :, j) = matmul(eignfnv, eignft)
278 END DO
279
280 DO j = jfiltsu, jjm
281 DO i = 1, iim
282 IF (i < modfrstsu(j)) then
283 coff = 0.
284 else
285 coff = coefilu(i, j) / (1. + coefilu(i, j))
286 end IF
287 eignft(i, :) = eignfnv(:, i) * coff
288 END DO
289 matrinvs(:, :, j) = matmul(eignfnv, eignft)
290 END DO
291
292 END SUBROUTINE inifilr
293
294 end module inifilr_m

  ViewVC Help
Powered by ViewVC 1.1.21