/[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 150 by guez, Thu Jun 18 13:49:26 2015 UTC revision 186 by guez, Mon Mar 21 15:36:26 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_compress_m, only: cv30_compress
18      ! - iflag_con = 3: version lmd      use cv30_feed_m, only: cv30_feed
19      ! - iflag_con = 4: version 4.3b      use cv30_mixing_m, only: cv30_mixing
20        use cv30_param_m, only: cv30_param
21      use clesphys2, only: iflag_con      use cv30_prelim_m, only: cv30_prelim
22      use cv3_compress_m, only: cv3_compress      use cv30_tracer_m, only: cv30_tracer
23      use cv3_feed_m, only: cv3_feed      use cv30_uncompress_m, only: cv30_uncompress
24      use cv3_mixing_m, only: cv3_mixing      use cv30_undilute2_m, only: cv30_undilute2
25      use cv3_param_m, only: cv3_param      use cv30_unsat_m, only: cv30_unsat
26      use cv3_prelim_m, only: cv3_prelim      use cv30_yield_m, only: cv30_yield
     use cv3_tracer_m, only: cv3_tracer  
     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  
27      USE dimphy, ONLY: klev, klon      USE dimphy, ONLY: klev, klon
28    
29      real, intent(in):: t1(klon, klev) ! temperature      real, intent(in):: t1(klon, klev) ! temperature
# Line 46  contains Line 40  contains
40      real, intent(out):: fv1(klon, klev) ! v-wind tend      real, intent(out):: fv1(klon, klev) ! v-wind tend
41      real, intent(out):: precip1(klon) ! precipitation      real, intent(out):: precip1(klon) ! precipitation
42    
43      real, intent(out):: VPrecip1(klon, klev+1)      real, intent(out):: VPrecip1(klon, klev + 1)
44      ! vertical profile of precipitation      ! vertical profile of precipitation
45    
     real, intent(inout):: cbmf1(klon) ! cloud base mass flux  
46      real, intent(inout):: sig1(klon, klev) ! section adiabatic updraft      real, intent(inout):: sig1(klon, klev) ! section adiabatic updraft
47    
48      real, intent(inout):: w01(klon, klev)      real, intent(inout):: w01(klon, klev)
# Line 60  contains Line 53  contains
53      real, intent(in):: delt ! time step      real, intent(in):: delt ! time step
54      real Ma1(klon, klev)      real Ma1(klon, klev)
55      ! Ma1 Real Output mass flux adiabatic updraft      ! Ma1 Real Output mass flux adiabatic updraft
56      real, intent(out):: upwd1(klon, klev) ! total upward mass flux (adiab+mixed)  
57        real, intent(out):: upwd1(klon, klev)
58        ! total upward mass flux (adiab + mixed)
59    
60      real, intent(out):: dnwd1(klon, klev) ! saturated downward mass flux (mixed)      real, intent(out):: dnwd1(klon, klev) ! saturated downward mass flux (mixed)
61      real, intent(out):: dnwd01(klon, klev) ! unsaturated downward mass flux      real, intent(out):: dnwd01(klon, klev) ! unsaturated downward mass flux
62    
# Line 74  contains Line 70  contains
70      real, intent(inout):: da1(klon, klev), phi1(klon, klev, klev)      real, intent(inout):: da1(klon, klev), phi1(klon, klev, klev)
71      real, intent(inout):: mp1(klon, klev)      real, intent(inout):: mp1(klon, klev)
72    
73      ! --- ARGUMENTS      ! ARGUMENTS
74    
75      ! --- On input:      ! On input:
76    
77      ! t: Array of absolute temperature (K) of dimension KLEV, with first      ! t: Array of absolute temperature (K) of dimension KLEV, with first
78      ! index corresponding to lowest model level. Note that this array      ! index corresponding to lowest model level. Note that this array
# Line 104  contains Line 100  contains
100      ! index corresponding to lowest model level. Must be defined      ! index corresponding to lowest model level. Must be defined
101      ! at same grid levels as T.      ! at same grid levels as T.
102    
103      ! ph: Array of pressure (mb) of dimension KLEV+1, with first index      ! ph: Array of pressure (mb) of dimension KLEV + 1, with first index
104      ! corresponding to lowest level. These pressures are defined at      ! corresponding to lowest level. These pressures are defined at
105      ! levels intermediate between those of P, T, Q and QS. The first      ! levels intermediate between those of P, T, Q and QS. The first
106      ! value of PH should be greater than (i.e. at a lower level than)      ! value of PH should be greater than (i.e. at a lower level than)
# Line 115  contains Line 111  contains
111    
112      ! delt: The model time step (sec) between calls to CONVECT      ! delt: The model time step (sec) between calls to CONVECT
113    
114      ! --- On Output:      ! On Output:
115    
116      ! iflag: An output integer whose value denotes the following:      ! iflag: An output integer whose value denotes the following:
117      ! VALUE INTERPRETATION      ! VALUE INTERPRETATION
# Line 205  contains Line 201  contains
201      integer iflag(klon), nk(klon), icb(klon)      integer iflag(klon), nk(klon), icb(klon)
202      integer nent(klon, klev)      integer nent(klon, klev)
203      integer icbs(klon)      integer icbs(klon)
204      integer inb(klon), inbis(klon)      integer inb(klon)
205    
206      real cbmf(klon), plcl(klon), tnk(klon), qnk(klon), gznk(klon)      real plcl(klon), tnk(klon), qnk(klon), gznk(klon)
207      real t(klon, klev), q(klon, klev), qs(klon, klev)      real t(klon, klev), q(klon, klev), qs(klon, klev)
208      real u(klon, klev), v(klon, klev)      real u(klon, klev), v(klon, klev)
209      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)
210      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)
211      real clw(klon, klev)      real clw(klon, klev)
     real dph(klon, klev)  
212      real pbase(klon), buoybase(klon), th(klon, klev)      real pbase(klon), buoybase(klon), th(klon, klev)
213      real tvp(klon, klev)      real tvp(klon, klev)
214      real sig(klon, klev), w0(klon, klev)      real sig(klon, klev), w0(klon, klev)
215      real hp(klon, klev), ep(klon, klev), sigp(klon, klev)      real hp(klon, klev), ep(klon, klev), sigp(klon, klev)
216      real frac(klon), buoy(klon, klev)      real buoy(klon, klev)
217      real cape(klon)      real cape(klon)
218      real m(klon, klev), ment(klon, klev, klev), qent(klon, klev, klev)      real m(klon, klev), ment(klon, klev, klev), qent(klon, klev, klev)
219      real uent(klon, klev, klev), vent(klon, klev, klev)      real uent(klon, klev, klev), vent(klon, klev, klev)
# Line 230  contains Line 225  contains
225      real fu(klon, klev), fv(klon, klev)      real fu(klon, klev), fv(klon, klev)
226      real upwd(klon, klev), dnwd(klon, klev), dnwd0(klon, klev)      real upwd(klon, klev), dnwd(klon, klev), dnwd0(klon, klev)
227      real Ma(klon, klev), mike(klon, klev), tls(klon, klev)      real Ma(klon, klev), mike(klon, klev), tls(klon, klev)
228      real tps(klon, klev), qprime(klon), tprime(klon)      real tps(klon, klev)
229      real precip(klon)      real precip(klon)
230      real VPrecip(klon, klev+1)      real VPrecip(klon, klev + 1)
231      real qcondc(klon, klev) ! cld      real qcondc(klon, klev) ! cld
232      real wd(klon) ! gust      real wd(klon) ! gust
233    
234      !-------------------------------------------------------------------      !-------------------------------------------------------------------
     ! --- SET CONSTANTS AND PARAMETERS  
   
     ! -- set simulation flags:  
     ! (common cvflag)  
235    
236      CALL cv_flag      ! SET CONSTANTS AND PARAMETERS
237    
238      ! -- set thermodynamical constants:      ! set thermodynamical constants:
239      ! (common cvthermo)      ! (common cvthermo)
   
240      CALL cv_thermo      CALL cv_thermo
241    
242      ! -- set convect parameters      ! set convect parameters
   
243      ! includes microphysical parameters and parameters that      ! includes microphysical parameters and parameters that
244      ! control the rate of approach to quasi-equilibrium)      ! control the rate of approach to quasi-equilibrium)
245      ! (common cvparam)      ! (common cvparam)
246    
247      if (iflag_con == 3) CALL cv3_param(klev, delt)      CALL cv30_param(delt)
248    
249      ! --- INITIALIZE OUTPUT ARRAYS AND PARAMETERS      ! INITIALIZE OUTPUT ARRAYS AND PARAMETERS
250    
251      do k = 1, klev      do k = 1, klev
252         do i = 1, klon         do i = 1, klon
# Line 268  contains Line 257  contains
257            tvp1(i, k) = 0.0            tvp1(i, k) = 0.0
258            tp1(i, k) = 0.0            tp1(i, k) = 0.0
259            clw1(i, k) = 0.0            clw1(i, k) = 0.0
           !ym  
260            clw(i, k) = 0.0            clw(i, k) = 0.0
261            gz1(i, k) = 0.            gz1(i, k) = 0.
262            VPrecip1(i, k) = 0.            VPrecip1(i, k) = 0.
# Line 285  contains Line 273  contains
273         iflag1(i) = 0         iflag1(i) = 0
274         wd1(i) = 0.0         wd1(i) = 0.0
275         cape1(i) = 0.0         cape1(i) = 0.0
276         VPrecip1(i, klev+1) = 0.0         VPrecip1(i, klev + 1) = 0.0
277      end do      end do
278    
279      if (iflag_con == 3) then      do il = 1, klon
280         do il = 1, klon         sig1(il, klev) = sig1(il, klev) + 1.
281            sig1(il, klev) = sig1(il, klev) + 1.         sig1(il, klev) = min(sig1(il, klev), 12.1)
282            sig1(il, klev) = min(sig1(il, klev), 12.1)      enddo
283         enddo  
284      endif      ! CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY
285        CALL cv30_prelim(klon, klev, klev + 1, t1, q1, p1, ph1, lv1, cpn1, tv1, &
286      ! --- CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY           gz1, h1, hm1, th1)
287    
288      if (iflag_con == 3) then      ! CONVECTIVE FEED
289         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, &
290              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, 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  
291    
292      ! --- UNDILUTE (ADIABATIC) UPDRAFT / 1st part      ! UNDILUTE (ADIABATIC) UPDRAFT / 1st part
293      ! (up through ICB for convect4, up through ICB+1 for convect3)      ! (up through ICB for convect4, up through ICB + 1 for convect3)
294      ! Calculates the lifted parcel virtual temperature at nk, the      ! Calculates the lifted parcel virtual temperature at nk, the
295      ! actual temperature, and the adiabatic liquid water content.      ! actual temperature, and the adiabatic liquid water content.
296        CALL cv30_undilute1(klon, klev, t1, q1, qs1, gz1, plcl1, p1, nk1, icb1, &
297             tp1, tvp1, clw1, icbs1) ! klev->na
298    
299      if (iflag_con == 3) then      ! TRIGGERING
300         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, &
301              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  
302    
303      ! --- IF THIS POINT IS REACHED, MOIST CONVECTIVE ADJUSTMENT IS NECESSARY      ! Moist convective adjustment is necessary
304    
305      ncum = 0      ncum = 0
306      do i = 1, klon      do i = 1, klon
307         if(iflag1(i) == 0)then         if (iflag1(i) == 0) then
308            ncum = ncum+1            ncum = ncum + 1
309            idcum(ncum) = i            idcum(ncum) = i
310         endif         endif
311      end do      end do
312    
313      IF (ncum > 0) THEN      IF (ncum > 0) THEN
314         ! --- COMPRESS THE FIELDS         ! COMPRESS THE FIELDS
315         ! (-> vectorization over convective gridpoints)         ! (-> vectorization over convective gridpoints)
316           CALL cv30_compress(klon, klon, ncum, klev, iflag1, nk1, icb1, icbs1, &
317                plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1, t1, q1, qs1, u1, &
318                v1, gz1, th1, h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, &
319                sig1, w01, iflag, nk, icb, icbs, plcl, tnk, qnk, gznk, pbase, &
320                buoybase, t, q, qs, u, v, gz, th, h, lv, cpn, p, ph, tv, tp, &
321                tvp, clw, sig, w0)
322    
323           ! Undilute (adiabatic) updraft, second part: find the rest of
324           ! the lifted parcel temperatures; compute the precipitation
325           ! efficiencies and the fraction of precipitation falling
326           ! outside of cloud; find the level of neutral buoyancy.
327           CALL cv30_undilute2(klon, ncum, klev, icb, icbs, nk, tnk, qnk, gznk, &
328                t, qs, gz, p, h, tv, lv, pbase, buoybase, plcl, inb, tp, &
329                tvp, clw, hp, ep, sigp, buoy) !na->klev
330    
331           ! CLOSURE
332           CALL cv30_closure(klon, ncum, klev, icb, inb, pbase, p, ph, tv, &
333                buoy, sig, w0, cape, m) ! na->klev
334    
335           ! MIXING
336           CALL cv30_mixing(klon, ncum, klev, klev, icb, nk, inb, t, q, qs, u, &
337                v, h, lv, hp, ep, clw, m, sig, ment, qent, uent, vent, nent, &
338                sij, elij, ments, qents)
339    
340           ! Unsaturated (precipitating) downdrafts
341           CALL cv30_unsat(klon, ncum, klev, klev, icb(:ncum), inb(:ncum), t, q, &
342                qs, gz, u, v, p, ph, th, tv, lv, cpn, ep, sigp, clw, m, ment, &
343                elij, delt, plcl, mp, qp, up, vp, wt, water, evap, b)! na->klev
344    
345           ! Yield (tendencies, precipitation, variables of interface with
346           ! other processes, etc)
347           CALL cv30_yield(klon, ncum, klev, klev, icb, inb, delt, t, q, u, v, &
348                gz, p, ph, h, hp, lv, cpn, th, ep, clw, m, tp, mp, qp, up, vp, &
349                wt, water, evap, b, ment, qent, uent, vent, nent, elij, sig, &
350                tv, tvp, iflag, precip, VPrecip, ft, fq, fu, fv, upwd, dnwd, &
351                dnwd0, ma, mike, tls, tps, qcondc, wd)! na->klev
352    
353         if (iflag_con == 3) then         ! passive tracers
354            CALL cv3_compress(klon, klon, ncum, klev, iflag1, nk1, icb1, icbs1, &         CALL cv30_tracer(klon, ncum, klev, ment, sij, da, phi)
                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, 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, &  
                qs, gz, p, dph, h, tv, lv, inb, inbis, tp, tvp, clw, hp, ep, &  
                sigp, frac)  
        endif  
   
        ! --- CLOSURE  
   
        if (iflag_con == 3) then  
           CALL cv3_closure(klon, ncum, klev, icb, inb, pbase, p, ph, tv, &  
                buoy, sig, w0, cape, m) ! na->klev  
        else  
           ! iflag_con == 4  
           CALL cv_closure(klon, ncum, klev, nk, icb, tv, tvp, p, ph, dph, &  
                plcl, cpn, iflag, cbmf)  
        endif  
   
        ! --- MIXING  
355    
356         if (iflag_con == 3) then         ! UNCOMPRESS THE FIELDS
           CALL cv3_mixing(klon, ncum, klev, klev, icb, nk, inb, t, q, qs, u, &  
                v, h, lv, hp, ep, clw, m, sig, ment, qent, uent, vent, nent, &  
                sij, elij, ments, qents)  
        else  
           ! iflag_con == 4  
           CALL cv_mixing(klon, ncum, klev, icb, nk, inb, inbis, ph, t, q, qs, &  
                u, v, h, lv, qnk, hp, tv, tvp, ep, clw, cbmf, m, ment, qent, &  
                uent, vent, nent, sij, elij)  
        endif  
   
        ! --- UNSATURATED (PRECIPITATING) DOWNDRAFTS  
   
        if (iflag_con == 3) then  
           CALL cv3_unsat(klon, ncum, klev, klev, icb, inb, t, q, qs, gz, u, &  
                v, p, ph, th, tv, lv, cpn, ep, sigp, clw, m, ment, elij, delt, &  
                plcl, mp, qp, up, vp, wt, water, evap, b)! na->klev  
        else  
           ! iflag_con == 4  
           CALL cv_unsat(klon, ncum, klev, inb, t, q, qs, gz, u, v, p, ph, h, &  
                lv, ep, sigp, clw, m, ment, elij, iflag, mp, qp, up, vp, wt, &  
                water, evap)  
        endif  
   
        ! --- 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  
   
        if (iflag_con == 3) CALL cv3_tracer(klon, ncum, klev, ment, sij, da, phi)  
   
        ! --- UNCOMPRESS THE FIELDS  
357    
358         ! set iflag1 = 42 for non convective points         ! set iflag1 = 42 for non convective points
359         do i = 1, klon         iflag1 = 42
           iflag1(i) = 42  
        end do  
360    
361         if (iflag_con == 3) then         CALL cv30_uncompress(idcum(:ncum), iflag, precip, VPrecip, sig, w0, &
362            CALL cv3_uncompress(idcum(:ncum), iflag, precip, VPrecip, sig, w0, &              ft, fq, fu, fv, inb, Ma, upwd, dnwd, dnwd0, qcondc, wd, cape, &
363                 ft, fq, fu, fv, inb, Ma, upwd, dnwd, dnwd0, qcondc, wd, cape, &              da, phi, mp, iflag1, precip1, VPrecip1, sig1, w01, ft1, fq1, &
364                 da, phi, mp, iflag1, precip1, VPrecip1, sig1, w01, ft1, fq1, &              fu1, fv1, inb1, Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, &
365                 fu1, fv1, inb1, Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, &              cape1, da1, phi1, mp1)
366                 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  
367    
368    end SUBROUTINE cv_driver    end SUBROUTINE cv_driver
369    

Legend:
Removed from v.150  
changed lines
  Added in v.186

  ViewVC Help
Powered by ViewVC 1.1.21