source: LMDZ5/trunk/libf/phylmd/cv_driver.F @ 1742

Last change on this file since 1742 was 1742, checked in by idelkadi, 11 years ago

1- Inclusion des developpements de la these de Romain Pilon sur le
lessivage des aerosols :

a/ par les pluies convectives (modifs cv30_routines et cv3_routines pour

sortir les champs nécessaires au calcul off-line ; modif cvltr)

b/ par les pluies stratiformes (modifs phytrac et introduction

lsc_scav).

2- Choix entre plusieurs schemas pour les pluies stratiformes, commande
par iflag_lscav.

3- Quelques corrections dans la convection "Nouvelle Physique" pour
assurer la conservation des traceurs (cv3p1_mixing et cva_driver) (travail
de Robin Locatelli).

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