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

Legend:
Removed from v.47  
changed lines
  Added in v.62

  ViewVC Help
Powered by ViewVC 1.1.21