/[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

revision 139 by guez, Tue May 26 17:46:03 2015 UTC revision 188 by guez, Tue Mar 22 16:31:39 2016 UTC
# Line 4  module cv_driver_m Line 4  module cv_driver_m
4    
5  contains  contains
6    
7    SUBROUTINE cv_driver(t1, q1, qs1, u1, v1, p1, ph1, iflag1, ft1, &    SUBROUTINE cv_driver(t1, q1, qs1, u1, v1, p1, ph1, iflag1, ft1, fq1, fu1, &
8         fq1, fu1, fv1, precip1, VPrecip1, cbmf1, sig1, w01, icb1, inb1, delt, &         fv1, precip1, VPrecip1, sig1, w01, icb1, inb1, delt, Ma1, upwd1, &
9         Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, cape1, da1, phi1, mp1)         dnwd1, dnwd01, qcondc1, wd1, cape1, da1, phi1, mp1)
10    
11      ! From LMDZ4/libf/phylmd/cv_driver.F, version 1.3, 2005/04/15 12:36:17      ! From LMDZ4/libf/phylmd/cv_driver.F, version 1.3, 2005/04/15 12:36:17
12      ! Main driver for convection      ! Main driver for convection
# Line 14  contains Line 14  contains
14    
15      ! Several modules corresponding to different physical processes      ! Several modules corresponding to different physical processes
16    
17      ! Several versions of convect may be used:      use cv30_closure_m, only: cv30_closure
18      ! - iflag_con = 3: version lmd      use cv30_compress_m, only: cv30_compress
19      ! - iflag_con = 4: version 4.3b      use cv30_feed_m, only: cv30_feed
20        use cv30_mixing_m, only: cv30_mixing
21      use clesphys2, only: iflag_con      use cv30_param_m, only: cv30_param, nl
22      use cv3_compress_m, only: cv3_compress      use cv30_prelim_m, only: cv30_prelim
23      use cv3_feed_m, only: cv3_feed      use cv30_tracer_m, only: cv30_tracer
24      use cv3_mixing_m, only: cv3_mixing      use cv30_uncompress_m, only: cv30_uncompress
25      use cv3_param_m, only: cv3_param      use cv30_undilute2_m, only: cv30_undilute2
26      use cv3_prelim_m, only: cv3_prelim      use cv30_unsat_m, only: cv30_unsat
27      use cv3_tracer_m, only: cv3_tracer      use cv30_yield_m, only: cv30_yield
     use cv3_uncompress_m, only: cv3_uncompress  
     use cv3_unsat_m, only: cv3_unsat  
     use cv3_yield_m, only: cv3_yield  
     use cv_feed_m, only: cv_feed  
     use cv_uncompress_m, only: cv_uncompress  
28      USE dimphy, ONLY: klev, klon      USE dimphy, ONLY: klev, klon
29    
30      real, intent(in):: t1(klon, klev) ! temperature      real, intent(in):: t1(klon, klev)
31      real, intent(in):: q1(klon, klev) ! specific hum      ! temperature (K), with first index corresponding to lowest model
32      real, intent(in):: qs1(klon, klev) ! sat specific hum      ! level
     real, intent(in):: u1(klon, klev) ! u-wind  
     real, intent(in):: v1(klon, klev) ! v-wind  
     real, intent(in):: p1(klon, klev) ! full level pressure  
     real, intent(in):: ph1(klon, klev + 1) ! half level pressure  
     integer, intent(out):: iflag1(klon) ! flag for Emanuel conditions  
     real, intent(out):: ft1(klon, klev) ! temp tend  
     real, intent(out):: fq1(klon, klev) ! spec hum tend  
     real, intent(out):: fu1(klon, klev) ! u-wind tend  
     real, intent(out):: fv1(klon, klev) ! v-wind tend  
     real, intent(out):: precip1(klon) ! precipitation  
33    
34      real, intent(out):: VPrecip1(klon, klev+1)      real, intent(in):: q1(klon, klev)
35      ! vertical profile of precipitation      ! Specific humidity, with first index corresponding to lowest
36        ! model level. Must be defined at same grid levels as T1.
37    
38        real, intent(in):: qs1(klon, klev)
39        ! Saturation specific humidity, with first index corresponding to
40        ! lowest model level. Must be defined at same grid levels as
41        ! T1.
42    
43        real, intent(in):: u1(klon, klev), v1(klon, klev)
44        ! Zonal wind and meridional velocity (m/s), witth first index
45        ! corresponding with the lowest model level. Defined at same
46        ! levels as T1.
47    
48        real, intent(in):: p1(klon, klev)
49        ! Full level pressure (mb) of dimension KLEV, with first index
50        ! corresponding to lowest model level. Must be defined at same
51        ! grid levels as T1.
52    
53        real, intent(in):: ph1(klon, klev + 1)
54        ! Half level pressure (mb), with first index corresponding to
55        ! lowest level. These pressures are defined at levels intermediate
56        ! between those of P1, T1, Q1 and QS1. The first value of PH
57        ! should be greater than (i.e. at a lower level than) the first
58        ! value of the array P1.
59    
60        integer, intent(out):: iflag1(klon)
61        ! Flag for Emanuel conditions.
62    
63        ! 0: Moist convection occurs.
64    
65        ! 1: Moist convection occurs, but a CFL condition on the
66        ! subsidence warming is violated. This does not cause the scheme
67        ! to terminate.
68    
69        ! 2: Moist convection, but no precipitation because ep(inb) < 1e-4
70    
71        ! 3: No moist convection because new cbmf is 0 and old cbmf is 0.
72    
73        ! 4: No moist convection; atmosphere is not unstable
74    
75        ! 6: No moist convection because ihmin le minorig.
76    
77        ! 7: No moist convection because unreasonable parcel level
78        ! temperature or specific humidity.
79    
80        ! 8: No moist convection: lifted condensation level is above the
81        ! 200 mb level.
82    
83        ! 9: No moist convection: cloud base is higher then the level NL-1.
84    
85        real, intent(out):: ft1(klon, klev)
86        ! Temperature tendency (K/s), defined at same grid levels as T1,
87        ! Q1, QS1 and P1.
88    
89        real, intent(out):: fq1(klon, klev)
90        ! Specific humidity tendencies (s-1), defined at same grid levels
91        ! as T1, Q1, QS1 and P1.
92    
93        real, intent(out):: fu1(klon, klev), fv1(klon, klev)
94        ! Forcing (tendency) of zonal and meridional velocity (m/s^2),
95        ! defined at same grid levels as T1.
96    
97        real, intent(out):: precip1(klon) ! convective precipitation rate (mm/day)
98    
99        real, intent(out):: VPrecip1(klon, klev + 1)
100        ! vertical profile of convective precipitation (kg/m2/s)
101    
     real, intent(inout):: cbmf1(klon) ! cloud base mass flux  
102      real, intent(inout):: sig1(klon, klev) ! section adiabatic updraft      real, intent(inout):: sig1(klon, klev) ! section adiabatic updraft
103    
104      real, intent(inout):: w01(klon, klev)      real, intent(inout):: w01(klon, klev)
# Line 57  contains Line 106  contains
106    
107      integer, intent(out):: icb1(klon)      integer, intent(out):: icb1(klon)
108      integer, intent(inout):: inb1(klon)      integer, intent(inout):: inb1(klon)
109      real, intent(in):: delt ! time step      real, intent(in):: delt ! the model time step (sec) between calls
     real Ma1(klon, klev)  
     ! Ma1 Real Output mass flux adiabatic updraft  
     real, intent(out):: upwd1(klon, klev) ! total upward mass flux (adiab+mixed)  
     real, intent(out):: dnwd1(klon, klev) ! saturated downward mass flux (mixed)  
     real, intent(out):: dnwd01(klon, klev) ! unsaturated downward mass flux  
   
     real qcondc1(klon, klev) ! cld  
     ! qcondc1 Real Output in-cld mixing ratio of condensed water  
     real wd1(klon) ! gust  
     ! wd1 Real Output downdraft velocity scale for sfc fluxes  
     real cape1(klon)  
     ! cape1 Real Output CAPE  
   
     real, intent(inout):: da1(klon, klev), phi1(klon, klev, klev)  
     real, intent(inout):: mp1(klon, klev)  
110    
111      ! --- ARGUMENTS      real Ma1(klon, klev) ! Output mass flux adiabatic updraft
112    
113      ! --- On input:      real, intent(out):: upwd1(klon, klev)
114        ! total upward mass flux (adiab + mixed)
115    
116      ! t: Array of absolute temperature (K) of dimension KLEV, with first      real, intent(out):: dnwd1(klon, klev) ! saturated downward mass flux (mixed)
117      ! index corresponding to lowest model level. Note that this array      real, intent(out):: dnwd01(klon, klev) ! unsaturated downward mass flux
     ! 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 KLEV, 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 KLEV, 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 KLEV, 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.  
   
     ! p: Array of pressure (mb) of dimension KLEV, with first  
     ! index corresponding to lowest model level. Must be defined  
     ! at same grid levels as T.  
   
     ! ph: Array of pressure (mb) of dimension KLEV+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 KLEV-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 KLEV, defined at same  
     ! grid levels as T, Q, QS and P.  
   
     ! fq: Array of specific humidity tendencies ((gm/gm)/s) of dimension KLEV,  
     ! defined at same grid levels as T, Q, QS and P.  
   
     ! fu: Array of forcing of zonal velocity (m/s^2) of dimension KLEV,  
     ! defined at same grid levels as T.  
   
     ! fv: Same as FU, but for forcing of meridional velocity.  
   
     ! precip: Scalar convective precipitation rate (mm/day).  
118    
119      ! VPrecip: Vertical profile of convective precipitation (kg/m2/s).      real qcondc1(klon, klev) ! Output in-cld mixing ratio of condensed water
120    
121      ! wd: A convective downdraft velocity scale. For use in surface      real wd1(klon) ! gust
122        ! Output downdraft velocity scale for surface fluxes
123        ! A convective downdraft velocity scale. For use in surface
124      ! flux parameterizations. See convect.ps file for details.      ! flux parameterizations. See convect.ps file for details.
125    
126      ! tprime: A convective downdraft temperature perturbation scale (K).      real cape1(klon) ! Output
127      ! For use in surface flux parameterizations. See convect.ps      real, intent(inout):: da1(klon, klev), phi1(klon, klev, klev)
128      ! file for details.      real, intent(inout):: mp1(klon, klev)
   
     ! 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 KLEV.  
129    
130      ! Local arrays      ! Local:
131    
132      real da(klon, klev), phi(klon, klev, klev), mp(klon, klev)      real da(klon, klev), phi(klon, klev, klev), mp(klon, klev)
133    
# Line 199  contains Line 156  contains
156    
157      integer ncum      integer ncum
158    
159      ! (local) compressed fields:      ! Compressed fields:
160    
161      integer idcum(klon)      integer idcum(klon)
162      integer iflag(klon), nk(klon), icb(klon)      integer iflag(klon), nk(klon), icb(klon)
163      integer nent(klon, klev)      integer nent(klon, klev)
164      integer icbs(klon)      integer icbs(klon)
165      integer inb(klon), inbis(klon)      integer inb(klon)
166    
167      real cbmf(klon), plcl(klon), tnk(klon), qnk(klon), gznk(klon)      real plcl(klon), tnk(klon), qnk(klon), gznk(klon)
168      real t(klon, klev), q(klon, klev), qs(klon, klev)      real t(klon, klev), q(klon, klev), qs(klon, klev)
169      real u(klon, klev), v(klon, klev)      real u(klon, klev), v(klon, klev)
170      real gz(klon, klev), h(klon, klev), lv(klon, klev), cpn(klon, klev)      real gz(klon, klev), h(klon, klev), lv(klon, klev), cpn(klon, klev)
171      real p(klon, klev), ph(klon, klev+1), tv(klon, klev), tp(klon, klev)      real p(klon, klev), ph(klon, klev + 1), tv(klon, klev), tp(klon, klev)
172      real clw(klon, klev)      real clw(klon, klev)
     real dph(klon, klev)  
173      real pbase(klon), buoybase(klon), th(klon, klev)      real pbase(klon), buoybase(klon), th(klon, klev)
174      real tvp(klon, klev)      real tvp(klon, klev)
175      real sig(klon, klev), w0(klon, klev)      real sig(klon, klev), w0(klon, klev)
176      real hp(klon, klev), ep(klon, klev), sigp(klon, klev)      real hp(klon, klev), ep(klon, klev), sigp(klon, klev)
177      real frac(klon), buoy(klon, klev)      real buoy(klon, klev)
178      real cape(klon)      real cape(klon)
179      real m(klon, klev), ment(klon, klev, klev), qent(klon, klev, klev)      real m(klon, klev), ment(klon, klev, klev), qent(klon, klev, klev)
180      real uent(klon, klev, klev), vent(klon, klev, klev)      real uent(klon, klev, klev), vent(klon, klev, klev)
# Line 226  contains Line 182  contains
182      real sij(klon, klev, klev), elij(klon, klev, klev)      real sij(klon, klev, klev), elij(klon, klev, klev)
183      real qp(klon, klev), up(klon, klev), vp(klon, klev)      real qp(klon, klev), up(klon, klev), vp(klon, klev)
184      real wt(klon, klev), water(klon, klev), evap(klon, klev)      real wt(klon, klev), water(klon, klev), evap(klon, klev)
185      real b(klon, klev), ft(klon, klev), fq(klon, klev)      real, allocatable:: b(:, :) ! (ncum, nl)
186        real ft(klon, klev), fq(klon, klev)
187      real fu(klon, klev), fv(klon, klev)      real fu(klon, klev), fv(klon, klev)
188      real upwd(klon, klev), dnwd(klon, klev), dnwd0(klon, klev)      real upwd(klon, klev), dnwd(klon, klev), dnwd0(klon, klev)
189      real Ma(klon, klev), mike(klon, klev), tls(klon, klev)      real Ma(klon, klev), mike(klon, klev), tls(klon, klev)
190      real tps(klon, klev), qprime(klon), tprime(klon)      real tps(klon, klev)
191      real precip(klon)      real precip(klon)
192      real VPrecip(klon, klev+1)      real VPrecip(klon, klev + 1)
193      real qcondc(klon, klev) ! cld      real qcondc(klon, klev) ! cld
194      real wd(klon) ! gust      real wd(klon) ! gust
195    
196      !-------------------------------------------------------------------      !-------------------------------------------------------------------
     ! --- SET CONSTANTS AND PARAMETERS  
   
     ! -- set simulation flags:  
     ! (common cvflag)  
197    
198      CALL cv_flag      ! SET CONSTANTS AND PARAMETERS
199    
200      ! -- set thermodynamical constants:      ! set thermodynamical constants:
201      ! (common cvthermo)      ! (common cvthermo)
   
202      CALL cv_thermo      CALL cv_thermo
203    
204      ! -- set convect parameters      ! set convect parameters
   
205      ! includes microphysical parameters and parameters that      ! includes microphysical parameters and parameters that
206      ! control the rate of approach to quasi-equilibrium)      ! control the rate of approach to quasi-equilibrium)
207      ! (common cvparam)      ! (common cvparam)
208        CALL cv30_param(delt)
209    
210      if (iflag_con == 3) CALL cv3_param(klev, delt)      ! INITIALIZE OUTPUT ARRAYS AND PARAMETERS
   
     ! --- INITIALIZE OUTPUT ARRAYS AND PARAMETERS  
211    
212      do k = 1, klev      do k = 1, klev
213         do i = 1, klon         do i = 1, klon
214            ft1(i, k) = 0.0            ft1(i, k) = 0.
215            fq1(i, k) = 0.0            fq1(i, k) = 0.
216            fu1(i, k) = 0.0            fu1(i, k) = 0.
217            fv1(i, k) = 0.0            fv1(i, k) = 0.
218            tvp1(i, k) = 0.0            tvp1(i, k) = 0.
219            tp1(i, k) = 0.0            tp1(i, k) = 0.
220            clw1(i, k) = 0.0            clw1(i, k) = 0.
221            !ym            clw(i, k) = 0.
           clw(i, k) = 0.0  
222            gz1(i, k) = 0.            gz1(i, k) = 0.
223            VPrecip1(i, k) = 0.            VPrecip1(i, k) = 0.
224            Ma1(i, k) = 0.0            Ma1(i, k) = 0.
225            upwd1(i, k) = 0.0            upwd1(i, k) = 0.
226            dnwd1(i, k) = 0.0            dnwd1(i, k) = 0.
227            dnwd01(i, k) = 0.0            dnwd01(i, k) = 0.
228            qcondc1(i, k) = 0.0            qcondc1(i, k) = 0.
229         end do         end do
230      end do      end do
231    
232      do i = 1, klon      do i = 1, klon
233         precip1(i) = 0.0         precip1(i) = 0.
234         iflag1(i) = 0         iflag1(i) = 0
235         wd1(i) = 0.0         wd1(i) = 0.
236         cape1(i) = 0.0         cape1(i) = 0.
237         VPrecip1(i, klev+1) = 0.0         VPrecip1(i, klev + 1) = 0.
238      end do      end do
239    
240      if (iflag_con == 3) then      do il = 1, klon
241         do il = 1, klon         sig1(il, klev) = sig1(il, klev) + 1.
242            sig1(il, klev) = sig1(il, klev) + 1.         sig1(il, klev) = min(sig1(il, klev), 12.1)
243            sig1(il, klev) = min(sig1(il, klev), 12.1)      enddo
244         enddo  
245      endif      ! CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY
246        CALL cv30_prelim(klon, klev, klev + 1, t1, q1, p1, ph1, lv1, cpn1, tv1, &
247      ! --- CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY           gz1, h1, hm1, th1)
248    
249      if (iflag_con == 3) then      ! CONVECTIVE FEED
250         CALL cv3_prelim(klon, klev, klev + 1, t1, q1, p1, ph1, lv1, cpn1, tv1, &      CALL cv30_feed(klon, klev, t1, q1, qs1, p1, ph1, gz1, nk1, icb1, &
251              gz1, h1, hm1, th1)           icbmax, iflag1, tnk1, qnk1, gznk1, plcl1) ! klev->na
     else  
        ! iflag_con == 4  
        CALL cv_prelim(klon, klev, klev + 1, t1, q1, p1, ph1, lv1, cpn1, tv1, &  
             gz1, h1, hm1)  
     endif  
   
     ! --- CONVECTIVE FEED  
   
     if (iflag_con == 3) then  
        CALL cv3_feed(klon, klev, t1, q1, qs1, p1, ph1, hm1, gz1, nk1, icb1, &  
             icbmax, iflag1, tnk1, qnk1, gznk1, plcl1) ! klev->na  
     else  
        ! iflag_con == 4  
        CALL cv_feed(klon, klev, t1, q1, qs1, p1, hm1, gz1, nk1, icb1, icbmax, &  
             iflag1, tnk1, qnk1, gznk1, plcl1)  
     endif  
252    
253      ! --- UNDILUTE (ADIABATIC) UPDRAFT / 1st part      ! UNDILUTE (ADIABATIC) UPDRAFT / 1st part
254      ! (up through ICB for convect4, up through ICB+1 for convect3)      ! (up through ICB for convect4, up through ICB + 1 for convect3)
255      ! Calculates the lifted parcel virtual temperature at nk, the      ! Calculates the lifted parcel virtual temperature at nk, the
256      ! actual temperature, and the adiabatic liquid water content.      ! actual temperature, and the adiabatic liquid water content.
257        CALL cv30_undilute1(klon, klev, t1, q1, qs1, gz1, plcl1, p1, nk1, icb1, &
258             tp1, tvp1, clw1, icbs1) ! klev->na
259    
260      if (iflag_con == 3) then      ! TRIGGERING
261         CALL cv3_undilute1(klon, klev, t1, q1, qs1, gz1, plcl1, p1, nk1, icb1, &      CALL cv30_trigger(klon, klev, icb1, plcl1, p1, th1, tv1, tvp1, pbase1, &
262              tp1, tvp1, clw1, icbs1) ! klev->na           buoybase1, iflag1, sig1, w01) ! klev->na
     else  
        ! iflag_con == 4  
        CALL cv_undilute1(klon, klev, t1, q1, qs1, gz1, p1, nk1, icb1, icbmax, &  
             tp1, tvp1, clw1)  
     endif  
   
     ! --- TRIGGERING  
   
     if (iflag_con == 3) then  
        CALL cv3_trigger(klon, klev, icb1, plcl1, p1, th1, tv1, tvp1, pbase1, &  
             buoybase1, iflag1, sig1, w01) ! klev->na  
     else  
        ! iflag_con == 4  
        CALL cv_trigger(klon, klev, icb1, cbmf1, tv1, tvp1, iflag1)  
     end if  
263    
264      ! --- IF THIS POINT IS REACHED, MOIST CONVECTIVE ADJUSTMENT IS NECESSARY      ! Moist convective adjustment is necessary
265    
266      ncum = 0      ncum = 0
267      do i = 1, klon      do i = 1, klon
268         if(iflag1(i) == 0)then         if (iflag1(i) == 0) then
269            ncum = ncum+1            ncum = ncum + 1
270            idcum(ncum) = i            idcum(ncum) = i
271         endif         endif
272      end do      end do
273    
274      IF (ncum > 0) THEN      IF (ncum > 0) THEN
275         ! --- COMPRESS THE FIELDS         allocate(b(ncum, nl))
        ! (-> vectorization over convective gridpoints)  
   
        if (iflag_con == 3) then  
           CALL cv3_compress(klon, klon, ncum, klev, iflag1, nk1, icb1, icbs1, &  
                plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1, t1, q1, qs1, u1, &  
                v1, gz1, th1, h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, &  
                sig1, w01, iflag, nk, icb, icbs, plcl, tnk, qnk, gznk, pbase, &  
                buoybase, t, q, qs, u, v, gz, th, h, lv, cpn, p, ph, tv, tp, &  
                tvp, clw, sig, w0)  
        else  
           ! iflag_con == 4  
           CALL cv_compress(klon, klon, ncum, klev, iflag1, nk1, icb1, cbmf1, &  
                plcl1, tnk1, qnk1, gznk1, t1, q1, qs1, u1, v1, gz1, h1, lv1, &  
                cpn1, p1, ph1, tv1, tp1, tvp1, clw1, iflag, nk, icb, cbmf, &  
                plcl, tnk, qnk, gznk, t, q, qs, u, v, gz, h, lv, cpn, p, ph, &  
                tv, tp, tvp, clw, dph)  
        endif  
   
        ! --- UNDILUTE (ADIABATIC) UPDRAFT / second part :  
        ! --- FIND THE REST OF THE LIFTED PARCEL TEMPERATURES  
        ! --- &  
        ! --- COMPUTE THE PRECIPITATION EFFICIENCIES AND THE  
        ! --- FRACTION OF PRECIPITATION FALLING OUTSIDE OF CLOUD  
        ! --- &  
        ! --- FIND THE LEVEL OF NEUTRAL BUOYANCY  
   
        if (iflag_con == 3) then  
           CALL cv3_undilute2(klon, ncum, klev, icb, icbs, nk, tnk, qnk, gznk, &  
                t, q, qs, gz, p, h, tv, lv, pbase, buoybase, plcl, inb, tp, &  
                tvp, clw, hp, ep, sigp, buoy) !na->klev  
        else  
           ! iflag_con == 4  
           CALL cv_undilute2(klon, ncum, klev, icb, nk, tnk, qnk, gznk, t, q, &  
                qs, gz, p, dph, h, tv, lv, inb, inbis, tp, tvp, clw, hp, ep, &  
                sigp, frac)  
        endif  
   
        ! --- CLOSURE  
276    
277         if (iflag_con == 3) then         ! COMPRESS THE FIELDS
278            CALL cv3_closure(klon, ncum, klev, icb, inb, pbase, p, ph, tv, &         ! (-> vectorization over convective gridpoints)
279                 buoy, sig, w0, cape, m) ! na->klev         CALL cv30_compress(klon, klon, ncum, klev, iflag1, nk1, icb1, icbs1, &
280         else              plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1, t1, q1, qs1, u1, &
281            ! iflag_con == 4              v1, gz1, th1, h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, &
282            CALL cv_closure(klon, ncum, klev, nk, icb, tv, tvp, p, ph, dph, &              sig1, w01, iflag, nk, icb, icbs, plcl, tnk, qnk, gznk, pbase, &
283                 plcl, cpn, iflag, cbmf)              buoybase, t, q, qs, u, v, gz, th, h, lv, cpn, p, ph, tv, tp, &
284         endif              tvp, clw, sig, w0)
285    
286         ! --- MIXING         CALL cv30_undilute2(ncum, icb, icbs, nk, tnk, qnk, gznk, t, qs, gz, p, &
287                h, tv, lv, pbase, buoybase, plcl, inb(:ncum), tp, tvp, clw, hp, &
288         if (iflag_con == 3) then              ep, sigp, buoy)
289            CALL cv3_mixing(klon, ncum, klev, klev, icb, nk, inb, ph, t, q, &  
290                 qs, u, v, h, lv, qnk, hp, tv, tvp, ep, clw, m, sig, ment, &         ! CLOSURE
291                 qent, uent, vent, nent, sij, elij, ments, qents)         CALL cv30_closure(klon, ncum, klev, icb, inb, pbase, p, ph, tv, &
292         else              buoy, sig, w0, cape, m) ! na->klev
293            ! iflag_con == 4  
294            CALL cv_mixing(klon, ncum, klev, icb, nk, inb, inbis, ph, t, q, qs, &         ! MIXING
295                 u, v, h, lv, qnk, hp, tv, tvp, ep, clw, cbmf, m, ment, qent, &         CALL cv30_mixing(klon, ncum, klev, klev, icb, nk, inb, t, q, qs, u, &
296                 uent, vent, nent, sij, elij)              v, h, lv, hp, ep, clw, m, sig, ment, qent, uent, vent, nent, &
297         endif              sij, elij, ments, qents)
298    
299         ! --- UNSATURATED (PRECIPITATING) DOWNDRAFTS         ! Unsaturated (precipitating) downdrafts
300           CALL cv30_unsat(icb(:ncum), inb(:ncum), t, q, qs, gz, u, v, p, ph, th, &
301         if (iflag_con == 3) then              tv, lv, cpn, ep, sigp, clw, m, ment, elij, delt, plcl, mp, qp, &
302            CALL cv3_unsat(klon, ncum, klev, klev, icb, inb, t, q, qs, gz, u, &              up, vp, wt, water, evap, b)
303                 v, p, ph, th, tv, lv, cpn, ep, sigp, clw, m, ment, elij, delt, &  
304                 plcl, mp, qp, up, vp, wt, water, evap, b)! na->klev         ! Yield (tendencies, precipitation, variables of interface with
305         else         ! other processes, etc)
306            ! iflag_con == 4         CALL cv30_yield(icb(:ncum), inb(:ncum), delt, t, q, u, v, gz, p, ph, &
307            CALL cv_unsat(klon, ncum, klev, inb, t, q, qs, gz, u, v, p, ph, h, &              h, hp, lv, cpn, th, ep, clw, m, tp, mp, qp, up, vp, wt, &
308                 lv, ep, sigp, clw, m, ment, elij, iflag, mp, qp, up, vp, wt, &              water(:ncum, :nl), evap(:ncum, :nl), b, ment, qent, uent, vent, &
309                 water, evap)              nent, elij, sig, tv, tvp, iflag, precip, VPrecip, ft, fq, fu, fv, &
310         endif              upwd, dnwd, dnwd0, ma, mike, tls, tps, qcondc, wd)
   
        ! --- YIELD  
        ! (tendencies, precipitation, variables of interface with other  
        ! processes, etc)  
   
        if (iflag_con == 3) then  
           CALL cv3_yield(klon, ncum, klev, klev, icb, inb, delt, t, q, u, v, &  
                gz, p, ph, h, hp, lv, cpn, th, ep, clw, m, tp, mp, qp, up, vp, &  
                wt, water, evap, b, ment, qent, uent, vent, nent, elij, sig, &  
                tv, tvp, iflag, precip, VPrecip, ft, fq, fu, fv, upwd, dnwd, &  
                dnwd0, ma, mike, tls, tps, qcondc, wd)! na->klev  
        else  
           ! iflag_con == 4  
           CALL cv_yield(klon, ncum, klev, nk, icb, inb, delt, t, q, u, v, gz, &  
                p, ph, h, hp, lv, cpn, ep, clw, frac, m, mp, qp, up, vp, wt, &  
                water, evap, ment, qent, uent, vent, nent, elij, tv, tvp, &  
                iflag, wd, qprime, tprime, precip, cbmf, ft, fq, fu, fv, Ma, &  
                qcondc)  
        endif  
   
        ! --- passive tracers  
311    
312         if (iflag_con == 3) CALL cv3_tracer(klon, ncum, klev, ment, sij, da, phi)         ! passive tracers
313           CALL cv30_tracer(klon, ncum, klev, ment, sij, da, phi)
314    
315         ! --- UNCOMPRESS THE FIELDS         ! UNCOMPRESS THE FIELDS
316    
317         ! set iflag1 = 42 for non convective points         ! set iflag1 = 42 for non convective points
318         do i = 1, klon         iflag1 = 42
           iflag1(i) = 42  
        end do  
319    
320         if (iflag_con == 3) then         CALL cv30_uncompress(idcum(:ncum), iflag, precip, VPrecip, sig, w0, &
321            CALL cv3_uncompress(idcum(:ncum), iflag, precip, VPrecip, sig, w0, &              ft, fq, fu, fv, inb, Ma, upwd, dnwd, dnwd0, qcondc, wd, cape, &
322                 ft, fq, fu, fv, inb, Ma, upwd, dnwd, dnwd0, qcondc, wd, cape, &              da, phi, mp, iflag1, precip1, VPrecip1, sig1, w01, ft1, fq1, &
323                 da, phi, mp, iflag1, precip1, VPrecip1, sig1, w01, ft1, fq1, &              fu1, fv1, inb1, Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, &
324                 fu1, fv1, inb1, Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, &              cape1, da1, phi1, mp1)
325                 cape1, da1, phi1, mp1)      ENDIF
        else  
           ! iflag_con == 4  
           CALL cv_uncompress(idcum(:ncum), iflag, precip, cbmf, ft, fq, fu, &  
                fv, Ma, qcondc, iflag1, precip1, cbmf1, ft1, fq1, fu1, fv1, &  
                Ma1, qcondc1)  
        endif  
     ENDIF ! ncum>0  
326    
327    end SUBROUTINE cv_driver    end SUBROUTINE cv_driver
328    

Legend:
Removed from v.139  
changed lines
  Added in v.188

  ViewVC Help
Powered by ViewVC 1.1.21