/[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 183 by guez, Wed Mar 16 14:42:58 2016 UTC revision 187 by guez, Mon Mar 21 18:01:02 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    
17      use cv3_compress_m, only: cv3_compress      use cv30_closure_m, only: cv30_closure
18      use cv3_feed_m, only: cv3_feed      use cv30_compress_m, only: cv30_compress
19      use cv3_mixing_m, only: cv3_mixing      use cv30_feed_m, only: cv30_feed
20      use cv3_param_m, only: cv3_param      use cv30_mixing_m, only: cv30_mixing
21      use cv3_prelim_m, only: cv3_prelim      use cv30_param_m, only: cv30_param
22      use cv3_tracer_m, only: cv3_tracer      use cv30_prelim_m, only: cv30_prelim
23      use cv3_uncompress_m, only: cv3_uncompress      use cv30_tracer_m, only: cv30_tracer
24      use cv3_undilute2_m, only: cv3_undilute2      use cv30_uncompress_m, only: cv30_uncompress
25      use cv3_unsat_m, only: cv3_unsat      use cv30_undilute2_m, only: cv30_undilute2
26      use cv3_yield_m, only: cv3_yield      use cv30_unsat_m, only: cv30_unsat
27        use cv30_yield_m, only: cv30_yield
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
33      real, intent(in):: u1(klon, klev) ! u-wind  
34      real, intent(in):: v1(klon, klev) ! v-wind      real, intent(in):: q1(klon, klev)
35      real, intent(in):: p1(klon, klev) ! full level pressure      ! Specific humidity, with first index corresponding to lowest
36      real, intent(in):: ph1(klon, klev + 1) ! half level pressure      ! model level. Must be defined at same grid levels as T1.
37      integer, intent(out):: iflag1(klon) ! flag for Emanuel conditions  
38      real, intent(out):: ft1(klon, klev) ! temp tend      real, intent(in):: qs1(klon, klev)
39      real, intent(out):: fq1(klon, klev) ! spec hum tend      ! Saturation specific humidity, with first index corresponding to
40      real, intent(out):: fu1(klon, klev) ! u-wind tend      ! lowest model level. Must be defined at same grid levels as
41      real, intent(out):: fv1(klon, klev) ! v-wind tend      ! T1.
42      real, intent(out):: precip1(klon) ! precipitation  
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)      real, intent(out):: VPrecip1(klon, klev + 1)
100      ! vertical profile of precipitation      ! vertical profile of convective precipitation (kg/m2/s)
101    
102      real, intent(inout):: sig1(klon, klev) ! section adiabatic updraft      real, intent(inout):: sig1(klon, klev) ! section adiabatic updraft
103    
# Line 50  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
110      real Ma1(klon, klev)  
111      ! Ma1 Real Output mass flux adiabatic updraft      real Ma1(klon, klev) ! Output mass flux adiabatic updraft
112    
113      real, intent(out):: upwd1(klon, klev)      real, intent(out):: upwd1(klon, klev)
114      ! total upward mass flux (adiab + mixed)      ! total upward mass flux (adiab + mixed)
# Line 60  contains Line 116  contains
116      real, intent(out):: dnwd1(klon, klev) ! saturated downward mass flux (mixed)      real, intent(out):: dnwd1(klon, klev) ! saturated downward mass flux (mixed)
117      real, intent(out):: dnwd01(klon, klev) ! unsaturated downward mass flux      real, intent(out):: dnwd01(klon, klev) ! unsaturated downward mass flux
118    
119      real qcondc1(klon, klev) ! cld      real qcondc1(klon, klev) ! Output in-cld mixing ratio of condensed water
120      ! qcondc1 Real Output in-cld mixing ratio of condensed water  
121      real wd1(klon) ! gust      real wd1(klon) ! gust
122      ! wd1 Real Output downdraft velocity scale for sfc fluxes      ! Output downdraft velocity scale for surface fluxes
123      real cape1(klon)      ! A convective downdraft velocity scale. For use in surface
124      ! cape1 Real Output CAPE      ! flux parameterizations. See convect.ps file for details.
125    
126        real cape1(klon) ! Output
127      real, intent(inout):: da1(klon, klev), phi1(klon, klev, klev)      real, intent(inout):: da1(klon, klev), phi1(klon, klev, klev)
128      real, intent(inout):: mp1(klon, klev)      real, intent(inout):: mp1(klon, klev)
129    
130      ! ARGUMENTS      ! Local:
   
     ! On input:  
   
     ! t: Array of absolute temperature (K) of dimension KLEV, 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 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).  
   
     ! 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 KLEV.  
   
     ! Local arrays  
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 195  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)
# Line 235  contains Line 196  contains
196    
197      ! SET CONSTANTS AND PARAMETERS      ! SET CONSTANTS AND PARAMETERS
198    
     ! set simulation flags:  
     ! (common cvflag)  
     CALL cv_flag  
   
199      ! set thermodynamical constants:      ! set thermodynamical constants:
200      ! (common cvthermo)      ! (common cvthermo)
201      CALL cv_thermo      CALL cv_thermo
# Line 247  contains Line 204  contains
204      ! includes microphysical parameters and parameters that      ! includes microphysical parameters and parameters that
205      ! control the rate of approach to quasi-equilibrium)      ! control the rate of approach to quasi-equilibrium)
206      ! (common cvparam)      ! (common cvparam)
207        CALL cv30_param(delt)
     CALL cv3_param(klev, delt)  
208    
209      ! INITIALIZE OUTPUT ARRAYS AND PARAMETERS      ! INITIALIZE OUTPUT ARRAYS AND PARAMETERS
210    
211      do k = 1, klev      do k = 1, klev
212         do i = 1, klon         do i = 1, klon
213            ft1(i, k) = 0.0            ft1(i, k) = 0.
214            fq1(i, k) = 0.0            fq1(i, k) = 0.
215            fu1(i, k) = 0.0            fu1(i, k) = 0.
216            fv1(i, k) = 0.0            fv1(i, k) = 0.
217            tvp1(i, k) = 0.0            tvp1(i, k) = 0.
218            tp1(i, k) = 0.0            tp1(i, k) = 0.
219            clw1(i, k) = 0.0            clw1(i, k) = 0.
220            clw(i, k) = 0.0            clw(i, k) = 0.
221            gz1(i, k) = 0.            gz1(i, k) = 0.
222            VPrecip1(i, k) = 0.            VPrecip1(i, k) = 0.
223            Ma1(i, k) = 0.0            Ma1(i, k) = 0.
224            upwd1(i, k) = 0.0            upwd1(i, k) = 0.
225            dnwd1(i, k) = 0.0            dnwd1(i, k) = 0.
226            dnwd01(i, k) = 0.0            dnwd01(i, k) = 0.
227            qcondc1(i, k) = 0.0            qcondc1(i, k) = 0.
228         end do         end do
229      end do      end do
230    
231      do i = 1, klon      do i = 1, klon
232         precip1(i) = 0.0         precip1(i) = 0.
233         iflag1(i) = 0         iflag1(i) = 0
234         wd1(i) = 0.0         wd1(i) = 0.
235         cape1(i) = 0.0         cape1(i) = 0.
236         VPrecip1(i, klev + 1) = 0.0         VPrecip1(i, klev + 1) = 0.
237      end do      end do
238    
239      do il = 1, klon      do il = 1, klon
# Line 286  contains Line 242  contains
242      enddo      enddo
243    
244      ! CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY      ! CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY
245      CALL cv3_prelim(klon, klev, klev + 1, t1, q1, p1, ph1, lv1, cpn1, tv1, &      CALL cv30_prelim(klon, klev, klev + 1, t1, q1, p1, ph1, lv1, cpn1, tv1, &
246           gz1, h1, hm1, th1)           gz1, h1, hm1, th1)
247    
248      ! CONVECTIVE FEED      ! CONVECTIVE FEED
249      CALL cv3_feed(klon, klev, t1, q1, qs1, p1, ph1, gz1, nk1, icb1, &      CALL cv30_feed(klon, klev, t1, q1, qs1, p1, ph1, gz1, nk1, icb1, &
250           icbmax, iflag1, tnk1, qnk1, gznk1, plcl1) ! klev->na           icbmax, iflag1, tnk1, qnk1, gznk1, plcl1) ! klev->na
251    
252      ! UNDILUTE (ADIABATIC) UPDRAFT / 1st part      ! UNDILUTE (ADIABATIC) UPDRAFT / 1st part
253      ! (up through ICB for convect4, up through ICB + 1 for convect3)      ! (up through ICB for convect4, up through ICB + 1 for convect3)
254      ! Calculates the lifted parcel virtual temperature at nk, the      ! Calculates the lifted parcel virtual temperature at nk, the
255      ! actual temperature, and the adiabatic liquid water content.      ! actual temperature, and the adiabatic liquid water content.
256      CALL cv3_undilute1(klon, klev, t1, q1, qs1, gz1, plcl1, p1, nk1, icb1, &      CALL cv30_undilute1(klon, klev, t1, q1, qs1, gz1, plcl1, p1, nk1, icb1, &
257           tp1, tvp1, clw1, icbs1) ! klev->na           tp1, tvp1, clw1, icbs1) ! klev->na
258    
259      ! TRIGGERING      ! TRIGGERING
260      CALL cv3_trigger(klon, klev, icb1, plcl1, p1, th1, tv1, tvp1, pbase1, &      CALL cv30_trigger(klon, klev, icb1, plcl1, p1, th1, tv1, tvp1, pbase1, &
261           buoybase1, iflag1, sig1, w01) ! klev->na           buoybase1, iflag1, sig1, w01) ! klev->na
262    
263      ! Moist convective adjustment is necessary      ! Moist convective adjustment is necessary
# Line 317  contains Line 273  contains
273      IF (ncum > 0) THEN      IF (ncum > 0) THEN
274         ! COMPRESS THE FIELDS         ! COMPRESS THE FIELDS
275         ! (-> vectorization over convective gridpoints)         ! (-> vectorization over convective gridpoints)
276         CALL cv3_compress(klon, klon, ncum, klev, iflag1, nk1, icb1, icbs1, &         CALL cv30_compress(klon, klon, ncum, klev, iflag1, nk1, icb1, icbs1, &
277              plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1, t1, q1, qs1, u1, &              plcl1, tnk1, qnk1, gznk1, pbase1, buoybase1, t1, q1, qs1, u1, &
278              v1, gz1, th1, h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, &              v1, gz1, th1, h1, lv1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, &
279              sig1, w01, iflag, nk, icb, icbs, plcl, tnk, qnk, gznk, pbase, &              sig1, w01, iflag, nk, icb, icbs, plcl, tnk, qnk, gznk, pbase, &
280              buoybase, t, q, qs, u, v, gz, th, h, lv, cpn, p, ph, tv, tp, &              buoybase, t, q, qs, u, v, gz, th, h, lv, cpn, p, ph, tv, tp, &
281              tvp, clw, sig, w0)              tvp, clw, sig, w0)
282    
283         ! UNDILUTE (ADIABATIC) UPDRAFT / second part :         CALL cv30_undilute2(ncum, icb, icbs, nk, tnk, qnk, gznk, t, qs, gz, p, &
284         ! FIND THE REST OF THE LIFTED PARCEL TEMPERATURES              h, tv, lv, pbase, buoybase, plcl, inb(:ncum), tp, tvp, clw, hp, &
285         ! &              ep, sigp, buoy)
        ! COMPUTE THE PRECIPITATION EFFICIENCIES AND THE  
        ! FRACTION OF PRECIPITATION FALLING OUTSIDE OF CLOUD  
        ! &  
        ! FIND THE LEVEL OF NEUTRAL BUOYANCY  
        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  
286    
287         ! CLOSURE         ! CLOSURE
288         CALL cv3_closure(klon, ncum, klev, icb, inb, pbase, p, ph, tv, &         CALL cv30_closure(klon, ncum, klev, icb, inb, pbase, p, ph, tv, &
289              buoy, sig, w0, cape, m) ! na->klev              buoy, sig, w0, cape, m) ! na->klev
290    
291         ! MIXING         ! MIXING
292         CALL cv3_mixing(klon, ncum, klev, klev, icb, nk, inb, t, q, qs, u, &         CALL cv30_mixing(klon, ncum, klev, klev, icb, nk, inb, t, q, qs, u, &
293              v, h, lv, hp, ep, clw, m, sig, ment, qent, uent, vent, nent, &              v, h, lv, hp, ep, clw, m, sig, ment, qent, uent, vent, nent, &
294              sij, elij, ments, qents)              sij, elij, ments, qents)
295    
296         ! UNSATURATED (PRECIPITATING) DOWNDRAFTS         ! Unsaturated (precipitating) downdrafts
297         CALL cv3_unsat(klon, ncum, klev, klev, icb, inb, t, q, qs, gz, u, &         CALL cv30_unsat(ncum, icb(:ncum), inb(:ncum), t, q, qs, gz, u, v, p, &
298              v, p, ph, th, tv, lv, cpn, ep, sigp, clw, m, ment, elij, delt, &              ph, th, tv, lv, cpn, ep, sigp, clw, m, ment, elij, delt, plcl, &
299              plcl, mp, qp, up, vp, wt, water, evap, b)! na->klev              mp, qp, up, vp, wt, water, evap, b(:ncum, :))
300    
301         ! YIELD         ! Yield (tendencies, precipitation, variables of interface with
302         ! (tendencies, precipitation, variables of interface with other         ! other processes, etc)
303         ! processes, etc)         CALL cv30_yield(klon, ncum, klev, klev, icb, inb, delt, t, q, u, v, &
        CALL cv3_yield(klon, ncum, klev, klev, icb, inb, delt, t, q, u, v, &  
304              gz, p, ph, h, hp, lv, cpn, th, ep, clw, m, tp, mp, qp, up, vp, &              gz, p, ph, h, hp, lv, cpn, th, ep, clw, m, tp, mp, qp, up, vp, &
305              wt, water, evap, b, ment, qent, uent, vent, nent, elij, sig, &              wt, water, evap, b, ment, qent, uent, vent, nent, elij, sig, &
306              tv, tvp, iflag, precip, VPrecip, ft, fq, fu, fv, upwd, dnwd, &              tv, tvp, iflag, precip, VPrecip, ft, fq, fu, fv, upwd, dnwd, &
307              dnwd0, ma, mike, tls, tps, qcondc, wd)! na->klev              dnwd0, ma, mike, tls, tps, qcondc, wd)! na->klev
308    
309         ! passive tracers         ! passive tracers
310         CALL cv3_tracer(klon, ncum, klev, ment, sij, da, phi)         CALL cv30_tracer(klon, ncum, klev, ment, sij, da, phi)
311    
312         ! UNCOMPRESS THE FIELDS         ! UNCOMPRESS THE FIELDS
313    
314         ! set iflag1 = 42 for non convective points         ! set iflag1 = 42 for non convective points
315         do i = 1, klon         iflag1 = 42
           iflag1(i) = 42  
        end do  
316    
317         CALL cv3_uncompress(idcum(:ncum), iflag, precip, VPrecip, sig, w0, &         CALL cv30_uncompress(idcum(:ncum), iflag, precip, VPrecip, sig, w0, &
318              ft, fq, fu, fv, inb, Ma, upwd, dnwd, dnwd0, qcondc, wd, cape, &              ft, fq, fu, fv, inb, Ma, upwd, dnwd, dnwd0, qcondc, wd, cape, &
319              da, phi, mp, iflag1, precip1, VPrecip1, sig1, w01, ft1, fq1, &              da, phi, mp, iflag1, precip1, VPrecip1, sig1, w01, ft1, fq1, &
320              fu1, fv1, inb1, Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, &              fu1, fv1, inb1, Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, &

Legend:
Removed from v.183  
changed lines
  Added in v.187

  ViewVC Help
Powered by ViewVC 1.1.21