1 | SUBROUTINE ps_amont(nq,iq,q,w,pbaru,pbarv,dq) |
---|
2 | c |
---|
3 | c Auteurs: P.Le Van, F.Hourdin, F.Forget |
---|
4 | c |
---|
5 | c ******************************************************************** |
---|
6 | c Shema d'advection " pseudo amont " . |
---|
7 | c ******************************************************************** |
---|
8 | c nq,iq,q,pbaru,pbarv,w sont des arguments d'entree pour le s-pg .... |
---|
9 | c dq sont des arguments de sortie pour le s-pg .... |
---|
10 | c |
---|
11 | c |
---|
12 | c -------------------------------------------------------------------- |
---|
13 | IMPLICIT NONE |
---|
14 | c |
---|
15 | #include "dimensions.h" |
---|
16 | #include "paramet.h" |
---|
17 | #include "logic.h" |
---|
18 | #include "comvert.h" |
---|
19 | #include "comgeom.h" |
---|
20 | c |
---|
21 | c |
---|
22 | c Arguments: |
---|
23 | c ---------- |
---|
24 | INTEGER nq,iq |
---|
25 | REAL pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm) |
---|
26 | REAL q(ip1jmp1,llm,nq), dq( ip1jmp1,llm,nq ) |
---|
27 | REAL w(ip1jmp1,llm) |
---|
28 | c |
---|
29 | c Local |
---|
30 | c --------- |
---|
31 | c |
---|
32 | INTEGER i,ij,l |
---|
33 | c |
---|
34 | REAL airej2,airejjm,airescb(iim),airesch(iim) |
---|
35 | REAL pente(ip1jmp1),xg(ip1jmp1),xd(ip1jmp1),xs(ip1jmp1) , |
---|
36 | * xn(ip1jmp1),xb(ip1jmp1),xh(ip1jmp1) |
---|
37 | REAL qg(ip1jmp1),qd(ip1jmp1),qs(ip1jmp1) , |
---|
38 | * qn(ip1jmp1),qb(ip1jmp1,llm),qh(ip1jmp1,llm) |
---|
39 | REAL qbyv(ip1jm,llm), qbxu(ip1jmp1,llm), ww,dqh(ip1jmp1,llm) |
---|
40 | REAL qpns,qpsn |
---|
41 | logical first,extrpn,extrps |
---|
42 | save first |
---|
43 | c |
---|
44 | c |
---|
45 | REAL SSUM,CVMGP,CVMGT |
---|
46 | EXTERNAL SSUM, convflu |
---|
47 | |
---|
48 | data first/.true./ |
---|
49 | |
---|
50 | if(first) then |
---|
51 | print*,'SCHEMA AMONT NOUVEAU' |
---|
52 | first=.false. |
---|
53 | endif |
---|
54 | |
---|
55 | |
---|
56 | c |
---|
57 | c |
---|
58 | IF( forward.OR.leapf ) THEN |
---|
59 | c |
---|
60 | c |
---|
61 | DO 100 l = 1, llm |
---|
62 | c |
---|
63 | c ... Boucle sur les llm niveaux verticaux ... |
---|
64 | c |
---|
65 | c |
---|
66 | c -------------------------------------------------------------- |
---|
67 | c -------------------------------------------------------------- |
---|
68 | c ............. Traitement en longitude ............... |
---|
69 | c -------------------------------------------------------------- |
---|
70 | c -------------------------------------------------------------- |
---|
71 | c |
---|
72 | c |
---|
73 | c | | | | |
---|
74 | c | q(i-1) | q(i) | q(i+1) | |
---|
75 | c | |qg(i) qd(i)|qg(i+1) | |
---|
76 | c |
---|
77 | c |
---|
78 | c En longitude , |
---|
79 | c Pour chaque maille ( i ) avec q(i,j,l,iq), on cherche a determiner |
---|
80 | c avec une methode de ' pente' les valeurs qg(i) et qd(i) qui se trouvent |
---|
81 | c au bord gauche et droite de cette maille . |
---|
82 | c |
---|
83 | c Si ( q(i+1)-q(i) ) * ( q(i)-q(i-1)) < 0. ,on a qg(i)=qd(i)=q(i) |
---|
84 | c Sinon |
---|
85 | c qg(i)= q(i) - 1/4 * ( q(i+1) - q(i-1)) |
---|
86 | c qd(i)= q(i) + 1/4 * ( q(i+1) - q(i-1) ) |
---|
87 | c |
---|
88 | c On utilisera la meme methode pour determiner les valeurs qs(i) et qn(i) |
---|
89 | c en latitude , ainsi que les valeurs qb(i) et qh(i) en altitude . |
---|
90 | c |
---|
91 | c |
---|
92 | c |
---|
93 | DO ij = 1,iip1 |
---|
94 | qg(ij) = 0. |
---|
95 | qd(ij) = 0. |
---|
96 | qg(ij+ ip1jm) = 0. |
---|
97 | qd(ij+ ip1jm) = 0. |
---|
98 | ENDDO |
---|
99 | c |
---|
100 | c .... calculs pour les lignes j= 2 a j = jjm .... |
---|
101 | c |
---|
102 | DO ij = iip2, ip1jm -1 |
---|
103 | pente(ij) =( q(ij+1,l,iq)-q(ij,l,iq)) *(q(ij,l,iq)-q(ij-1,l,iq)) |
---|
104 | xg(ij) = q(ij,l,iq) - 0.25 * ( q(ij+1,l,iq) - q(ij-1,l,iq) ) |
---|
105 | xd(ij) = q(ij,l,iq) + 0.25 * ( q(ij+1,l,iq) - q(ij-1,l,iq) ) |
---|
106 | qg(ij) = CVMGP( xg(ij), q(ij,l,iq) ,pente(ij) ) |
---|
107 | qd(ij) = CVMGP( xd(ij), q(ij,l,iq), pente(ij) ) |
---|
108 | ENDDO |
---|
109 | |
---|
110 | c ... Correction aux points ( i= 1, j ) ..... |
---|
111 | c |
---|
112 | DO ij = iip2, ip1jm, iip1 |
---|
113 | pente(ij) = ( q(ij+1,l,iq) - q(ij,l,iq) ) * |
---|
114 | * ( q(ij,l,iq) - q(ij+iim-1,l,iq) ) |
---|
115 | xg(ij) = q(ij,l,iq) - 0.25* ( q(ij+1,l,iq)- q(ij+iim-1,l,iq) ) |
---|
116 | xd(ij) = q(ij,l,iq) + 0.25* ( q(ij+1,l,iq)- q(ij+iim-1,l,iq) ) |
---|
117 | qg(ij) = CVMGP( xg(ij), q(ij,l,iq) ,pente(ij) ) |
---|
118 | qd(ij) = CVMGP( xd(ij), q(ij,l,iq), pente(ij) ) |
---|
119 | ENDDO |
---|
120 | c |
---|
121 | c ... Correction aux points ( i= iip1, j ) ..... |
---|
122 | c |
---|
123 | DO ij = iip2, ip1jm, iip1 |
---|
124 | qg( ij+ iim ) = qg( ij ) |
---|
125 | qd( ij+ iim ) = qd( ij ) |
---|
126 | ENDDO |
---|
127 | c |
---|
128 | c ............................................................. |
---|
129 | c ......... Limitation des pentes a gauche des boites ..... |
---|
130 | c |
---|
131 | c Si (q(i)-qg(i))*(qg(i)-q(i-1)) < 0. , on a qg(i)=q(i-1) |
---|
132 | c et qd(i)=2*q(i)-qg(i) |
---|
133 | c ............................................................. |
---|
134 | c |
---|
135 | DO ij = iip2,ip1jm -1 |
---|
136 | pente(ij)= ( qg(ij) -q(ij-1,l,iq))*(q(ij,l,iq)-qg(ij) ) |
---|
137 | qg(ij) = CVMGP( qg(ij), q(ij-1,l,iq) ,pente(ij) ) |
---|
138 | qd(ij) = CVMGP( qd(ij), |
---|
139 | * q(ij,l,iq)+ q(ij,l,iq) -qg(ij) , pente(ij) ) |
---|
140 | ENDDO |
---|
141 | c |
---|
142 | c ..... Correction aux points ( i= 1, j ) ...... |
---|
143 | c |
---|
144 | DO ij = iip2 ,ip1jm, iip1 |
---|
145 | qg(ij) = qg(ij+ iim) |
---|
146 | qd(ij) = qd(ij+ iim) |
---|
147 | ENDDO |
---|
148 | c |
---|
149 | c ............................................................... |
---|
150 | c ...... Limitation des pentes a droite des boites ......... |
---|
151 | c Si (q(i+1)-qd(i))*(qd(i)-q(i)) < 0. , on a qd(i)=q(i+1) |
---|
152 | c et qg(i)=2*q(i)-qd(i) . |
---|
153 | c ............................................................... |
---|
154 | c |
---|
155 | DO ij = iip2, ip1jm -1 |
---|
156 | pente(ij) = ( qd(ij)-q(ij,l,iq) )*(q(ij+1,l,iq)-qd(ij) ) |
---|
157 | qd(ij) = CVMGP( qd(ij), q(ij+1,l,iq), pente(ij) ) |
---|
158 | qg(ij) = CVMGP( qg(ij), |
---|
159 | * q(ij,l,iq)+ q(ij,l,iq) -qd(ij) , pente(ij) ) |
---|
160 | ENDDO |
---|
161 | c |
---|
162 | c .... Correction aux points ( i = iip1, j ) ..... |
---|
163 | c |
---|
164 | DO ij = iip2, ip1jm, iip1 |
---|
165 | qg( ij+ iim ) = qg( ij ) |
---|
166 | qd( ij+ iim ) = qd( ij ) |
---|
167 | ENDDO |
---|
168 | c |
---|
169 | |
---|
170 | c ------------------------------------------------------------- |
---|
171 | c ------------------------------------------------------------- |
---|
172 | c ............. Traitement en latitude ................. |
---|
173 | c ------------------------------------------------------------- |
---|
174 | c ------------------------------------------------------------- |
---|
175 | c |
---|
176 | c |
---|
177 | c q(j=1) PN |
---|
178 | c -------------- |
---|
179 | c --------- |
---|
180 | c -------------- |
---|
181 | c |
---|
182 | c q(j-1) |
---|
183 | c |
---|
184 | c -------------- |
---|
185 | c qn(j) |
---|
186 | c q(j) |
---|
187 | c qs(j) |
---|
188 | c -------------- |
---|
189 | c |
---|
190 | c q(j+1) |
---|
191 | c |
---|
192 | c -------------- |
---|
193 | c |
---|
194 | c q(jjp1) PS |
---|
195 | c |
---|
196 | c -------------- |
---|
197 | c |
---|
198 | c |
---|
199 | c ...... operations pour les lignes j= 2 a j= jjm ....... |
---|
200 | c |
---|
201 | DO ij = iip2, ip1jm |
---|
202 | pente(ij) = ( q(ij-iip1,l,iq)- q(ij,l,iq) ) * |
---|
203 | * ( q(ij,l,iq) - q(ij+iip1,l,iq) ) |
---|
204 | xs(ij) = q(ij,l,iq) - 0.25 * ( q(ij-iip1,l,iq) -q(ij+iip1,l,iq) ) |
---|
205 | xn(ij) = q(ij,l,iq) + 0.25 * ( q(ij-iip1,l,iq) -q(ij+iip1,l,iq) ) |
---|
206 | qs(ij) = CVMGP( xs(ij), q(ij,l,iq), pente(ij) ) |
---|
207 | qn(ij) = CVMGP( xn(ij), q(ij,l,iq), pente(ij) ) |
---|
208 | ENDDO |
---|
209 | c |
---|
210 | c |
---|
211 | c ...... Calculs aux poles ............................. |
---|
212 | c ............................................................ |
---|
213 | c |
---|
214 | c On n'a pas besoin des valeurs de qn au pole Nord ( j= 1) , |
---|
215 | c ainsi que de celles de qs au pole Sud ( j= jjp1) |
---|
216 | c |
---|
217 | c |
---|
218 | airej2 = SSUM( iim, aire(iip2), 1 ) |
---|
219 | airejjm= SSUM( iim, aire(ip1jm -iim), 1 ) |
---|
220 | DO i = 1, iim |
---|
221 | airescb(i) = aire(i+ iip1) * q(i+ iip1,l,iq) |
---|
222 | airesch(i) = aire(i+ ip1jm- iip1) * q(i+ ip1jm- iip1,l,iq) |
---|
223 | ENDDO |
---|
224 | qpns = SSUM( iim, airescb ,1 ) / airej2 |
---|
225 | qpsn = SSUM( iim, airesch ,1 ) / airejjm |
---|
226 | c |
---|
227 | c qpns , val.moyenne de q sur la ligne j= 2 |
---|
228 | c qpsn , val.moyenne de q sur la ligne j= jjm |
---|
229 | c |
---|
230 | c |
---|
231 | c |
---|
232 | c on cherche si on a un extremum au pole |
---|
233 | c |
---|
234 | extrpn=.true. |
---|
235 | extrps=.true. |
---|
236 | DO ij=2,iim |
---|
237 | if((q(iip1+i,l,iq)-q(1,l,iq))*(q(iip2,l,iq)-q(1,l,iq)).lt.0.) |
---|
238 | . extrpn=.false. |
---|
239 | if((q(ip1jm-iip1+i,l,iq)-q(1,l,iq))* |
---|
240 | . (q(ip1jm-iim,l,iq)-q(1,l,iq)).lt.0.) |
---|
241 | . extrps=.false. |
---|
242 | ENDDO |
---|
243 | |
---|
244 | c calcul des pentes au pole |
---|
245 | |
---|
246 | if(extrpn) then |
---|
247 | DO ij = 1, iip1 |
---|
248 | qs(ij)= q(ij,l,iq) |
---|
249 | ENDDO |
---|
250 | else |
---|
251 | DO ij = 1, iip1 |
---|
252 | qs(ij)= q(ij,l,iq) + 0.5 * ( q(ij+ iip1,l,iq) - qpns ) |
---|
253 | ENDDO |
---|
254 | endif |
---|
255 | |
---|
256 | if(extrps) then |
---|
257 | DO ij = 1, iip1 |
---|
258 | qn(ij+ip1jm) = q(ij+ip1jm,l,iq) |
---|
259 | ENDDO |
---|
260 | else |
---|
261 | DO ij = 1, iip1 |
---|
262 | qn(ij+ip1jm) = q(ij+ip1jm,l,iq) + 0.5 * |
---|
263 | * ( q(ij+ip1jm-iip1,l,iq) - qpsn ) |
---|
264 | ENDDO |
---|
265 | endif |
---|
266 | |
---|
267 | c |
---|
268 | c |
---|
269 | c ......................................................... |
---|
270 | c ...... Limitation des pentes au sud des boites ..... |
---|
271 | c ......................................................... |
---|
272 | c |
---|
273 | DO ij = 1, ip1jm |
---|
274 | pente(ij) = ( qs(ij) - q (ij+iip1,l,iq) ) * |
---|
275 | * ( q( ij,l,iq) - qs( ij ) ) |
---|
276 | qs(ij) = CVMGP( qs(ij) , q(ij+iip1,l,iq), pente(ij) ) |
---|
277 | qn(ij) = CVMGP( qn(ij) , |
---|
278 | * q(ij,l,iq)+ q(ij,l,iq) -qs(ij), pente(ij) ) |
---|
279 | ENDDO |
---|
280 | c |
---|
281 | c |
---|
282 | c ....................................................... |
---|
283 | c .... Limitation des pentes au nord des boites ......... |
---|
284 | c ....................................................... |
---|
285 | c |
---|
286 | DO ij = iip2, ip1jmp1 |
---|
287 | pente(ij) = ( qn( ij ) - q(ij,l,iq) ) * |
---|
288 | * ( q(ij-iip1,l,iq) - qn(ij) ) |
---|
289 | qn(ij) = CVMGP( qn(ij), q(ij-iip1,l,iq), pente(ij) ) |
---|
290 | qs(ij) = CVMGP( qs(ij), |
---|
291 | * q(ij,l,iq)+ q(ij,l,iq) -qn(ij) , pente(ij) ) |
---|
292 | ENDDO |
---|
293 | c |
---|
294 | c |
---|
295 | c ............................................................. |
---|
296 | c ..... Calculs des flux de q sur le plan horizontal ...... |
---|
297 | c ............................................................. |
---|
298 | c |
---|
299 | c |
---|
300 | c |
---|
301 | c |
---|
302 | c .... Selon X .... |
---|
303 | c |
---|
304 | DO ij = iip2, ip1jm - 1 |
---|
305 | c |
---|
306 | qbxu( ij,l ) = pbaru( ij,l ) * |
---|
307 | * CVMGT( qd(ij), qg(ij +1), pbaru(ij,l).GT.0. ) |
---|
308 | ENDDO |
---|
309 | c |
---|
310 | c ..... correction pour qbxu(iip1,j,l) ..... |
---|
311 | c ... qbxu(iip1,j,l)= qbxu(1,j,l) ... |
---|
312 | c |
---|
313 | c &&&CDIR$ IVDEP |
---|
314 | DO ij = iip1 +iip1, ip1jm, iip1 |
---|
315 | qbxu( ij,l ) = qbxu( ij - iim, l ) |
---|
316 | ENDDO |
---|
317 | c |
---|
318 | c .... Selon Y ..... |
---|
319 | c |
---|
320 | DO ij = 1, ip1jm |
---|
321 | qbyv( ij,l ) = pbarv( ij,l ) * |
---|
322 | * CVMGT( qn(ij+iip1), qs(ij), pbarv(ij,l).GT.0. ) |
---|
323 | ENDDO |
---|
324 | c |
---|
325 | c |
---|
326 | c |
---|
327 | 100 CONTINUE |
---|
328 | c |
---|
329 | c .......................................................... |
---|
330 | c ( ... fin des traitements en longitude et latitude ... ) |
---|
331 | c |
---|
332 | c |
---|
333 | c stockage dans dqh de la convergence horiz.du flux d'humidite . |
---|
334 | c .... |
---|
335 | c |
---|
336 | c |
---|
337 | CALL convflu( qbxu, qbyv, llm, dqh ) |
---|
338 | c |
---|
339 | c |
---|
340 | c |
---|
341 | c ---------------------------------------------------------------- |
---|
342 | c ---------------------------------------------------------------- |
---|
343 | c ............. Traitement en altitude ............. |
---|
344 | c ---------------------------------------------------------------- |
---|
345 | c ---------------------------------------------------------------- |
---|
346 | c |
---|
347 | c |
---|
348 | c ------------- |
---|
349 | c q (llm) |
---|
350 | c |
---|
351 | c ------------- |
---|
352 | c ------------- |
---|
353 | c |
---|
354 | c q(l+1) |
---|
355 | c |
---|
356 | c ------------- |
---|
357 | c qh(l) |
---|
358 | c q(l) |
---|
359 | c qb(l) |
---|
360 | c ------------- |
---|
361 | c |
---|
362 | c q(l-1) |
---|
363 | c |
---|
364 | c ------------- |
---|
365 | c ------------- |
---|
366 | c q(1) |
---|
367 | c ------------- |
---|
368 | c |
---|
369 | c |
---|
370 | c ... Calculs pour les niveaux 2 a llm -1 ... |
---|
371 | c |
---|
372 | c |
---|
373 | DO 200 l = 2, llm -1 |
---|
374 | |
---|
375 | DO ij = 1, ip1jmp1 |
---|
376 | pente(ij) = ( q(ij, l+1 ,iq) - q(ij , l , iq) ) * |
---|
377 | * ( q(ij, l ,iq) - q(ij ,l-1 , iq) ) |
---|
378 | xb(ij) = q(ij,l,iq) - 0.25* ( q(ij,l+1,iq) - q(ij,l-1,iq) ) |
---|
379 | xh(ij) = q(ij,l,iq) + 0.25* ( q(ij,l+1,iq) - q(ij,l-1,iq) ) |
---|
380 | qb(ij,l) = CVMGP( xb(ij), q(ij,l,iq), pente(ij) ) |
---|
381 | qh(ij,l) = CVMGP( xh(ij), q(ij,l,iq), pente(ij) ) |
---|
382 | ENDDO |
---|
383 | c |
---|
384 | c ........................................................ |
---|
385 | c ...... Limitation des pentes en bas des boites ...... |
---|
386 | c ........................................................ |
---|
387 | c |
---|
388 | DO ij = 1, ip1jmp1 |
---|
389 | pente(ij) = ( qb(ij,l) - q ( ij,l-1,iq) ) * |
---|
390 | * ( q (ij,l,iq) - qb( ij,l ) ) |
---|
391 | qb(ij,l) = CVMGP( qb(ij,l), q(ij,l-1,iq), pente(ij) ) |
---|
392 | qh(ij,l) = CVMGP( qh(ij,l), |
---|
393 | * q(ij,l,iq) + q(ij,l,iq) -qb(ij,l), pente(ij) ) |
---|
394 | ENDDO |
---|
395 | c |
---|
396 | c |
---|
397 | c ........................................................ |
---|
398 | c ...... Limitation des pentes en haut des boites ...... |
---|
399 | c ........................................................ |
---|
400 | c |
---|
401 | DO ij = 1, ip1jmp1 |
---|
402 | pente(ij) = ( qh(ij,l) - q ( ij,l+1,iq) ) * |
---|
403 | * ( q (ij,l,iq) - qh( ij,l ) ) |
---|
404 | qh(ij,l) = CVMGP( qh(ij,l), q(ij,l+1,iq), pente(ij) ) |
---|
405 | qb(ij,l) = CVMGP( qb(ij,l), |
---|
406 | * q(ij,l,iq) + q(ij,l,iq) -qh(ij,l), pente(ij) ) |
---|
407 | ENDDO |
---|
408 | c |
---|
409 | c |
---|
410 | 200 CONTINUE |
---|
411 | c |
---|
412 | c |
---|
413 | c ............................................................ |
---|
414 | c ..... Calculs pour les niveaux l= 1 et l= llm ......... |
---|
415 | c ............................................................ |
---|
416 | c |
---|
417 | DO ij = 1, ip1jmp1 |
---|
418 | qb(ij,1) = q(ij, 1 , iq) |
---|
419 | qb(ij,llm) = q(ij,llm, iq) |
---|
420 | qh(ij,1) = q(ij, 1 , iq) |
---|
421 | qh(ij,llm) = q(ij,llm, iq) |
---|
422 | ENDDO |
---|
423 | c |
---|
424 | |
---|
425 | c --------------------------------------------------------------- |
---|
426 | c .... calcul des termes d'advection verticale ....... |
---|
427 | c --------------------------------------------------------------- |
---|
428 | |
---|
429 | c calcul de - d( q * w )/ d(sigma) qu'on ajoute a dqh pour calculer dq |
---|
430 | c |
---|
431 | |
---|
432 | DO 300 l = 1,llmm1 |
---|
433 | c |
---|
434 | DO ij = 1,ip1jmp1 |
---|
435 | ww= - w( ij,l+1 ) * |
---|
436 | * CVMGT ( qh(ij,l), qb(ij,l+1), w(ij,l+1).LT.0.) |
---|
437 | |
---|
438 | dq (ij, l ,iq ) = dqh(ij, l ) - dsig1( l ) * ww |
---|
439 | dqh(ij,l+1 ) = dqh(ij,l+1) + dsig1(l+1) * ww |
---|
440 | ENDDO |
---|
441 | c |
---|
442 | 300 CONTINUE |
---|
443 | c |
---|
444 | c |
---|
445 | c |
---|
446 | DO ij = 1,ip1jmp1 |
---|
447 | dq( ij,llm,iq ) = dqh( ij,llm ) |
---|
448 | END DO |
---|
449 | c |
---|
450 | c |
---|
451 | END IF |
---|
452 | c |
---|
453 | RETURN |
---|
454 | END |
---|