/[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 182 by guez, Wed Mar 16 11:11:27 2016 UTC
# Line 14  contains Line 14  contains
14    
15      ! Several modules corresponding to different physical processes      ! Several modules corresponding to different physical processes
16    
     ! Several versions of convect may be used:  
     ! - iflag_con = 3: version lmd  
     ! - iflag_con = 4: version 4.3b  
   
     use clesphys2, only: iflag_con  
17      use cv3_compress_m, only: cv3_compress      use cv3_compress_m, only: cv3_compress
18      use cv3_feed_m, only: cv3_feed      use cv3_feed_m, only: cv3_feed
19      use cv3_mixing_m, only: cv3_mixing      use cv3_mixing_m, only: cv3_mixing
# Line 28  contains Line 23  contains
23      use cv3_uncompress_m, only: cv3_uncompress      use cv3_uncompress_m, only: cv3_uncompress
24      use cv3_unsat_m, only: cv3_unsat      use cv3_unsat_m, only: cv3_unsat
25      use cv3_yield_m, only: cv3_yield      use cv3_yield_m, only: cv3_yield
     use cv_feed_m, only: cv_feed  
     use cv_uncompress_m, only: cv_uncompress  
26      USE dimphy, ONLY: klev, klon      USE dimphy, ONLY: klev, klon
27    
28      real, intent(in):: t1(klon, klev) ! temperature      real, intent(in):: t1(klon, klev) ! temperature
# Line 46  contains Line 39  contains
39      real, intent(out):: fv1(klon, klev) ! v-wind tend      real, intent(out):: fv1(klon, klev) ! v-wind tend
40      real, intent(out):: precip1(klon) ! precipitation      real, intent(out):: precip1(klon) ! precipitation
41    
42      real, intent(out):: VPrecip1(klon, klev+1)      real, intent(out):: VPrecip1(klon, klev + 1)
43      ! vertical profile of precipitation      ! vertical profile of precipitation
44    
45      real, intent(inout):: cbmf1(klon) ! cloud base mass flux      real, intent(inout):: cbmf1(klon) ! cloud base mass flux
# 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 207  contains Line 203  contains
203      integer icbs(klon)      integer icbs(klon)
204      integer inb(klon), inbis(klon)      integer inb(klon), inbis(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)
212      real dph(klon, klev)      real dph(klon, klev)
213      real pbase(klon), buoybase(klon), th(klon, klev)      real pbase(klon), buoybase(klon), th(klon, klev)
# Line 232  contains Line 228  contains
228      real Ma(klon, klev), mike(klon, klev), tls(klon, klev)      real Ma(klon, klev), mike(klon, klev), tls(klon, klev)
229      real tps(klon, klev), qprime(klon), tprime(klon)      real tps(klon, klev), qprime(klon), tprime(klon)
230      real precip(klon)      real precip(klon)
231      real VPrecip(klon, klev+1)      real VPrecip(klon, klev + 1)
232      real qcondc(klon, klev) ! cld      real qcondc(klon, klev) ! cld
233      real wd(klon) ! gust      real wd(klon) ! gust
234    
235      !-------------------------------------------------------------------      !-------------------------------------------------------------------
     ! --- SET CONSTANTS AND PARAMETERS  
236    
237      ! -- set simulation flags:      ! SET CONSTANTS AND PARAMETERS
238    
239        ! set simulation flags:
240      ! (common cvflag)      ! (common cvflag)
241    
242      CALL cv_flag      CALL cv_flag
243    
244      ! -- set thermodynamical constants:      ! set thermodynamical constants:
245      ! (common cvthermo)      ! (common cvthermo)
246    
247      CALL cv_thermo      CALL cv_thermo
248    
249      ! -- set convect parameters      ! set convect parameters
250    
251      ! includes microphysical parameters and parameters that      ! includes microphysical parameters and parameters that
252      ! control the rate of approach to quasi-equilibrium)      ! control the rate of approach to quasi-equilibrium)
253      ! (common cvparam)      ! (common cvparam)
254    
255      if (iflag_con == 3) CALL cv3_param(klev, delt)      CALL cv3_param(klev, delt)
256    
257      ! --- INITIALIZE OUTPUT ARRAYS AND PARAMETERS      ! INITIALIZE OUTPUT ARRAYS AND PARAMETERS
258    
259      do k = 1, klev      do k = 1, klev
260         do i = 1, klon         do i = 1, klon
# Line 285  contains Line 282  contains
282         iflag1(i) = 0         iflag1(i) = 0
283         wd1(i) = 0.0         wd1(i) = 0.0
284         cape1(i) = 0.0         cape1(i) = 0.0
285         VPrecip1(i, klev+1) = 0.0         VPrecip1(i, klev + 1) = 0.0
286      end do      end do
287    
288      if (iflag_con == 3) then      do il = 1, klon
289         do il = 1, klon         sig1(il, klev) = sig1(il, klev) + 1.
290            sig1(il, klev) = sig1(il, klev) + 1.         sig1(il, klev) = min(sig1(il, klev), 12.1)
291            sig1(il, klev) = min(sig1(il, klev), 12.1)      enddo
292         enddo  
293      endif      ! CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY
294    
295      ! --- CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY      CALL cv3_prelim(klon, klev, klev + 1, t1, q1, p1, ph1, lv1, cpn1, tv1, &
296             gz1, h1, hm1, th1)
     if (iflag_con == 3) then  
        CALL cv3_prelim(klon, klev, klev + 1, t1, q1, p1, ph1, lv1, cpn1, tv1, &  
             gz1, h1, hm1, th1)  
     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  
297    
298      ! --- UNDILUTE (ADIABATIC) UPDRAFT / 1st part      ! CONVECTIVE FEED
299      ! (up through ICB for convect4, up through ICB+1 for convect3)  
300        CALL cv3_feed(klon, klev, t1, q1, qs1, p1, ph1, gz1, nk1, icb1, &
301             icbmax, iflag1, tnk1, qnk1, gznk1, plcl1) ! klev->na
302    
303        ! UNDILUTE (ADIABATIC) UPDRAFT / 1st part
304        ! (up through ICB for convect4, up through ICB + 1 for convect3)
305      ! Calculates the lifted parcel virtual temperature at nk, the      ! Calculates the lifted parcel virtual temperature at nk, the
306      ! actual temperature, and the adiabatic liquid water content.      ! actual temperature, and the adiabatic liquid water content.
307    
308      if (iflag_con == 3) then      CALL cv3_undilute1(klon, klev, t1, q1, qs1, gz1, plcl1, p1, nk1, icb1, &
309         CALL cv3_undilute1(klon, klev, t1, q1, qs1, gz1, plcl1, p1, nk1, icb1, &           tp1, tvp1, clw1, icbs1) ! klev->na
310              tp1, tvp1, clw1, icbs1) ! klev->na  
311      else      ! TRIGGERING
        ! 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  
312    
313      ! --- IF THIS POINT IS REACHED, MOIST CONVECTIVE ADJUSTMENT IS NECESSARY      CALL cv3_trigger(klon, klev, icb1, plcl1, p1, th1, tv1, tvp1, pbase1, &
314             buoybase1, iflag1, sig1, w01) ! klev->na
315    
316        ! Moist convective adjustment is necessary
317    
318      ncum = 0      ncum = 0
319      do i = 1, klon      do i = 1, klon
320         if(iflag1(i) == 0)then         if (iflag1(i) == 0) then
321            ncum = ncum+1            ncum = ncum + 1
322            idcum(ncum) = i            idcum(ncum) = i
323         endif         endif
324      end do      end do
325    
326      IF (ncum > 0) THEN      IF (ncum > 0) THEN
327         ! --- COMPRESS THE FIELDS         ! COMPRESS THE FIELDS
328         ! (-> vectorization over convective gridpoints)         ! (-> vectorization over convective gridpoints)
329    
330         if (iflag_con == 3) then         CALL cv3_compress(klon, klon, ncum, klev, iflag1, nk1, icb1, icbs1, &
331            CALL cv3_compress(klon, klon, ncum, klev, iflag1, nk1, icb1, icbs1, &              plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1, t1, q1, qs1, u1, &
332                 plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1, t1, q1, qs1, u1, &              v1, gz1, th1, h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, &
333                 v1, gz1, th1, h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, &              sig1, w01, iflag, nk, icb, icbs, plcl, tnk, qnk, gznk, pbase, &
334                 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, &
335                 buoybase, t, q, qs, u, v, gz, th, h, lv, cpn, p, ph, tv, tp, &              tvp, clw, sig, w0)
336                 tvp, clw, sig, w0)  
337         else         ! UNDILUTE (ADIABATIC) UPDRAFT / second part :
338            ! iflag_con == 4         ! FIND THE REST OF THE LIFTED PARCEL TEMPERATURES
339            CALL cv_compress(klon, klon, ncum, klev, iflag1, nk1, icb1, cbmf1, &         ! &
340                 plcl1, tnk1, qnk1, gznk1, t1, q1, qs1, u1, v1, gz1, h1, lv1, &         ! COMPUTE THE PRECIPITATION EFFICIENCIES AND THE
341                 cpn1, p1, ph1, tv1, tp1, tvp1, clw1, iflag, nk, icb, cbmf, &         ! FRACTION OF PRECIPITATION FALLING OUTSIDE OF CLOUD
342                 plcl, tnk, qnk, gznk, t, q, qs, u, v, gz, h, lv, cpn, p, ph, &         ! &
343                 tv, tp, tvp, clw, dph)         ! FIND THE LEVEL OF NEUTRAL BUOYANCY
344         endif  
345           CALL cv3_undilute2(klon, ncum, klev, icb, icbs, nk, tnk, qnk, gznk, &
346         ! --- UNDILUTE (ADIABATIC) UPDRAFT / second part :              t, qs, gz, p, h, tv, lv, pbase, buoybase, plcl, inb, tp, &
347         ! --- FIND THE REST OF THE LIFTED PARCEL TEMPERATURES              tvp, clw, hp, ep, sigp, buoy) !na->klev
348         ! --- &  
349         ! --- COMPUTE THE PRECIPITATION EFFICIENCIES AND THE         ! CLOSURE
350         ! --- FRACTION OF PRECIPITATION FALLING OUTSIDE OF CLOUD  
351         ! --- &         CALL cv3_closure(klon, ncum, klev, icb, inb, pbase, p, ph, tv, &
352         ! --- FIND THE LEVEL OF NEUTRAL BUOYANCY              buoy, sig, w0, cape, m) ! na->klev
353    
354         if (iflag_con == 3) then         ! MIXING
355            CALL cv3_undilute2(klon, ncum, klev, icb, icbs, nk, tnk, qnk, gznk, &  
356                 t, qs, gz, p, h, tv, lv, pbase, buoybase, plcl, inb, tp, &         CALL cv3_mixing(klon, ncum, klev, klev, icb, nk, inb, t, q, qs, u, &
357                 tvp, clw, hp, ep, sigp, buoy) !na->klev              v, h, lv, hp, ep, clw, m, sig, ment, qent, uent, vent, nent, &
358         else              sij, elij, ments, qents)
359            ! iflag_con == 4  
360            CALL cv_undilute2(klon, ncum, klev, icb, nk, tnk, qnk, gznk, t, &         ! UNSATURATED (PRECIPITATING) DOWNDRAFTS
361                 qs, gz, p, dph, h, tv, lv, inb, inbis, tp, tvp, clw, hp, ep, &  
362                 sigp, frac)         CALL cv3_unsat(klon, ncum, klev, klev, icb, inb, t, q, qs, gz, u, &
363         endif              v, p, ph, th, tv, lv, cpn, ep, sigp, clw, m, ment, elij, delt, &
364                plcl, mp, qp, up, vp, wt, water, evap, b)! na->klev
        ! --- 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  
   
        if (iflag_con == 3) then  
           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  
365    
366         ! --- YIELD         ! YIELD
367         ! (tendencies, precipitation, variables of interface with other         ! (tendencies, precipitation, variables of interface with other
368         ! processes, etc)         ! processes, etc)
369    
370         if (iflag_con == 3) then         CALL cv3_yield(klon, ncum, klev, klev, icb, inb, delt, t, q, u, v, &
371            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, &
372                 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, &
373                 wt, water, evap, b, ment, qent, uent, vent, nent, elij, sig, &              tv, tvp, iflag, precip, VPrecip, ft, fq, fu, fv, upwd, dnwd, &
374                 tv, tvp, iflag, precip, VPrecip, ft, fq, fu, fv, upwd, dnwd, &              dnwd0, ma, mike, tls, tps, qcondc, wd)! na->klev
                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  
375    
376         ! --- passive tracers         ! passive tracers
377    
378         if (iflag_con == 3) CALL cv3_tracer(klon, ncum, klev, ment, sij, da, phi)         CALL cv3_tracer(klon, ncum, klev, ment, sij, da, phi)
379    
380         ! --- UNCOMPRESS THE FIELDS         ! UNCOMPRESS THE FIELDS
381    
382         ! set iflag1 = 42 for non convective points         ! set iflag1 = 42 for non convective points
383         do i = 1, klon         do i = 1, klon
384            iflag1(i) = 42            iflag1(i) = 42
385         end do         end do
386    
387         if (iflag_con == 3) then         CALL cv3_uncompress(idcum(:ncum), iflag, precip, VPrecip, sig, w0, &
388            CALL cv3_uncompress(idcum(:ncum), iflag, precip, VPrecip, sig, w0, &              ft, fq, fu, fv, inb, Ma, upwd, dnwd, dnwd0, qcondc, wd, cape, &
389                 ft, fq, fu, fv, inb, Ma, upwd, dnwd, dnwd0, qcondc, wd, cape, &              da, phi, mp, iflag1, precip1, VPrecip1, sig1, w01, ft1, fq1, &
390                 da, phi, mp, iflag1, precip1, VPrecip1, sig1, w01, ft1, fq1, &              fu1, fv1, inb1, Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, &
391                 fu1, fv1, inb1, Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, &              cape1, da1, phi1, mp1)
                cape1, da1, phi1, mp1)  
        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  
392      ENDIF ! ncum>0      ENDIF ! ncum>0
393    
394    end SUBROUTINE cv_driver    end SUBROUTINE cv_driver

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

  ViewVC Help
Powered by ViewVC 1.1.21