/[lmdze]/trunk/phylmd/cv_driver.f
ViewVC logotype

Contents of /trunk/phylmd/cv_driver.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 103 - (show annotations)
Fri Aug 29 13:00:05 2014 UTC (9 years, 8 months ago) by guez
File size: 17317 byte(s)
Renamed module cvparam to cv_param. Deleted procedure
cv_param. Changed variables of module cv_param into parameters.

In procedures cv_driver, cv_uncompress and cv3_uncompress, removed
some arguments giving dimensions and used module variables klon and
klev instead.

In procedures gradiv2, laplacien_gam and laplacien, changed
declarations of local variables because klevel is not always klev.

Removed code for nudging surface pressure.

Removed arguments pim and pjm of tau2alpha. Added assignment of false
to variable first.

Replaced real argument del of procedures foeew and FOEDE by logical
argument.

1 module cv_driver_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE cv_driver(t1, q1, qs1, u1, v1, p1, ph1, iflag1, ft1, &
8 fq1, fu1, fv1, precip1, VPrecip1, cbmf1, sig1, w01, icb1, inb1, delt, &
9 Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, cape1, da1, phi1, mp1)
10
11 ! From LMDZ4/libf/phylmd/cv_driver.F, version 1.3, 2005/04/15 12:36:17
12 ! Main driver for convection
13 ! Author: S. Bony, March 2002
14
15 ! Several modules corresponding to different physical processes
16
17 ! Several versions of convect may be used:
18 ! - iflag_con = 3: version lmd
19 ! - iflag_con = 4: version 4.3b
20
21 use clesphys2, only: iflag_con
22 use cv3_compress_m, only: cv3_compress
23 use cv3_feed_m, only: cv3_feed
24 use cv3_mixing_m, only: cv3_mixing
25 use cv3_param_m, only: cv3_param
26 use cv3_prelim_m, only: cv3_prelim
27 use cv3_tracer_m, only: cv3_tracer
28 use cv3_uncompress_m, only: cv3_uncompress
29 use cv3_unsat_m, only: cv3_unsat
30 use cv3_yield_m, only: cv3_yield
31 use cv_feed_m, only: cv_feed
32 use cv_uncompress_m, only: cv_uncompress
33 USE dimphy, ONLY: klev, klon
34
35 real, intent(in):: t1(klon, klev) ! temperature
36 real, intent(in):: q1(klon, klev) ! specific hum
37 real, intent(in):: qs1(klon, klev) ! sat specific hum
38 real, intent(in):: u1(klon, klev) ! u-wind
39 real, intent(in):: v1(klon, klev) ! v-wind
40 real, intent(in):: p1(klon, klev) ! full level pressure
41 real, intent(in):: ph1(klon, klev + 1) ! half level pressure
42 integer, intent(out):: iflag1(klon) ! flag for Emanuel conditions
43 real, intent(out):: ft1(klon, klev) ! temp tend
44 real, intent(out):: fq1(klon, klev) ! spec hum tend
45 real, intent(out):: fu1(klon, klev) ! u-wind tend
46 real, intent(out):: fv1(klon, klev) ! v-wind tend
47 real, intent(out):: precip1(klon) ! precipitation
48
49 real, intent(out):: VPrecip1(klon, klev+1)
50 ! vertical profile of precipitation
51
52 real, intent(inout):: cbmf1(klon) ! cloud base mass flux
53 real, intent(inout):: sig1(klon, klev) ! section adiabatic updraft
54
55 real, intent(inout):: w01(klon, klev)
56 ! vertical velocity within adiabatic updraft
57
58 integer, intent(out):: icb1(klon)
59 integer, intent(inout):: inb1(klon)
60 real, intent(in):: delt ! time step
61 real Ma1(klon, klev)
62 ! Ma1 Real Output mass flux adiabatic updraft
63 real, intent(out):: upwd1(klon, klev) ! total upward mass flux (adiab+mixed)
64 real, intent(out):: dnwd1(klon, klev) ! saturated downward mass flux (mixed)
65 real, intent(out):: dnwd01(klon, klev) ! unsaturated downward mass flux
66
67 real qcondc1(klon, klev) ! cld
68 ! qcondc1 Real Output in-cld mixing ratio of condensed water
69 real wd1(klon) ! gust
70 ! wd1 Real Output downdraft velocity scale for sfc fluxes
71 real cape1(klon)
72 ! cape1 Real Output CAPE
73
74 real, intent(inout):: da1(klon, klev), phi1(klon, klev, klev)
75 real, intent(inout):: mp1(klon, klev)
76
77 ! --- ARGUMENTS
78
79 ! --- On input:
80
81 ! t: Array of absolute temperature (K) of dimension KLEV, with first
82 ! index corresponding to lowest model level. Note that this array
83 ! will be altered by the subroutine if dry convective adjustment
84 ! occurs and if IPBL is not equal to 0.
85
86 ! q: Array of specific humidity (gm/gm) of dimension KLEV, with first
87 ! index corresponding to lowest model level. Must be defined
88 ! at same grid levels as T. Note that this array will be altered
89 ! if dry convective adjustment occurs and if IPBL is not equal to 0.
90
91 ! qs: Array of saturation specific humidity of dimension KLEV, with first
92 ! index corresponding to lowest model level. Must be defined
93 ! at same grid levels as T. Note that this array will be altered
94 ! if dry convective adjustment occurs and if IPBL is not equal to 0.
95
96 ! u: Array of zonal wind velocity (m/s) of dimension KLEV, witth first
97 ! index corresponding with the lowest model level. Defined at
98 ! same levels as T. Note that this array will be altered if
99 ! dry convective adjustment occurs and if IPBL is not equal to 0.
100
101 ! v: Same as u but for meridional velocity.
102
103 ! p: Array of pressure (mb) of dimension KLEV, with first
104 ! index corresponding to lowest model level. Must be defined
105 ! at same grid levels as T.
106
107 ! ph: Array of pressure (mb) of dimension KLEV+1, with first index
108 ! corresponding to lowest level. These pressures are defined at
109 ! levels intermediate between those of P, T, Q and QS. The first
110 ! value of PH should be greater than (i.e. at a lower level than)
111 ! the first value of the array P.
112
113 ! nl: The maximum number of levels to which convection can penetrate, plus 1
114 ! NL MUST be less than or equal to KLEV-1.
115
116 ! delt: The model time step (sec) between calls to CONVECT
117
118 ! --- On Output:
119
120 ! iflag: An output integer whose value denotes the following:
121 ! VALUE INTERPRETATION
122 ! ----- --------------
123 ! 0 Moist convection occurs.
124 ! 1 Moist convection occurs, but a CFL condition
125 ! on the subsidence warming is violated. This
126 ! does not cause the scheme to terminate.
127 ! 2 Moist convection, but no precip because ep(inb) lt 0.0001
128 ! 3 No moist convection because new cbmf is 0 and old cbmf is 0.
129 ! 4 No moist convection; atmosphere is not
130 ! unstable
131 ! 6 No moist convection because ihmin le minorig.
132 ! 7 No moist convection because unreasonable
133 ! parcel level temperature or specific humidity.
134 ! 8 No moist convection: lifted condensation
135 ! level is above the 200 mb level.
136 ! 9 No moist convection: cloud base is higher
137 ! then the level NL-1.
138
139 ! ft: Array of temperature tendency (K/s) of dimension KLEV, defined at same
140 ! grid levels as T, Q, QS and P.
141
142 ! fq: Array of specific humidity tendencies ((gm/gm)/s) of dimension KLEV,
143 ! defined at same grid levels as T, Q, QS and P.
144
145 ! fu: Array of forcing of zonal velocity (m/s^2) of dimension KLEV,
146 ! defined at same grid levels as T.
147
148 ! fv: Same as FU, but for forcing of meridional velocity.
149
150 ! precip: Scalar convective precipitation rate (mm/day).
151
152 ! VPrecip: Vertical profile of convective precipitation (kg/m2/s).
153
154 ! wd: A convective downdraft velocity scale. For use in surface
155 ! flux parameterizations. See convect.ps file for details.
156
157 ! tprime: A convective downdraft temperature perturbation scale (K).
158 ! For use in surface flux parameterizations. See convect.ps
159 ! file for details.
160
161 ! qprime: A convective downdraft specific humidity
162 ! perturbation scale (gm/gm).
163 ! For use in surface flux parameterizations. See convect.ps
164 ! file for details.
165
166 ! cbmf: The cloud base mass flux ((kg/m**2)/s). THIS SCALAR VALUE MUST
167 ! BE STORED BY THE CALLING PROGRAM AND RETURNED TO CONVECT AT
168 ! ITS NEXT CALL. That is, the value of CBMF must be "remembered"
169 ! by the calling program between calls to CONVECT.
170
171 ! det: Array of detrainment mass flux of dimension KLEV.
172
173 ! Local arrays
174
175 real da(klon, klev), phi(klon, klev, klev), mp(klon, klev)
176
177 integer i, k, il
178 integer icbmax
179 integer nk1(klon)
180 integer icbs1(klon)
181
182 real plcl1(klon)
183 real tnk1(klon)
184 real qnk1(klon)
185 real gznk1(klon)
186 real pbase1(klon)
187 real buoybase1(klon)
188
189 real lv1(klon, klev)
190 real cpn1(klon, klev)
191 real tv1(klon, klev)
192 real gz1(klon, klev)
193 real hm1(klon, klev)
194 real h1(klon, klev)
195 real tp1(klon, klev)
196 real tvp1(klon, klev)
197 real clw1(klon, klev)
198 real th1(klon, klev)
199
200 integer ncum
201
202 ! (local) compressed fields:
203
204 integer idcum(klon)
205 integer iflag(klon), nk(klon), icb(klon)
206 integer nent(klon, klev)
207 integer icbs(klon)
208 integer inb(klon), inbis(klon)
209
210 real cbmf(klon), plcl(klon), tnk(klon), qnk(klon), gznk(klon)
211 real t(klon, klev), q(klon, klev), qs(klon, klev)
212 real u(klon, klev), v(klon, klev)
213 real gz(klon, klev), h(klon, klev), lv(klon, klev), cpn(klon, klev)
214 real p(klon, klev), ph(klon, klev+1), tv(klon, klev), tp(klon, klev)
215 real clw(klon, klev)
216 real dph(klon, klev)
217 real pbase(klon), buoybase(klon), th(klon, klev)
218 real tvp(klon, klev)
219 real sig(klon, klev), w0(klon, klev)
220 real hp(klon, klev), ep(klon, klev), sigp(klon, klev)
221 real frac(klon), buoy(klon, klev)
222 real cape(klon)
223 real m(klon, klev), ment(klon, klev, klev), qent(klon, klev, klev)
224 real uent(klon, klev, klev), vent(klon, klev, klev)
225 real ments(klon, klev, klev), qents(klon, klev, klev)
226 real sij(klon, klev, klev), elij(klon, klev, klev)
227 real qp(klon, klev), up(klon, klev), vp(klon, klev)
228 real wt(klon, klev), water(klon, klev), evap(klon, klev)
229 real b(klon, klev), ft(klon, klev), fq(klon, klev)
230 real fu(klon, klev), fv(klon, klev)
231 real upwd(klon, klev), dnwd(klon, klev), dnwd0(klon, klev)
232 real Ma(klon, klev), mike(klon, klev), tls(klon, klev)
233 real tps(klon, klev), qprime(klon), tprime(klon)
234 real precip(klon)
235 real VPrecip(klon, klev+1)
236 real qcondc(klon, klev) ! cld
237 real wd(klon) ! gust
238
239 !-------------------------------------------------------------------
240 ! --- SET CONSTANTS AND PARAMETERS
241
242 ! -- set simulation flags:
243 ! (common cvflag)
244
245 CALL cv_flag
246
247 ! -- set thermodynamical constants:
248 ! (common cvthermo)
249
250 CALL cv_thermo
251
252 ! -- set convect parameters
253
254 ! includes microphysical parameters and parameters that
255 ! control the rate of approach to quasi-equilibrium)
256 ! (common cvparam)
257
258 if (iflag_con == 3) CALL cv3_param(klev, delt)
259
260 ! --- INITIALIZE OUTPUT ARRAYS AND PARAMETERS
261
262 do k = 1, klev
263 do i = 1, klon
264 ft1(i, k) = 0.0
265 fq1(i, k) = 0.0
266 fu1(i, k) = 0.0
267 fv1(i, k) = 0.0
268 tvp1(i, k) = 0.0
269 tp1(i, k) = 0.0
270 clw1(i, k) = 0.0
271 !ym
272 clw(i, k) = 0.0
273 gz1(i, k) = 0.
274 VPrecip1(i, k) = 0.
275 Ma1(i, k) = 0.0
276 upwd1(i, k) = 0.0
277 dnwd1(i, k) = 0.0
278 dnwd01(i, k) = 0.0
279 qcondc1(i, k) = 0.0
280 end do
281 end do
282
283 do i = 1, klon
284 precip1(i) = 0.0
285 iflag1(i) = 0
286 wd1(i) = 0.0
287 cape1(i) = 0.0
288 VPrecip1(i, klev+1) = 0.0
289 end do
290
291 if (iflag_con == 3) then
292 do il = 1, klon
293 sig1(il, klev) = sig1(il, klev) + 1.
294 sig1(il, klev) = min(sig1(il, klev), 12.1)
295 enddo
296 endif
297
298 ! --- CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY
299
300 if (iflag_con == 3) then
301 CALL cv3_prelim(klon, klev, klev + 1, t1, q1, p1, ph1, lv1, cpn1, tv1, &
302 gz1, h1, hm1, th1)
303 else
304 ! iflag_con == 4
305 CALL cv_prelim(klon, klev, klev + 1, t1, q1, p1, ph1, lv1, cpn1, tv1, &
306 gz1, h1, hm1)
307 endif
308
309 ! --- CONVECTIVE FEED
310
311 if (iflag_con == 3) then
312 CALL cv3_feed(klon, klev, t1, q1, qs1, p1, ph1, hm1, gz1, nk1, icb1, &
313 icbmax, iflag1, tnk1, qnk1, gznk1, plcl1) ! klev->na
314 else
315 ! iflag_con == 4
316 CALL cv_feed(klon, klev, t1, q1, qs1, p1, hm1, gz1, nk1, icb1, icbmax, &
317 iflag1, tnk1, qnk1, gznk1, plcl1)
318 endif
319
320 ! --- UNDILUTE (ADIABATIC) UPDRAFT / 1st part
321 ! (up through ICB for convect4, up through ICB+1 for convect3)
322 ! Calculates the lifted parcel virtual temperature at nk, the
323 ! actual temperature, and the adiabatic liquid water content.
324
325 if (iflag_con == 3) then
326 CALL cv3_undilute1(klon, klev, t1, q1, qs1, gz1, plcl1, p1, nk1, icb1, &
327 tp1, tvp1, clw1, icbs1) ! klev->na
328 else
329 ! iflag_con == 4
330 CALL cv_undilute1(klon, klev, t1, q1, qs1, gz1, p1, nk1, icb1, icbmax, &
331 tp1, tvp1, clw1)
332 endif
333
334 ! --- TRIGGERING
335
336 if (iflag_con == 3) then
337 CALL cv3_trigger(klon, klev, icb1, plcl1, p1, th1, tv1, tvp1, pbase1, &
338 buoybase1, iflag1, sig1, w01) ! klev->na
339 else
340 ! iflag_con == 4
341 CALL cv_trigger(klon, klev, icb1, cbmf1, tv1, tvp1, iflag1)
342 end if
343
344 ! --- IF THIS POINT IS REACHED, MOIST CONVECTIVE ADJUSTMENT IS NECESSARY
345
346 ncum = 0
347 do i = 1, klon
348 if(iflag1(i) == 0)then
349 ncum = ncum+1
350 idcum(ncum) = i
351 endif
352 end do
353
354 IF (ncum > 0) THEN
355 ! --- COMPRESS THE FIELDS
356 ! (-> vectorization over convective gridpoints)
357
358 if (iflag_con == 3) then
359 CALL cv3_compress(klon, klon, ncum, klev, iflag1, nk1, icb1, icbs1, &
360 plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1, t1, q1, qs1, u1, &
361 v1, gz1, th1, h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, &
362 sig1, w01, iflag, nk, icb, icbs, plcl, tnk, qnk, gznk, pbase, &
363 buoybase, t, q, qs, u, v, gz, th, h, lv, cpn, p, ph, tv, tp, &
364 tvp, clw, sig, w0)
365 else
366 ! iflag_con == 4
367 CALL cv_compress(klon, klon, ncum, klev, iflag1, nk1, icb1, cbmf1, &
368 plcl1, tnk1, qnk1, gznk1, t1, q1, qs1, u1, v1, gz1, h1, lv1, &
369 cpn1, p1, ph1, tv1, tp1, tvp1, clw1, iflag, nk, icb, cbmf, &
370 plcl, tnk, qnk, gznk, t, q, qs, u, v, gz, h, lv, cpn, p, ph, &
371 tv, tp, tvp, clw, dph)
372 endif
373
374 ! --- UNDILUTE (ADIABATIC) UPDRAFT / second part :
375 ! --- FIND THE REST OF THE LIFTED PARCEL TEMPERATURES
376 ! --- &
377 ! --- COMPUTE THE PRECIPITATION EFFICIENCIES AND THE
378 ! --- FRACTION OF PRECIPITATION FALLING OUTSIDE OF CLOUD
379 ! --- &
380 ! --- FIND THE LEVEL OF NEUTRAL BUOYANCY
381
382 if (iflag_con == 3) then
383 CALL cv3_undilute2(klon, ncum, klev, icb, icbs, nk, tnk, qnk, gznk, &
384 t, q, qs, gz, p, h, tv, lv, pbase, buoybase, plcl, inb, tp, &
385 tvp, clw, hp, ep, sigp, buoy) !na->klev
386 else
387 ! iflag_con == 4
388 CALL cv_undilute2(klon, ncum, klev, icb, nk, tnk, qnk, gznk, t, q, &
389 qs, gz, p, dph, h, tv, lv, inb, inbis, tp, tvp, clw, hp, ep, &
390 sigp, frac)
391 endif
392
393 ! --- CLOSURE
394
395 if (iflag_con == 3) then
396 CALL cv3_closure(klon, ncum, klev, icb, inb, pbase, p, ph, tv, &
397 buoy, sig, w0, cape, m) ! na->klev
398 else
399 ! iflag_con == 4
400 CALL cv_closure(klon, ncum, klev, nk, icb, tv, tvp, p, ph, dph, &
401 plcl, cpn, iflag, cbmf)
402 endif
403
404 ! --- MIXING
405
406 if (iflag_con == 3) then
407 CALL cv3_mixing(klon, ncum, klev, klev, icb, nk, inb, ph, t, q, &
408 qs, u, v, h, lv, qnk, hp, tv, tvp, ep, clw, m, sig, ment, &
409 qent, uent, vent, nent, sij, elij, ments, qents)
410 else
411 ! iflag_con == 4
412 CALL cv_mixing(klon, ncum, klev, icb, nk, inb, inbis, ph, t, q, qs, &
413 u, v, h, lv, qnk, hp, tv, tvp, ep, clw, cbmf, m, ment, qent, &
414 uent, vent, nent, sij, elij)
415 endif
416
417 ! --- UNSATURATED (PRECIPITATING) DOWNDRAFTS
418
419 if (iflag_con == 3) then
420 CALL cv3_unsat(klon, ncum, klev, klev, icb, inb, t, q, qs, gz, u, &
421 v, p, ph, th, tv, lv, cpn, ep, sigp, clw, m, ment, elij, delt, &
422 plcl, mp, qp, up, vp, wt, water, evap, b)! na->klev
423 else
424 ! iflag_con == 4
425 CALL cv_unsat(klon, ncum, klev, inb, t, q, qs, gz, u, v, p, ph, h, &
426 lv, ep, sigp, clw, m, ment, elij, iflag, mp, qp, up, vp, wt, &
427 water, evap)
428 endif
429
430 ! --- YIELD
431 ! (tendencies, precipitation, variables of interface with other
432 ! processes, etc)
433
434 if (iflag_con == 3) then
435 CALL cv3_yield(klon, ncum, klev, klev, icb, inb, delt, t, q, u, v, &
436 gz, p, ph, h, hp, lv, cpn, th, ep, clw, m, tp, mp, qp, up, vp, &
437 wt, water, evap, b, ment, qent, uent, vent, nent, elij, sig, &
438 tv, tvp, iflag, precip, VPrecip, ft, fq, fu, fv, upwd, dnwd, &
439 dnwd0, ma, mike, tls, tps, qcondc, wd)! na->klev
440 else
441 ! iflag_con == 4
442 CALL cv_yield(klon, ncum, klev, nk, icb, inb, delt, t, q, u, v, gz, &
443 p, ph, h, hp, lv, cpn, ep, clw, frac, m, mp, qp, up, vp, wt, &
444 water, evap, ment, qent, uent, vent, nent, elij, tv, tvp, &
445 iflag, wd, qprime, tprime, precip, cbmf, ft, fq, fu, fv, Ma, &
446 qcondc)
447 endif
448
449 ! --- passive tracers
450
451 if (iflag_con == 3) CALL cv3_tracer(klon, klon, ncum, klev, klev, &
452 ment, sij, da, phi)
453
454 ! --- UNCOMPRESS THE FIELDS
455
456 ! set iflag1 = 42 for non convective points
457 do i = 1, klon
458 iflag1(i) = 42
459 end do
460
461 if (iflag_con == 3) then
462 CALL cv3_uncompress(idcum(:ncum), iflag, precip, VPrecip, sig, w0, &
463 ft, fq, fu, fv, inb, Ma, upwd, dnwd, dnwd0, qcondc, wd, cape, &
464 da, phi, mp, iflag1, precip1, VPrecip1, sig1, w01, ft1, fq1, &
465 fu1, fv1, inb1, Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, &
466 cape1, da1, phi1, mp1)
467 else
468 ! iflag_con == 4
469 CALL cv_uncompress(idcum(:ncum), iflag, precip, cbmf, ft, fq, fu, &
470 fv, Ma, qcondc, iflag1, precip1, cbmf1, ft1, fq1, fu1, fv1, &
471 Ma1, qcondc1)
472 endif
473 ENDIF ! ncum>0
474
475 end SUBROUTINE cv_driver
476
477 end module cv_driver_m

  ViewVC Help
Powered by ViewVC 1.1.21