1 | SUBROUTINE convadj(ngrid,nlay,nq,ptimestep, |
---|
2 | S pplay,pplev,ppopsk, |
---|
3 | $ pu,pv,ph,pq, |
---|
4 | $ pdufi,pdvfi,pdhfi,pdqfi, |
---|
5 | $ pduadj,pdvadj,pdhadj, |
---|
6 | $ pdqadj) |
---|
7 | IMPLICIT NONE |
---|
8 | |
---|
9 | c======================================================================= |
---|
10 | c |
---|
11 | c ajustement convectif sec |
---|
12 | c on ajoute les tendances pdhfi au profil pdh avant l'ajustement |
---|
13 | c SPECIAL VERSION : if one tracer is CO2, take into account the |
---|
14 | c Molecular mass variation (e.g. when CO2 condense) to trigger |
---|
15 | c convection F. Forget 01/2005 |
---|
16 | c |
---|
17 | c======================================================================= |
---|
18 | |
---|
19 | c----------------------------------------------------------------------- |
---|
20 | c declarations: |
---|
21 | c ------------- |
---|
22 | |
---|
23 | #include "dimensions.h" |
---|
24 | #include "dimphys.h" |
---|
25 | #include "comcstfi.h" |
---|
26 | #include "callkeys.h" |
---|
27 | #include "tracer.h" |
---|
28 | |
---|
29 | |
---|
30 | c arguments: |
---|
31 | c ---------- |
---|
32 | |
---|
33 | INTEGER ngrid,nlay |
---|
34 | REAL ptimestep |
---|
35 | REAL ph(ngrid,nlay),pdhfi(ngrid,nlay),pdhadj(ngrid,nlay) |
---|
36 | REAL pplay(ngrid,nlay),pplev(ngrid,nlay+1),ppopsk(ngrid,nlay) |
---|
37 | REAL pu(ngrid,nlay),pdufi(ngrid,nlay),pduadj(ngrid,nlay) |
---|
38 | REAL pv(ngrid,nlay),pdvfi(ngrid,nlay),pdvadj(ngrid,nlay) |
---|
39 | |
---|
40 | c Traceurs : |
---|
41 | integer nq |
---|
42 | real pq(ngrid,nlay,nq), pdqfi(ngrid,nlay,nq) |
---|
43 | real pdqadj(ngrid,nlay,nq) |
---|
44 | |
---|
45 | |
---|
46 | c local: |
---|
47 | c ------ |
---|
48 | |
---|
49 | INTEGER ig,i,l,l1,l2,jj |
---|
50 | INTEGER jcnt, jadrs(ngridmx) |
---|
51 | |
---|
52 | REAL sig(nlayermx+1),sdsig(nlayermx),dsig(nlayermx) |
---|
53 | REAL zu(ngridmx,nlayermx),zv(ngridmx,nlayermx) |
---|
54 | REAL zh(ngridmx,nlayermx) |
---|
55 | REAL zu2(ngridmx,nlayermx),zv2(ngridmx,nlayermx) |
---|
56 | REAL zh2(ngridmx,nlayermx), zhc(ngridmx,nlayermx) |
---|
57 | REAL zhm,zsm,zum,zvm,zalpha,zhmc |
---|
58 | |
---|
59 | |
---|
60 | c Traceurs : |
---|
61 | INTEGER iq,ico2 |
---|
62 | save ico2 |
---|
63 | REAL zq(ngridmx,nlayermx,nqmx), zq2(ngridmx,nlayermx,nqmx) |
---|
64 | REAL zqm(nqmx),zqco2m |
---|
65 | real m_co2, m_noco2, A , B |
---|
66 | save A, B |
---|
67 | c Temporaire (for diagnostic) |
---|
68 | c REAL diag_alpha(ngridmx) |
---|
69 | |
---|
70 | |
---|
71 | LOGICAL vtest(ngridmx),down,firstcall |
---|
72 | save firstcall |
---|
73 | data firstcall/.true./ |
---|
74 | |
---|
75 | EXTERNAL SCOPY |
---|
76 | c |
---|
77 | c----------------------------------------------------------------------- |
---|
78 | c initialisation: |
---|
79 | c --------------- |
---|
80 | c |
---|
81 | IF (firstcall) THEN |
---|
82 | IF(ngrid.NE.ngridmx) THEN |
---|
83 | PRINT* |
---|
84 | PRINT*,'STOP dans convadj' |
---|
85 | PRINT*,'ngrid =',ngrid |
---|
86 | PRINT*,'ngridmx =',ngridmx |
---|
87 | ENDIF |
---|
88 | ico2=0 |
---|
89 | if (tracer) then |
---|
90 | c Prepare Special treatment if one of the tracer is CO2 gas |
---|
91 | c write(*,*) "convadj: nqmx=",nqmx |
---|
92 | do iq=1,nqmx |
---|
93 | c write(*,*) "convadj: iq=",iq," noms(iq)=",noms(iq) |
---|
94 | if (noms(iq).eq."co2") then |
---|
95 | ico2=iq |
---|
96 | m_co2 = 44.01E-3 ! CO2 molecular mass (kg/m-3) |
---|
97 | m_noco2 = 33.37E-3 ! Non condensible mol mass (kg/m-3) |
---|
98 | c Compute A and B coefficient use to compute |
---|
99 | c mean molecular mass Mair defined by |
---|
100 | c 1/Mair = q(ico2)/m_co2 + (1-q(ico2))/m_noco2 |
---|
101 | c 1/Mair = A*q(ico2) + B |
---|
102 | A =(1/m_co2 - 1/m_noco2) |
---|
103 | B=1/m_noco2 |
---|
104 | end if |
---|
105 | enddo |
---|
106 | firstcall=.false. |
---|
107 | endif |
---|
108 | ENDIF |
---|
109 | |
---|
110 | c |
---|
111 | c----------------------------------------------------------------------- |
---|
112 | c detection des profils a modifier: |
---|
113 | c --------------------------------- |
---|
114 | c si le profil est a modifier |
---|
115 | c (i.e. ph(niv_sup) < ph(niv_inf) ) |
---|
116 | c alors le tableau "vtest" est mis a .TRUE. ; |
---|
117 | c sinon, il reste a sa valeur initiale (.FALSE.) |
---|
118 | c cette operation est vectorisable |
---|
119 | c On en profite pour copier la valeur initiale de "ph" |
---|
120 | c dans le champ de travail "zh" |
---|
121 | |
---|
122 | |
---|
123 | DO l=1,nlay |
---|
124 | DO ig=1,ngrid |
---|
125 | zh(ig,l)=ph(ig,l)+pdhfi(ig,l)*ptimestep |
---|
126 | zu(ig,l)=pu(ig,l)+pdufi(ig,l)*ptimestep |
---|
127 | zv(ig,l)=pv(ig,l)+pdvfi(ig,l)*ptimestep |
---|
128 | ENDDO |
---|
129 | ENDDO |
---|
130 | |
---|
131 | if(tracer) then |
---|
132 | DO iq =1, nq |
---|
133 | DO l=1,nlay |
---|
134 | DO ig=1,ngrid |
---|
135 | zq(ig,l,iq)=pq(ig,l,iq)+pdqfi(ig,l,iq)*ptimestep |
---|
136 | ENDDO |
---|
137 | ENDDO |
---|
138 | ENDDO |
---|
139 | end if |
---|
140 | |
---|
141 | |
---|
142 | CALL scopy(ngrid*nlay,zh,1,zh2,1) |
---|
143 | CALL scopy(ngrid*nlay,zu,1,zu2,1) |
---|
144 | CALL scopy(ngrid*nlay,zv,1,zv2,1) |
---|
145 | CALL scopy(ngrid*nlay*nq,zq,1,zq2,1) |
---|
146 | |
---|
147 | DO ig=1,ngrid |
---|
148 | vtest(ig)=.FALSE. |
---|
149 | ENDDO |
---|
150 | c |
---|
151 | if (ico2.ne.0) then |
---|
152 | c Special case if one of the tracer is CO2 gas |
---|
153 | c write(*,*) "convadj: ico2=",ico2," nqmx=",nqmx |
---|
154 | DO l=1,nlay |
---|
155 | DO ig=1,ngrid |
---|
156 | zhc(ig,l) = zh2(ig,l)*(A*zq2(ig,l,ico2)+B) |
---|
157 | ENDDO |
---|
158 | ENDDO |
---|
159 | else |
---|
160 | CALL scopy(ngrid*nlay,zh2,1,zhc,1) |
---|
161 | end if |
---|
162 | |
---|
163 | |
---|
164 | |
---|
165 | DO l=2,nlay |
---|
166 | DO ig=1,ngrid |
---|
167 | IF(zhc(ig,l).LT.zhc(ig,l-1)) vtest(ig)=.TRUE. |
---|
168 | ENDDO |
---|
169 | ENDDO |
---|
170 | c |
---|
171 | CRAY CALL WHENNE(ngrid, vtest, 1, 0, jadrs, jcnt) |
---|
172 | jcnt=0 |
---|
173 | DO ig=1,ngrid |
---|
174 | IF(vtest(ig)) THEN |
---|
175 | jcnt=jcnt+1 |
---|
176 | jadrs(jcnt)=ig |
---|
177 | ENDIF |
---|
178 | ENDDO |
---|
179 | |
---|
180 | |
---|
181 | c----------------------------------------------------------------------- |
---|
182 | c Ajustement des "jcnt" profils instables indices par "jadrs": |
---|
183 | c ------------------------------------------------------------ |
---|
184 | c |
---|
185 | DO jj = 1, jcnt |
---|
186 | c |
---|
187 | i = jadrs(jj) |
---|
188 | c |
---|
189 | c Calcul des niveaux sigma sur cette colonne |
---|
190 | DO l=1,nlay+1 |
---|
191 | sig(l)=pplev(i,l)/pplev(i,1) |
---|
192 | ENDDO |
---|
193 | DO l=1,nlay |
---|
194 | dsig(l)=sig(l)-sig(l+1) |
---|
195 | sdsig(l)=ppopsk(i,l)*dsig(l) |
---|
196 | ENDDO |
---|
197 | l2 = 1 |
---|
198 | c |
---|
199 | c -- boucle de sondage vers le haut |
---|
200 | c |
---|
201 | cins$ Loop |
---|
202 | DO |
---|
203 | c |
---|
204 | l2 = l2 + 1 |
---|
205 | c |
---|
206 | cins$ Exit |
---|
207 | IF (l2 .GT. nlay) EXIT |
---|
208 | c |
---|
209 | IF (zhc(i, l2) .LT. zhc(i, l2-1)) THEN |
---|
210 | c |
---|
211 | c -- l2 est le niveau le plus haut de la colonne instable |
---|
212 | c |
---|
213 | l1 = l2 - 1 |
---|
214 | l = l1 |
---|
215 | zsm = sdsig(l2) |
---|
216 | zhm = zh2(i, l2) |
---|
217 | if(ico2.ne.0) zqco2m = zq2(i,l2,ico2) |
---|
218 | c |
---|
219 | c -- boucle de sondage vers le bas |
---|
220 | c |
---|
221 | cins$ Loop |
---|
222 | DO |
---|
223 | c |
---|
224 | zsm = zsm + sdsig(l) |
---|
225 | zhm = zhm + sdsig(l) * (zh2(i, l) - zhm) / zsm |
---|
226 | if(ico2.ne.0) then |
---|
227 | zqco2m = |
---|
228 | & zqco2m + sdsig(l) * (zq2(i,l,ico2) - zqco2m) / zsm |
---|
229 | zhmc = zhm*(A*zqco2m+B) |
---|
230 | else |
---|
231 | zhmc = zhm |
---|
232 | end if |
---|
233 | c |
---|
234 | c -- doit on etendre la colonne vers le bas ? |
---|
235 | c |
---|
236 | c_EC (M1875) 20/6/87 : AND -> AND THEN |
---|
237 | c |
---|
238 | down = .FALSE. |
---|
239 | IF (l1 .NE. 1) THEN !-- and then |
---|
240 | IF (zhmc .LT. zhc(i, l1-1)) THEN |
---|
241 | down = .TRUE. |
---|
242 | END IF |
---|
243 | END IF |
---|
244 | c |
---|
245 | IF (down) THEN |
---|
246 | c |
---|
247 | l1 = l1 - 1 |
---|
248 | l = l1 |
---|
249 | c |
---|
250 | ELSE |
---|
251 | c |
---|
252 | c -- peut on etendre la colonne vers le haut ? |
---|
253 | c |
---|
254 | cins$ Exit |
---|
255 | IF (l2 .EQ. nlay) EXIT |
---|
256 | c |
---|
257 | cins$ Exit |
---|
258 | IF (zhc(i, l2+1) .GE. zhmc) EXIT |
---|
259 | c |
---|
260 | l2 = l2 + 1 |
---|
261 | l = l2 |
---|
262 | c |
---|
263 | END IF |
---|
264 | c |
---|
265 | cins$ End Loop |
---|
266 | ENDDO |
---|
267 | c |
---|
268 | c -- nouveau profil : constant (valeur moyenne) |
---|
269 | c |
---|
270 | zalpha=0. |
---|
271 | zum=0. |
---|
272 | zvm=0. |
---|
273 | do iq=1,nq |
---|
274 | zqm(iq) = 0. |
---|
275 | end do |
---|
276 | DO l = l1, l2 |
---|
277 | if(ico2.ne.0) then |
---|
278 | zalpha=zalpha+ |
---|
279 | & ABS(zhc(i,l)/(A+B*zqco2m) -zhm)*dsig(l) |
---|
280 | else |
---|
281 | zalpha=zalpha+ABS(zh2(i,l)-zhm)*dsig(l) |
---|
282 | endif |
---|
283 | zh2(i, l) = zhm |
---|
284 | zum=zum+dsig(l)*zu(i,l) |
---|
285 | zvm=zvm+dsig(l)*zv(i,l) |
---|
286 | do iq=1,nq |
---|
287 | zqm(iq) = zqm(iq)+dsig(l)*zq(i,l,iq) |
---|
288 | end do |
---|
289 | ENDDO |
---|
290 | zalpha=zalpha/(zhm*(sig(l1)-sig(l2+1))) |
---|
291 | zum=zum/(sig(l1)-sig(l2+1)) |
---|
292 | zvm=zvm/(sig(l1)-sig(l2+1)) |
---|
293 | do iq=1,nq |
---|
294 | zqm(iq) = zqm(iq)/(sig(l1)-sig(l2+1)) |
---|
295 | end do |
---|
296 | |
---|
297 | IF(zalpha.GT.1.) THEN |
---|
298 | c PRINT*,'WARNING dans convadj zalpha=',zalpha |
---|
299 | c STOP |
---|
300 | zalpha=1. |
---|
301 | ELSE |
---|
302 | c IF(zalpha.LT.0.) STOP |
---|
303 | IF(zalpha.LT.1.e-4) zalpha=1.e-4 |
---|
304 | ENDIF |
---|
305 | |
---|
306 | DO l=l1,l2 |
---|
307 | zu2(i,l)=zu2(i,l)+zalpha*(zum-zu2(i,l)) |
---|
308 | zv2(i,l)=zv2(i,l)+zalpha*(zvm-zv2(i,l)) |
---|
309 | do iq=1,nq |
---|
310 | zq2(i,l,iq)=zq2(i,l,iq)+zalpha*(zqm(iq)-zq2(i,l,iq)) |
---|
311 | c zq2(i,l,iq)=zqm(iq) |
---|
312 | end do |
---|
313 | ENDDO |
---|
314 | c diag_alpha(i)=zalpha !temporaire |
---|
315 | |
---|
316 | l2 = l2 + 1 |
---|
317 | c |
---|
318 | END IF |
---|
319 | c |
---|
320 | cins$ End Loop |
---|
321 | ENDDO |
---|
322 | c |
---|
323 | ENDDO |
---|
324 | c |
---|
325 | DO l=1,nlay |
---|
326 | DO ig=1,ngrid |
---|
327 | pdhadj(ig,l)=(zh2(ig,l)-zh(ig,l))/ptimestep |
---|
328 | pduadj(ig,l)=(zu2(ig,l)-zu(ig,l))/ptimestep |
---|
329 | pdvadj(ig,l)=(zv2(ig,l)-zv(ig,l))/ptimestep |
---|
330 | c pdhadj(ig,l)=0. |
---|
331 | c pduadj(ig,l)=0. |
---|
332 | c pdvadj(ig,l)=0. |
---|
333 | ENDDO |
---|
334 | ENDDO |
---|
335 | |
---|
336 | if(tracer) then |
---|
337 | do iq=1, nq |
---|
338 | do l=1,nlay |
---|
339 | do ig=1, ngrid |
---|
340 | pdqadj(ig,l,iq)=(zq2(ig,l,iq)-zq(ig,l,iq))/ptimestep |
---|
341 | end do |
---|
342 | end do |
---|
343 | end do |
---|
344 | end if |
---|
345 | RETURN |
---|
346 | END |
---|