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

Diff of /trunk/Sources/phylmd/cv_driver.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

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

Legend:
Removed from v.14  
changed lines
  Added in v.76

  ViewVC Help
Powered by ViewVC 1.1.21