LMDZ
cv_driver.F90
Go to the documentation of this file.
1 
2 ! $Id: cv_driver.F90 2346 2015-08-21 15:13:46Z emillour $
3 
4 SUBROUTINE cv_driver(len, nd, ndp1, ntra, iflag_con, t1, q1, qs1, u1, v1, &
5  tra1, p1, ph1, iflag1, ft1, fq1, fu1, fv1, ftra1, precip1, vprecip1, &
6  cbmf1, sig1, w01, icb1, inb1, delt, ma1, upwd1, dnwd1, dnwd01, qcondc1, &
7  wd1, cape1, da1, phi1, mp1, phi21, d1a1, dam1, sij1, clw1, elij1, & !
8  ! RomP
9  evap1, ep1, epmlmmm1, eplamm1, & ! RomP
10  wdtraina1, wdtrainm1) ! RomP
11 
12  USE dimphy
13  IMPLICIT NONE
14 
15  ! .............................START PROLOGUE............................
16 
17 
18  ! All argument names (except len,nd,ntra,nloc,delt and the flags) have a
19  ! "1" appended.
20  ! The "1" is removed for the corresponding compressed (local) variables.
21 
22  ! PARAMETERS:
23  ! Name Type Usage Description
24  ! ---------- ---------- ------- ----------------------------
25 
26  ! len Integer Input first (i) dimension
27  ! nd Integer Input vertical (k) dimension
28  ! ndp1 Integer Input nd + 1
29  ! ntra Integer Input number of tracors
30  ! iflag_con Integer Input version of convect (3/4)
31  ! t1 Real Input temperature
32  ! q1 Real Input specific hum
33  ! qs1 Real Input sat specific hum
34  ! u1 Real Input u-wind
35  ! v1 Real Input v-wind
36  ! tra1 Real Input tracors
37  ! p1 Real Input full level pressure
38  ! ph1 Real Input half level pressure
39  ! iflag1 Integer Output flag for Emanuel conditions
40  ! ft1 Real Output temp tend
41  ! fq1 Real Output spec hum tend
42  ! fu1 Real Output u-wind tend
43  ! fv1 Real Output v-wind tend
44  ! ftra1 Real Output tracor tend
45  ! precip1 Real Output precipitation
46  ! VPrecip1 Real Output vertical profile of
47  ! precipitations
48  ! cbmf1 Real Output cloud base mass flux
49  ! sig1 Real In/Out section adiabatic updraft
50  ! w01 Real In/Out vertical velocity within adiab
51  ! updraft
52  ! delt Real Input time step
53  ! Ma1 Real Output mass flux adiabatic updraft
54  ! upwd1 Real Output total upward mass flux
55  ! (adiab+mixed)
56  ! dnwd1 Real Output saturated downward mass flux
57  ! (mixed)
58  ! dnwd01 Real Output unsaturated downward mass flux
59  ! qcondc1 Real Output in-cld mixing ratio of
60  ! condensed water
61  ! wd1 Real Output downdraft velocity scale for
62  ! sfc fluxes
63  ! cape1 Real Output CAPE
64 
65  ! wdtrainA1 Real Output precipitation detrained from
66  ! adiabatic draught;
67  ! used in tracer transport (cvltr)
68  ! wdtrainM1 Real Output precipitation detrained from mixed
69  ! draughts;
70  ! used in tracer transport (cvltr)
71  ! da1 Real Output used in tracer transport (cvltr)
72  ! phi1 Real Output used in tracer transport (cvltr)
73  ! mp1 Real Output used in tracer transport (cvltr)
74 
75  ! phi21 Real Output used in tracer transport (cvltr)
76 
77  ! d1a1 Real Output used in tracer transport (cvltr)
78  ! dam1 Real Output used in tracer transport (cvltr)
79 
80  ! evap1 Real Output
81  ! ep1 Real Output
82  ! sij1 Real Output
83  ! elij1 Real Output
84 
85  ! S. Bony, Mar 2002:
86  ! * Several modules corresponding to different physical processes
87  ! * Several versions of convect may be used:
88  ! - iflag_con=3: version lmd (previously named convect3)
89  ! - iflag_con=4: version 4.3b (vect. version, previously convect1/2)
90  ! + tard: - iflag_con=5: version lmd with ice (previously named convectg)
91  ! S. Bony, Oct 2002:
92  ! * Vectorization of convect3 (ie version lmd)
93 
94  ! ..............................END PROLOGUE.............................
95 
96 
97  ! Input
98  INTEGER len
99  INTEGER nd
100  INTEGER ndp1
101  INTEGER noff
102  INTEGER iflag_con
103  INTEGER ntra
104  REAL delt
105  REAL t1(len, nd)
106  REAL q1(len, nd)
107  REAL qs1(len, nd)
108  REAL u1(len, nd)
109  REAL v1(len, nd)
110  REAL tra1(len, nd, ntra)
111  REAL p1(len, nd)
112  REAL ph1(len, ndp1)
113 
114  ! Output
115  INTEGER iflag1(len)
116  REAL ft1(len, nd)
117  REAL fq1(len, nd)
118  REAL fu1(len, nd)
119  REAL fv1(len, nd)
120  REAL ftra1(len, nd, ntra)
121  REAL precip1(len)
122  REAL cbmf1(len)
123  REAL sig1(klon, klev)
124  REAL w01(klon, klev)
125  REAL vprecip1(len, nd+1)
126  REAL evap1(len, nd) !RomP
127  REAL ep1(len, nd) !RomP
128  REAL ma1(len, nd)
129  REAL upwd1(len, nd)
130  REAL dnwd1(len, nd)
131  REAL dnwd01(len, nd)
132 
133  REAL qcondc1(len, nd) ! cld
134  REAL wd1(len) ! gust
135  REAL cape1(len)
136 
137  ! RomP >>>
138  REAL wdtraina1(len, nd), wdtrainm1(len, nd)
139  REAL sij1(len, nd, nd), elij1(len, nd, nd)
140  REAL da1(len, nd), phi1(len, nd, nd), mp1(len, nd)
141 
142  REAL phi21(len, nd, nd)
143  REAL d1a1(len, nd), dam1(len, nd)
144  REAL epmlmmm1(len, nd, nd), eplamm1(len, nd)
145  ! RomP <<<
146 
147  ! -------------------------------------------------------------------
148  ! Original Prologue by Kerry Emanuel.
149  ! -------------------------------------------------------------------
150  ! --- ARGUMENTS
151  ! -------------------------------------------------------------------
152  ! --- On input:
153 
154  ! t: Array of absolute temperature (K) of dimension ND, with first
155  ! index corresponding to lowest model level. Note that this array
156  ! will be altered by the subroutine if dry convective adjustment
157  ! occurs and if IPBL is not equal to 0.
158 
159  ! q: Array of specific humidity (gm/gm) of dimension ND, with first
160  ! index corresponding to lowest model level. Must be defined
161  ! at same grid levels as T. Note that this array will be altered
162  ! if dry convective adjustment occurs and if IPBL is not equal to 0.
163 
164  ! qs: Array of saturation specific humidity of dimension ND, with first
165  ! index corresponding to lowest model level. Must be defined
166  ! at same grid levels as T. Note that this array will be altered
167  ! if dry convective adjustment occurs and if IPBL is not equal to 0.
168 
169  ! u: Array of zonal wind velocity (m/s) of dimension ND, witth first
170  ! index corresponding with the lowest model level. Defined at
171  ! same levels as T. Note that this array will be altered if
172  ! dry convective adjustment occurs and if IPBL is not equal to 0.
173 
174  ! v: Same as u but for meridional velocity.
175 
176  ! tra: Array of passive tracer mixing ratio, of dimensions (ND,NTRA),
177  ! where NTRA is the number of different tracers. If no
178  ! convective tracer transport is needed, define a dummy
179  ! input array of dimension (ND,1). Tracers are defined at
180  ! same vertical levels as T. Note that this array will be altered
181  ! if dry convective adjustment occurs and if IPBL is not equal to 0.
182 
183  ! p: Array of pressure (mb) of dimension ND, with first
184  ! index corresponding to lowest model level. Must be defined
185  ! at same grid levels as T.
186 
187  ! ph: Array of pressure (mb) of dimension ND+1, with first index
188  ! corresponding to lowest level. These pressures are defined at
189  ! levels intermediate between those of P, T, Q and QS. The first
190  ! value of PH should be greater than (i.e. at a lower level than)
191  ! the first value of the array P.
192 
193  ! nl: The maximum number of levels to which convection can penetrate, plus
194  ! 1.
195  ! NL MUST be less than or equal to ND-1.
196 
197  ! delt: The model time step (sec) between calls to CONVECT
198 
199  ! ----------------------------------------------------------------------------
200  ! --- On Output:
201 
202  ! iflag: An output integer whose value denotes the following:
203  ! VALUE INTERPRETATION
204  ! ----- --------------
205  ! 0 Moist convection occurs.
206  ! 1 Moist convection occurs, but a CFL condition
207  ! on the subsidence warming is violated. This
208  ! does not cause the scheme to terminate.
209  ! 2 Moist convection, but no precip because ep(inb) lt 0.0001
210  ! 3 No moist convection because new cbmf is 0 and old cbmf is 0.
211  ! 4 No moist convection; atmosphere is not
212  ! unstable
213  ! 6 No moist convection because ihmin le minorig.
214  ! 7 No moist convection because unreasonable
215  ! parcel level temperature or specific humidity.
216  ! 8 No moist convection: lifted condensation
217  ! level is above the 200 mb level.
218  ! 9 No moist convection: cloud base is higher
219  ! then the level NL-1.
220 
221  ! ft: Array of temperature tendency (K/s) of dimension ND, defined at
222  ! same
223  ! grid levels as T, Q, QS and P.
224 
225  ! fq: Array of specific humidity tendencies ((gm/gm)/s) of dimension ND,
226  ! defined at same grid levels as T, Q, QS and P.
227 
228  ! fu: Array of forcing of zonal velocity (m/s^2) of dimension ND,
229  ! defined at same grid levels as T.
230 
231  ! fv: Same as FU, but for forcing of meridional velocity.
232 
233  ! ftra: Array of forcing of tracer content, in tracer mixing ratio per
234  ! second, defined at same levels as T. Dimensioned (ND,NTRA).
235 
236  ! precip: Scalar convective precipitation rate (mm/day).
237 
238  ! VPrecip: Vertical profile of convective precipitation (kg/m2/s).
239 
240  ! wd: A convective downdraft velocity scale. For use in surface
241  ! flux parameterizations. See convect.ps file for details.
242 
243  ! tprime: A convective downdraft temperature perturbation scale (K).
244  ! For use in surface flux parameterizations. See convect.ps
245  ! file for details.
246 
247  ! qprime: A convective downdraft specific humidity
248  ! perturbation scale (gm/gm).
249  ! For use in surface flux parameterizations. See convect.ps
250  ! file for details.
251 
252  ! cbmf: The cloud base mass flux ((kg/m**2)/s). THIS SCALAR VALUE MUST
253  ! BE STORED BY THE CALLING PROGRAM AND RETURNED TO CONVECT AT
254  ! ITS NEXT CALL. That is, the value of CBMF must be "remembered"
255  ! by the calling program between calls to CONVECT.
256 
257  ! det: Array of detrainment mass flux of dimension ND.
258 
259  ! -------------------------------------------------------------------
260 
261  ! Local arrays
262 
263 
264  INTEGER i, k, n, il, j
265  INTEGER icbmax
266  INTEGER nk1(klon)
267  INTEGER icb1(klon)
268  INTEGER inb1(klon)
269  INTEGER icbs1(klon)
270 
271  REAL plcl1(klon)
272  REAL tnk1(klon)
273  REAL qnk1(klon)
274  REAL gznk1(klon)
275  REAL pnk1(klon)
276  REAL qsnk1(klon)
277  REAL pbase1(klon)
278  REAL buoybase1(klon)
279 
280  REAL lv1(klon, klev)
281  REAL cpn1(klon, klev)
282  REAL tv1(klon, klev)
283  REAL gz1(klon, klev)
284  REAL hm1(klon, klev)
285  REAL h1(klon, klev)
286  REAL tp1(klon, klev)
287  REAL tvp1(klon, klev)
288  REAL clw1(klon, klev)
289  REAL th1(klon, klev)
290 
291  INTEGER ncum
292 
293  ! (local) compressed fields:
294 
295  ! ym integer nloc
296  ! ym parameter (nloc=klon) ! pour l'instant
297 #define nloc klon
298  INTEGER idcum(nloc)
299  INTEGER iflag(nloc), nk(nloc), icb(nloc)
300  INTEGER nent(nloc, klev)
301  INTEGER icbs(nloc)
302  INTEGER inb(nloc), inbis(nloc)
303 
304  REAL cbmf(nloc), plcl(nloc), tnk(nloc), qnk(nloc), gznk(nloc)
305  REAL t(nloc, klev), q(nloc, klev), qs(nloc, klev)
306  REAL u(nloc, klev), v(nloc, klev)
307  REAL gz(nloc, klev), h(nloc, klev), lv(nloc, klev), cpn(nloc, klev)
308  REAL p(nloc, klev), ph(nloc, klev+1), tv(nloc, klev), tp(nloc, klev)
309  REAL clw(nloc, klev)
310  REAL dph(nloc, klev)
311  REAL pbase(nloc), buoybase(nloc), th(nloc, klev)
312  REAL tvp(nloc, klev)
313  REAL sig(nloc, klev), w0(nloc, klev)
314  REAL hp(nloc, klev), ep(nloc, klev), sigp(nloc, klev)
315  REAL frac(nloc), buoy(nloc, klev)
316  REAL cape(nloc)
317  REAL m(nloc, klev), ment(nloc, klev, klev), qent(nloc, klev, klev)
318  REAL uent(nloc, klev, klev), vent(nloc, klev, klev)
319  REAL ments(nloc, klev, klev), qents(nloc, klev, klev)
320  REAL sij(nloc, klev, klev), elij(nloc, klev, klev)
321  REAL qp(nloc, klev), up(nloc, klev), vp(nloc, klev)
322  REAL wt(nloc, klev), water(nloc, klev), evap(nloc, klev)
323  REAL b(nloc, klev), ft(nloc, klev), fq(nloc, klev)
324  REAL fu(nloc, klev), fv(nloc, klev)
325  REAL upwd(nloc, klev), dnwd(nloc, klev), dnwd0(nloc, klev)
326  REAL ma(nloc, klev), mike(nloc, klev), tls(nloc, klev)
327  REAL tps(nloc, klev), qprime(nloc), tprime(nloc)
328  REAL precip(nloc)
329  REAL vprecip(nloc, klev+1)
330  REAL tra(nloc, klev, ntra), trap(nloc, klev, ntra)
331  REAL ftra(nloc, klev, ntra), traent(nloc, klev, klev, ntra)
332  REAL qcondc(nloc, klev) ! cld
333  REAL wd(nloc) ! gust
334 
335  ! RomP >>>
336  REAL da(nloc, klev), phi(nloc, klev, klev), mp(nloc, klev)
337  REAL epmlmmm(nloc, klev, klev), eplamm(nloc, klev)
338  REAL phi2(nloc, klev, klev)
339  REAL d1a(nloc, klev), dam(nloc, klev)
340  REAL wdtraina(nloc, klev), wdtrainm(nloc, klev)
341  REAL sigd(nloc)
342  ! RomP <<<
343 
344  nent(:, :) = 0
345  ! -------------------------------------------------------------------
346  ! --- SET CONSTANTS AND PARAMETERS
347  ! -------------------------------------------------------------------
348  ! print *, '-> cv_driver' !jyg
349  ! -- set simulation flags:
350  ! (common cvflag)
351 
352  CALL cv_flag(0)
353 
354  ! -- set thermodynamical constants:
355  ! (common cvthermo)
356 
357  CALL cv_thermo(iflag_con)
358 
359  ! -- set convect parameters
360 
361  ! includes microphysical parameters and parameters that
362  ! control the rate of approach to quasi-equilibrium)
363  ! (common cvparam)
364 
365 
366  IF (iflag_con==30) THEN
367  CALL cv30_param(nd, delt)
368  END IF
369 
370  IF (iflag_con==4) THEN
371  CALL cv_param(nd)
372  END IF
373 
374  ! ---------------------------------------------------------------------
375  ! --- INITIALIZE OUTPUT ARRAYS AND PARAMETERS
376  ! ---------------------------------------------------------------------
377 
378  ft1(:, :) = 0.0
379  fq1(:, :) = 0.0
380  fu1(:, :) = 0.0
381  fv1(:, :) = 0.0
382  tvp1(:, :) = 0.0
383  tp1(:, :) = 0.0
384  clw1(:, :) = 0.0
385  ! ym
386  clw(:, :) = 0.0
387  gz1(:, :) = 0.
388  vprecip1(:, :) = 0.
389  ma1(:, :) = 0.0
390  upwd1(:, :) = 0.0
391  dnwd1(:, :) = 0.0
392  dnwd01(:, :) = 0.0
393  qcondc1(:, :) = 0.0
394 
395  ftra1(:, :, :) = 0.0
396 
397  elij1(:, :, :) = 0.0
398  sij1(:, :, :) = 0.0
399 
400  precip1(:) = 0.0
401  iflag1(:) = 0
402  wd1(:) = 0.0
403  cape1(:) = 0.0
404 
405  IF (iflag_con==30) THEN
406  DO il = 1, len
407  sig1(il, nd) = sig1(il, nd) + 1.
408  sig1(il, nd) = amin1(sig1(il,nd), 12.1)
409  END DO
410  END IF
411 
412  ! RomP >>>
413  wdtraina1(:, :) = 0.
414  wdtrainm1(:, :) = 0.
415  da1(:, :) = 0.
416  phi1(:, :, :) = 0.
417  epmlmmm1(:, :, :) = 0.
418  eplamm1(:, :) = 0.
419  mp1(:, :) = 0.
420  evap1(:, :) = 0.
421  ep1(:, :) = 0.
422  sij1(:, :, :) = 0.
423  elij1(:, :, :) = 0.
424  phi21(:, :, :) = 0.
425  d1a1(:, :) = 0.
426  dam1(:, :) = 0.
427  ! RomP <<<
428 
429  ! --------------------------------------------------------------------
430  ! --- CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY
431  ! --------------------------------------------------------------------
432 
433  IF (iflag_con==30) THEN
434 
435  ! print*,'Emanuel version 30 '
436  CALL cv30_prelim(len, nd, ndp1, t1, q1, p1, ph1 & ! nd->na
437  , lv1, cpn1, tv1, gz1, h1, hm1, th1)
438  END IF
439 
440  IF (iflag_con==4) THEN
441  CALL cv_prelim(len, nd, ndp1, t1, q1, p1, ph1, lv1, cpn1, tv1, gz1, h1, &
442  hm1)
443  END IF
444 
445  ! --------------------------------------------------------------------
446  ! --- CONVECTIVE FEED
447  ! --------------------------------------------------------------------
448 
449  IF (iflag_con==30) THEN
450  CALL cv30_feed(len, nd, t1, q1, qs1, p1, ph1, hm1, gz1 & !
451  ! nd->na
452  , nk1, icb1, icbmax, iflag1, tnk1, qnk1, gznk1, plcl1)
453  END IF
454 
455  IF (iflag_con==4) THEN
456  CALL cv_feed(len, nd, t1, q1, qs1, p1, hm1, gz1, nk1, icb1, icbmax, &
457  iflag1, tnk1, qnk1, gznk1, plcl1)
458  END IF
459 
460  ! --------------------------------------------------------------------
461  ! --- UNDILUTE (ADIABATIC) UPDRAFT / 1st part
462  ! (up through ICB for convect4, up through ICB+1 for convect3)
463  ! Calculates the lifted parcel virtual temperature at nk, the
464  ! actual temperature, and the adiabatic liquid water content.
465  ! --------------------------------------------------------------------
466 
467  IF (iflag_con==30) THEN
468  CALL cv30_undilute1(len, nd, t1, q1, qs1, gz1, plcl1, p1, nk1, icb1 & ! nd->na
469  , tp1, tvp1, clw1, icbs1)
470  END IF
471 
472  IF (iflag_con==4) THEN
473  CALL cv_undilute1(len, nd, t1, q1, qs1, gz1, p1, nk1, icb1, icbmax, tp1, &
474  tvp1, clw1)
475  END IF
476 
477  ! -------------------------------------------------------------------
478  ! --- TRIGGERING
479  ! -------------------------------------------------------------------
480 
481  IF (iflag_con==30) THEN
482  CALL cv30_trigger(len, nd, icb1, plcl1, p1, th1, tv1, tvp1 & !
483  ! nd->na
484  , pbase1, buoybase1, iflag1, sig1, w01)
485  END IF
486 
487  IF (iflag_con==4) THEN
488  CALL cv_trigger(len, nd, icb1, cbmf1, tv1, tvp1, iflag1)
489  END IF
490 
491  ! =====================================================================
492  ! --- IF THIS POINT IS REACHED, MOIST CONVECTIVE ADJUSTMENT IS NECESSARY
493  ! =====================================================================
494 
495  ncum = 0
496  DO i = 1, len
497  IF (iflag1(i)==0) THEN
498  ncum = ncum + 1
499  idcum(ncum) = i
500  END IF
501  END DO
502 
503  ! print*,'cv_driver : klon, ncum = ',len,ncum
504 
505  IF (ncum>0) THEN
506 
507  ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
508  ! --- COMPRESS THE FIELDS
509  ! (-> vectorization over convective gridpoints)
510  ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
511 
512  IF (iflag_con==30) THEN
513  CALL cv30_compress(len, nloc, ncum, nd, ntra, iflag1, nk1, icb1, icbs1, &
514  plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1, t1, q1, qs1, u1, v1, &
515  gz1, th1, tra1, h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, sig1, &
516  w01, iflag, nk, icb, icbs, plcl, tnk, qnk, gznk, pbase, buoybase, t, &
517  q, qs, u, v, gz, th, tra, h, lv, cpn, p, ph, tv, tp, tvp, clw, sig, &
518  w0)
519  END IF
520 
521  IF (iflag_con==4) THEN
522  CALL cv_compress(len, nloc, ncum, nd, iflag1, nk1, icb1, cbmf1, plcl1, &
523  tnk1, qnk1, gznk1, t1, q1, qs1, u1, v1, gz1, h1, lv1, cpn1, p1, ph1, &
524  tv1, tp1, tvp1, clw1, iflag, nk, icb, cbmf, plcl, tnk, qnk, gznk, t, &
525  q, qs, u, v, gz, h, lv, cpn, p, ph, tv, tp, tvp, clw, dph)
526  END IF
527 
528  ! -------------------------------------------------------------------
529  ! --- UNDILUTE (ADIABATIC) UPDRAFT / second part :
530  ! --- FIND THE REST OF THE LIFTED PARCEL TEMPERATURES
531  ! --- &
532  ! --- COMPUTE THE PRECIPITATION EFFICIENCIES AND THE
533  ! --- FRACTION OF PRECIPITATION FALLING OUTSIDE OF CLOUD
534  ! --- &
535  ! --- FIND THE LEVEL OF NEUTRAL BUOYANCY
536  ! -------------------------------------------------------------------
537 
538  IF (iflag_con==30) THEN
539  CALL cv30_undilute2(nloc, ncum, nd, icb, icbs, nk & !na->nd
540  , tnk, qnk, gznk, t, q, qs, gz, p, h, tv, lv, pbase, buoybase, plcl, &
541  inb, tp, tvp, clw, hp, ep, sigp, buoy)
542  END IF
543 
544  IF (iflag_con==4) THEN
545  CALL cv_undilute2(nloc, ncum, nd, icb, nk, tnk, qnk, gznk, t, q, qs, &
546  gz, p, dph, h, tv, lv, inb, inbis, tp, tvp, clw, hp, ep, sigp, frac)
547  END IF
548 
549  ! -------------------------------------------------------------------
550  ! --- CLOSURE
551  ! -------------------------------------------------------------------
552 
553  IF (iflag_con==30) THEN
554  CALL cv30_closure(nloc, ncum, nd, icb, inb & ! na->nd
555  , pbase, p, ph, tv, buoy, sig, w0, cape, m)
556  END IF
557 
558  IF (iflag_con==4) THEN
559  CALL cv_closure(nloc, ncum, nd, nk, icb, tv, tvp, p, ph, dph, plcl, &
560  cpn, iflag, cbmf)
561  END IF
562 
563  ! -------------------------------------------------------------------
564  ! --- MIXING
565  ! -------------------------------------------------------------------
566 
567  IF (iflag_con==30) THEN
568  CALL cv30_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb & !
569  ! na->nd
570  , ph, t, q, qs, u, v, tra, h, lv, qnk, hp, tv, tvp, ep, clw, m, sig, &
571  ment, qent, uent, vent, sij, elij, ments, qents, traent)
572  END IF
573 
574  IF (iflag_con==4) THEN
575  CALL cv_mixing(nloc, ncum, nd, icb, nk, inb, inbis, ph, t, q, qs, u, v, &
576  h, lv, qnk, hp, tv, tvp, ep, clw, cbmf, m, ment, qent, uent, vent, &
577  nent, sij, elij)
578  END IF
579 
580  ! -------------------------------------------------------------------
581  ! --- UNSATURATED (PRECIPITATING) DOWNDRAFTS
582  ! -------------------------------------------------------------------
583 
584  IF (iflag_con==30) THEN
585  ! RomP >>>
586  CALL cv30_unsat(nloc, ncum, nd, nd, ntra, icb, inb & ! na->nd
587  , t, q, qs, gz, u, v, tra, p, ph, th, tv, lv, cpn, ep, sigp, clw, m, &
588  ment, elij, delt, plcl, mp, qp, up, vp, trap, wt, water, evap, b, &
589  wdtraina, wdtrainm)
590  ! RomP <<<
591  END IF
592 
593  IF (iflag_con==4) THEN
594  CALL cv_unsat(nloc, ncum, nd, inb, t, q, qs, gz, u, v, p, ph, h, lv, &
595  ep, sigp, clw, m, ment, elij, iflag, mp, qp, up, vp, wt, water, evap)
596  END IF
597 
598  ! -------------------------------------------------------------------
599  ! --- YIELD
600  ! (tendencies, precipitation, variables of interface with other
601  ! processes, etc)
602  ! -------------------------------------------------------------------
603 
604  IF (iflag_con==30) THEN
605  CALL cv30_yield(nloc, ncum, nd, nd, ntra & ! na->nd
606  , icb, inb, delt, t, q, u, v, tra, gz, p, ph, h, hp, lv, cpn, th, ep, &
607  clw, m, tp, mp, qp, up, vp, trap, wt, water, evap, b, ment, qent, &
608  uent, vent, nent, elij, traent, sig, tv, tvp, iflag, precip, vprecip, &
609  ft, fq, fu, fv, ftra, upwd, dnwd, dnwd0, ma, mike, tls, tps, qcondc, &
610  wd)
611  END IF
612 
613  IF (iflag_con==4) THEN
614  CALL cv_yield(nloc, ncum, nd, nk, icb, inb, delt, t, q, u, v, gz, p, &
615  ph, h, hp, lv, cpn, ep, clw, frac, m, mp, qp, up, vp, wt, water, &
616  evap, ment, qent, uent, vent, nent, elij, tv, tvp, iflag, wd, qprime, &
617  tprime, precip, cbmf, ft, fq, fu, fv, ma, qcondc)
618  END IF
619 
620  ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
621  ! --- passive tracers
622  ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
623 
624  IF (iflag_con==30) THEN
625  ! RomP >>>
626  CALL cv30_tracer(nloc, len, ncum, nd, nd, ment, sij, da, phi, phi2, &
627  d1a, dam, ep, vprecip, elij, clw, epmlmmm, eplamm, icb, inb)
628  ! RomP <<<
629  END IF
630 
631  ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
632  ! --- UNCOMPRESS THE FIELDS
633  ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
634  ! set iflag1 =42 for non convective points
635  DO i = 1, len
636  iflag1(i) = 42
637  END DO
638 
639  IF (iflag_con==30) THEN
640  CALL cv30_uncompress(nloc, len, ncum, nd, ntra, idcum, iflag, precip, &
641  vprecip, evap, ep, sig, w0 & !RomP
642  , ft, fq, fu, fv, ftra, inb, ma, upwd, dnwd, dnwd0, qcondc, wd, cape, &
643  da, phi, mp, phi2, d1a, dam, sij & !RomP
644  , elij, clw, epmlmmm, eplamm & !RomP
645  , wdtraina, wdtrainm & !RomP
646  , iflag1, precip1, vprecip1, evap1, ep1, sig1, w01 & !RomP
647  , ft1, fq1, fu1, fv1, ftra1, inb1, ma1, upwd1, dnwd1, dnwd01, &
648  qcondc1, wd1, cape1, da1, phi1, mp1, phi21, d1a1, dam1, sij1 & !RomP
649  , elij1, clw1, epmlmmm1, eplamm1 & !RomP
650  , wdtraina1, wdtrainm1) !RomP
651  END IF
652 
653  IF (iflag_con==4) THEN
654  CALL cv_uncompress(nloc, len, ncum, nd, idcum, iflag, precip, cbmf, ft, &
655  fq, fu, fv, ma, qcondc, iflag1, precip1, cbmf1, ft1, fq1, fu1, fv1, &
656  ma1, qcondc1)
657  END IF
658 
659  END IF ! ncum>0
660 
661  ! print *, 'fin cv_driver ->' !jyg
662  RETURN
663 END SUBROUTINE cv_driver
664 
665 ! ==================================================================
666 SUBROUTINE cv_flag(iflag_ice_thermo)
667  IMPLICIT NONE
668 
669  ! Argument : iflag_ice_thermo : ice thermodynamics is taken into account if
670  ! iflag_ice_thermo >=1
671  INTEGER iflag_ice_thermo
672 
673  include "cvflag.h"
674 
675  ! -- si .TRUE., on rend la gravite plus explicite et eventuellement
676  ! differente de 10.0 dans convect3:
677  cvflag_grav = .true.
678  cvflag_ice = iflag_ice_thermo >= 1
679 
680  RETURN
681 END SUBROUTINE cv_flag
682 
683 ! ==================================================================
684 SUBROUTINE cv_thermo(iflag_con)
685  IMPLICIT NONE
686 
687  ! -------------------------------------------------------------
688  ! Set thermodynamical constants for convectL
689  ! -------------------------------------------------------------
690 
691  include "YOMCST.h"
692  include "cvthermo.h"
693 
694  INTEGER iflag_con
695 
696 
697  ! original set from convect:
698  IF (iflag_con==4) THEN
699  cpd = 1005.7
700  cpv = 1870.0
701  cl = 4190.0
702  rrv = 461.5
703  rrd = 287.04
704  lv0 = 2.501e6
705  g = 9.8
706  t0 = 273.15
707  grav = g
708  ELSE
709 
710  ! constants consistent with LMDZ:
711  cpd = rcpd
712  cpv = rcpv
713  cl = rcw
714  ci = rcs
715  rrv = rv
716  rrd = rd
717  lv0 = rlvtt
718  lf0 = rlstt - rlvtt
719  g = rg ! not used in convect3
720  ! ori t0 = RTT
721  t0 = 273.15 ! convect3 (RTT=273.16)
722  ! maf grav= 10. ! implicitely or explicitely used in convect3
723  grav = g ! implicitely or explicitely used in convect3
724  END IF
725 
726  rowl = 1000.0 !(a quelle variable de YOMCST cela correspond-il?)
727 
728  clmcpv = cl - cpv
729  clmcpd = cl - cpd
730  clmci = cl - ci
731  cpdmcp = cpd - cpv
732  cpvmcpd = cpv - cpd
733  cpvmcl = cl - cpv ! for convect3
734  eps = rrd/rrv
735  epsi = 1.0/eps
736  epsim1 = epsi - 1.0
737  ! ginv=1.0/g
738  ginv = 1.0/grav
739  hrd = 0.5*rrd
740 
741  RETURN
742 END SUBROUTINE cv_thermo
!$Id!Thermodynamical constants for t0 real clmcpv
Definition: cvthermo.h:6
!$Id!Thermodynamical constants for t0 real clmci real epsim1 real hrd real grav COMMON cvthermo rowl t0
Definition: cvthermo.h:6
!$Id!Thermodynamical constants for cpv
Definition: cvthermo.h:6
!$Id!logical cvflag_grav logical cvflag_ice COMMON cvflag cvflag_grav
Definition: cvflag.h:7
subroutine cv30_undilute1(len, nd, t, q, qs, gz, plcl, p, nk, icb, tp, tvp, clw, icbs)
!$Id mode_top_bound COMMON comconstr g
Definition: comconst.h:7
!$Id!Thermodynamical constants for t0 real cpvmcl
Definition: cvthermo.h:6
subroutine cv_param(nd)
Definition: cv_routines.F90:5
subroutine cv_closure(nloc, ncum, nd, nk, icb, tv, tvp, p, ph, dph, plcl, cpn, iflag, cbmf)
!$Id!Thermodynamical constants for t0 real clmci real epsim1 real hrd real grav COMMON cvthermo rowl cpvmcl hrd
Definition: cvthermo.h:6
integer, save klon
Definition: dimphy.F90:3
subroutine cv30_mixing(nloc, ncum, nd, na, ntra, icb, nk, inb, ph, t, rr, rs, u, v, tra, h, lv, qnk, hp, tv, tvp, ep, clw, m, sig, ment, qent, uent, vent, sij, elij, ments, qents, traent)
integer, save klev
Definition: dimphy.F90:7
subroutine cv_mixing(nloc, ncum, nd, icb, nk, inb, inb1, ph, t, q, qs, u, v, h, lv, qnk, hp, tv, tvp, ep, clw, cbmf, m, ment, qent, uent, vent, nent, sij, elij)
!$Id!Thermodynamical constants for t0 real clmci real epsim1 real hrd real grav COMMON cvthermo rowl cpvmcl clmci
Definition: cvthermo.h:6
!$Id!Thermodynamical constants for t0 real clmci real epsim1 real ginv
Definition: cvthermo.h:6
!$Id!Thermodynamical constants for ci
Definition: cvthermo.h:6
!$Id!Thermodynamical constants for t0 real clmci real eps
Definition: cvthermo.h:6
subroutine cv_compress(len, nloc, ncum, nd, iflag1, nk1, icb1, cbmf1, plcl1, tnk1, qnk1, gznk1, t1, q1, qs1, u1, v1, gz1, h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, iflag, nk, icb, cbmf, plcl, tnk, qnk, gznk, t, q, qs, u, v, gz, h, lv, cpn, p, ph, tv, tp, tvp, clw, dph)
subroutine cv_prelim(len, nd, ndp1, t, q, p, ph, lv, cpn, tv, gz, h, hm)
Definition: cv_routines.F90:77
!$Id!Thermodynamical constants for rrd
Definition: cvthermo.h:6
subroutine cv_trigger(len, nd, icb, cbmf, tv, tvp, iflag)
subroutine cv_undilute2(nloc, ncum, nd, icb, nk, tnk, qnk, gznk, t, q, qs, gz, p, dph, h, tv, lv, inb, inb1, tp, tvp, clw, hp, ep, sigp, frac)
subroutine cv_unsat(nloc, ncum, nd, inb, t, q, qs, gz, u, v, p, ph, h, lv, ep, sigp, clw, m, ment, elij, iflag, mp, qp, up, vp, wt, water, evap)
!$Id!Thermodynamical constants for cl
Definition: cvthermo.h:6
!$Id!Thermodynamical constants for t0 real clmcpd
Definition: cvthermo.h:6
subroutine cv_driver(len, nd, ndp1, ntra, iflag_con, t1, q1, qs1, u1, v1,tra1, p1, ph1, iflag1, ft1, fq1, fu1, fv1, ftra1, precip1, vprecip1,cbmf1, sig1, w01, icb1, inb1, delt, ma1, upwd1, dnwd1, dnwd01, qcondc1,wd1, cape1, da1, phi1, mp1, phi21, d1a1, dam1, sij1, clw1, elij1,
Definition: cv_driver.F90:9
subroutine cv30_closure(nloc, ncum, nd, icb, inb, pbase, p, ph, tv, buoy, sig, w0, cape, m)
subroutine cv30_undilute2(nloc, ncum, nd, icb, icbs, nk, tnk, qnk, gznk, t, q, qs, gz, p, h, tv, lv, pbase, buoybase, plcl, inb, tp, tvp, clw, hp, ep, sigp, buoy)
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
subroutine cv30_prelim(len, nd, ndp1, t, q, p, ph, lv, cpn, tv, gz, h, hm, th)
subroutine cv30_feed(len, nd, t, q, qs, p, ph, hm, gz, nk, icb, icbmax, iflag, tnk, qnk, gznk, plcl)
subroutine cv30_unsat(nloc, ncum, nd, na, ntra, icb, inb, t, rr, rs, gz, u, v, tra, p, ph, th, tv, lv, cpn, ep, sigp, clw, m, ment, elij, delt, plcl, mp, rp, up, vp, trap, wt, water, evap, b, wdtraina, wdtrainm)
subroutine cv_undilute1(len, nd, t, q, qs, gz, p, nk, icb, icbmax, tp, tvp, clw)
subroutine cv30_uncompress(nloc, len, ncum, nd, ntra, idcum, iflag, precip, vprecip, evap, ep, sig, w0, ft, fq, fu, fv, ftra, inb, ma, upwd, dnwd, dnwd0, qcondc, wd, cape, da, phi, mp, phi2, d1a, dam, sij, elij, clw, epmlmmm, eplamm, wdtraina, wdtrainm, iflag1, precip1, vprecip1, evap1, ep1, sig1, w01, ft1, fq1, fu1, fv1, ftra1, inb1, ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, cape1, da1, phi1, mp1, phi21, d1a1, dam1, sij1, elij1, clw1, epmlmmm1, eplamm1, wdtraina1, wdtrainm1)
subroutine cv_thermo(iflag_con)
Definition: cv_driver.F90:685
subroutine cv_yield(nloc, ncum, nd, nk, icb, inb, delt, t, q, u, v, gz, p, ph, h, hp, lv, cpn, ep, clw, frac, m, mp, qp, up, vp, wt, water, evap, ment, qent, uent, vent, nent, elij, tv, tvp, iflag, wd, qprime, tprime, precip, cbmf, ft, fq, fu, fv, ma, qcondc)
subroutine cv30_param(nd, delt)
!$Id!Thermodynamical constants for t0 real clmci real epsim1 real hrd real grav COMMON cvthermo rowl cpvmcl epsim1
Definition: cvthermo.h:6
subroutine cv30_compress(len, nloc, ncum, nd, ntra, iflag1, nk1, icb1, icbs1, plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1, t1, q1, qs1, u1, v1, gz1, th1, tra1, h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, sig1, w01, iflag, nk, icb, icbs, plcl, tnk, qnk, gznk, pbase, buoybase, t, q, qs, u, v, gz, th, tra, h, lv, cpn, p, ph, tv, tp, tvp, clw, sig, w0)
subroutine cv_flag(iflag_ice_thermo)
Definition: cv_driver.F90:667
subroutine cv_uncompress(nloc, len, ncum, nd, idcum, iflag, precip, cbmf, ft, fq, fu, fv, ma, qcondc, iflag1, precip1, cbmf1, ft1, fq1, fu1, fv1, ma1, qcondc1)
subroutine cv_feed(len, nd, t, q, qs, p, hm, gz, nk, icb, icbmax, iflag, tnk, qnk, gznk, plcl)
!$Id!Thermodynamical constants for t0 real cpvmcpd
Definition: cvthermo.h:6
!$Id!Thermodynamical constants for t0 real clmci real epsim1 real hrd real grav COMMON cvthermo cpd
Definition: cvthermo.h:6
!$Id!Thermodynamical constants for rrv
Definition: cvthermo.h:6
!$Id!Thermodynamical constants for t0 real cpdmcp
Definition: cvthermo.h:6
!$Id!Thermodynamical constants for lv0
Definition: cvthermo.h:6
subroutine cv30_trigger(len, nd, icb, plcl, p, th, tv, tvp, pbase, buoybase, iflag, sig, w0)
!$Id!Thermodynamical constants for rowl
Definition: cvthermo.h:6
Definition: dimphy.F90:1
!$Id!Thermodynamical constants for t0 real clmci real epsi
Definition: cvthermo.h:6
subroutine cv30_yield(nloc, ncum, nd, na, ntra, icb, inb, delt, t, rr, u, v, tra, gz, p, ph, h, hp, lv, cpn, th, ep, clw, m, tp, mp, rp, up, vp, trap, wt, water, evap, b, ment, qent, uent, vent, nent, elij, traent, sig, tv, tvp, iflag, precip, vprecip, ft, fr, fu, fv, ftra, upwd, dnwd, dnwd0, ma, mike, tls, tps, qcondc, wd)
subroutine cv30_tracer(nloc, len, ncum, nd, na, ment, sij, da, phi, phi2, d1a, dam, ep, vprecip, elij, clw, epmlmmm, eplamm, icb, inb)
real rg
Definition: comcstphy.h:1
!$Id!Thermodynamical constants for lf0
Definition: cvthermo.h:6