/[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 180 by guez, Tue Mar 15 17:07:47 2016 UTC
# Line 46  contains Line 46  contains
46      real, intent(out):: fv1(klon, klev) ! v-wind tend      real, intent(out):: fv1(klon, klev) ! v-wind tend
47      real, intent(out):: precip1(klon) ! precipitation      real, intent(out):: precip1(klon) ! precipitation
48    
49      real, intent(out):: VPrecip1(klon, klev+1)      real, intent(out):: VPrecip1(klon, klev + 1)
50      ! vertical profile of precipitation      ! vertical profile of precipitation
51    
52      real, intent(inout):: cbmf1(klon) ! cloud base mass flux      real, intent(inout):: cbmf1(klon) ! cloud base mass flux
# Line 60  contains Line 60  contains
60      real, intent(in):: delt ! time step      real, intent(in):: delt ! time step
61      real Ma1(klon, klev)      real Ma1(klon, klev)
62      ! Ma1 Real Output mass flux adiabatic updraft      ! Ma1 Real Output mass flux adiabatic updraft
63      real, intent(out):: upwd1(klon, klev) ! total upward mass flux (adiab+mixed)  
64        real, intent(out):: upwd1(klon, klev)
65        ! total upward mass flux (adiab + mixed)
66    
67      real, intent(out):: dnwd1(klon, klev) ! saturated downward mass flux (mixed)      real, intent(out):: dnwd1(klon, klev) ! saturated downward mass flux (mixed)
68      real, intent(out):: dnwd01(klon, klev) ! unsaturated downward mass flux      real, intent(out):: dnwd01(klon, klev) ! unsaturated downward mass flux
69    
# Line 74  contains Line 77  contains
77      real, intent(inout):: da1(klon, klev), phi1(klon, klev, klev)      real, intent(inout):: da1(klon, klev), phi1(klon, klev, klev)
78      real, intent(inout):: mp1(klon, klev)      real, intent(inout):: mp1(klon, klev)
79    
80      ! --- ARGUMENTS      ! ARGUMENTS
81    
82      ! --- On input:      ! On input:
83    
84      ! t: Array of absolute temperature (K) of dimension KLEV, with first      ! t: Array of absolute temperature (K) of dimension KLEV, with first
85      ! index corresponding to lowest model level. Note that this array      ! index corresponding to lowest model level. Note that this array
# Line 104  contains Line 107  contains
107      ! index corresponding to lowest model level. Must be defined      ! index corresponding to lowest model level. Must be defined
108      ! at same grid levels as T.      ! at same grid levels as T.
109    
110      ! ph: Array of pressure (mb) of dimension KLEV+1, with first index      ! ph: Array of pressure (mb) of dimension KLEV + 1, with first index
111      ! corresponding to lowest level. These pressures are defined at      ! corresponding to lowest level. These pressures are defined at
112      ! levels intermediate between those of P, T, Q and QS. The first      ! levels intermediate between those of P, T, Q and QS. The first
113      ! 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 118  contains
118    
119      ! delt: The model time step (sec) between calls to CONVECT      ! delt: The model time step (sec) between calls to CONVECT
120    
121      ! --- On Output:      ! On Output:
122    
123      ! iflag: An output integer whose value denotes the following:      ! iflag: An output integer whose value denotes the following:
124      ! VALUE INTERPRETATION      ! VALUE INTERPRETATION
# Line 211  contains Line 214  contains
214      real t(klon, klev), q(klon, klev), qs(klon, klev)      real t(klon, klev), q(klon, klev), qs(klon, klev)
215      real u(klon, klev), v(klon, klev)      real u(klon, klev), v(klon, klev)
216      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)
217      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)
218      real clw(klon, klev)      real clw(klon, klev)
219      real dph(klon, klev)      real dph(klon, klev)
220      real pbase(klon), buoybase(klon), th(klon, klev)      real pbase(klon), buoybase(klon), th(klon, klev)
# Line 232  contains Line 235  contains
235      real Ma(klon, klev), mike(klon, klev), tls(klon, klev)      real Ma(klon, klev), mike(klon, klev), tls(klon, klev)
236      real tps(klon, klev), qprime(klon), tprime(klon)      real tps(klon, klev), qprime(klon), tprime(klon)
237      real precip(klon)      real precip(klon)
238      real VPrecip(klon, klev+1)      real VPrecip(klon, klev + 1)
239      real qcondc(klon, klev) ! cld      real qcondc(klon, klev) ! cld
240      real wd(klon) ! gust      real wd(klon) ! gust
241    
242      !-------------------------------------------------------------------      !-------------------------------------------------------------------
     ! --- SET CONSTANTS AND PARAMETERS  
243    
244      ! -- set simulation flags:      ! SET CONSTANTS AND PARAMETERS
245    
246        ! set simulation flags:
247      ! (common cvflag)      ! (common cvflag)
248    
249      CALL cv_flag      CALL cv_flag
250    
251      ! -- set thermodynamical constants:      ! set thermodynamical constants:
252      ! (common cvthermo)      ! (common cvthermo)
253    
254      CALL cv_thermo      CALL cv_thermo
255    
256      ! -- set convect parameters      ! set convect parameters
257    
258      ! includes microphysical parameters and parameters that      ! includes microphysical parameters and parameters that
259      ! control the rate of approach to quasi-equilibrium)      ! control the rate of approach to quasi-equilibrium)
# Line 257  contains Line 261  contains
261    
262      if (iflag_con == 3) CALL cv3_param(klev, delt)      if (iflag_con == 3) CALL cv3_param(klev, delt)
263    
264      ! --- INITIALIZE OUTPUT ARRAYS AND PARAMETERS      ! INITIALIZE OUTPUT ARRAYS AND PARAMETERS
265    
266      do k = 1, klev      do k = 1, klev
267         do i = 1, klon         do i = 1, klon
# Line 285  contains Line 289  contains
289         iflag1(i) = 0         iflag1(i) = 0
290         wd1(i) = 0.0         wd1(i) = 0.0
291         cape1(i) = 0.0         cape1(i) = 0.0
292         VPrecip1(i, klev+1) = 0.0         VPrecip1(i, klev + 1) = 0.0
293      end do      end do
294    
295      if (iflag_con == 3) then      if (iflag_con == 3) then
# Line 295  contains Line 299  contains
299         enddo         enddo
300      endif      endif
301    
302      ! --- CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY      ! CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY
303    
304      if (iflag_con == 3) then      if (iflag_con == 3) then
305         CALL cv3_prelim(klon, klev, klev + 1, t1, q1, p1, ph1, lv1, cpn1, tv1, &         CALL cv3_prelim(klon, klev, klev + 1, t1, q1, p1, ph1, lv1, cpn1, tv1, &
# Line 306  contains Line 310  contains
310              gz1, h1, hm1)              gz1, h1, hm1)
311      endif      endif
312    
313      ! --- CONVECTIVE FEED      ! CONVECTIVE FEED
314    
315      if (iflag_con == 3) then      if (iflag_con == 3) then
316         CALL cv3_feed(klon, klev, t1, q1, qs1, p1, ph1, gz1, nk1, icb1, &         CALL cv3_feed(klon, klev, t1, q1, qs1, p1, ph1, gz1, nk1, icb1, &
# Line 317  contains Line 321  contains
321              iflag1, tnk1, qnk1, gznk1, plcl1)              iflag1, tnk1, qnk1, gznk1, plcl1)
322      endif      endif
323    
324      ! --- UNDILUTE (ADIABATIC) UPDRAFT / 1st part      ! UNDILUTE (ADIABATIC) UPDRAFT / 1st part
325      ! (up through ICB for convect4, up through ICB+1 for convect3)      ! (up through ICB for convect4, up through ICB + 1 for convect3)
326      ! Calculates the lifted parcel virtual temperature at nk, the      ! Calculates the lifted parcel virtual temperature at nk, the
327      ! actual temperature, and the adiabatic liquid water content.      ! actual temperature, and the adiabatic liquid water content.
328    
# Line 331  contains Line 335  contains
335              tp1, tvp1, clw1)              tp1, tvp1, clw1)
336      endif      endif
337    
338      ! --- TRIGGERING      ! TRIGGERING
339    
340      if (iflag_con == 3) then      if (iflag_con == 3) then
341         CALL cv3_trigger(klon, klev, icb1, plcl1, p1, th1, tv1, tvp1, pbase1, &         CALL cv3_trigger(klon, klev, icb1, plcl1, p1, th1, tv1, tvp1, pbase1, &
# Line 341  contains Line 345  contains
345         CALL cv_trigger(klon, klev, icb1, cbmf1, tv1, tvp1, iflag1)         CALL cv_trigger(klon, klev, icb1, cbmf1, tv1, tvp1, iflag1)
346      end if      end if
347    
348      ! --- IF THIS POINT IS REACHED, MOIST CONVECTIVE ADJUSTMENT IS NECESSARY      ! Moist convective adjustment is necessary
349    
350      ncum = 0      ncum = 0
351      do i = 1, klon      do i = 1, klon
352         if(iflag1(i) == 0)then         if (iflag1(i) == 0) then
353            ncum = ncum+1            ncum = ncum + 1
354            idcum(ncum) = i            idcum(ncum) = i
355         endif         endif
356      end do      end do
357    
358      IF (ncum > 0) THEN      IF (ncum > 0) THEN
359         ! --- COMPRESS THE FIELDS         ! COMPRESS THE FIELDS
360         ! (-> vectorization over convective gridpoints)         ! (-> vectorization over convective gridpoints)
361    
362         if (iflag_con == 3) then         if (iflag_con == 3) then
# Line 371  contains Line 375  contains
375                 tv, tp, tvp, clw, dph)                 tv, tp, tvp, clw, dph)
376         endif         endif
377    
378         ! --- UNDILUTE (ADIABATIC) UPDRAFT / second part :         ! UNDILUTE (ADIABATIC) UPDRAFT / second part :
379         ! --- FIND THE REST OF THE LIFTED PARCEL TEMPERATURES         ! FIND THE REST OF THE LIFTED PARCEL TEMPERATURES
380         ! --- &         ! &
381         ! --- COMPUTE THE PRECIPITATION EFFICIENCIES AND THE         ! COMPUTE THE PRECIPITATION EFFICIENCIES AND THE
382         ! --- FRACTION OF PRECIPITATION FALLING OUTSIDE OF CLOUD         ! FRACTION OF PRECIPITATION FALLING OUTSIDE OF CLOUD
383         ! --- &         ! &
384         ! --- FIND THE LEVEL OF NEUTRAL BUOYANCY         ! FIND THE LEVEL OF NEUTRAL BUOYANCY
385    
386         if (iflag_con == 3) then         if (iflag_con == 3) then
387            CALL cv3_undilute2(klon, ncum, klev, icb, icbs, nk, tnk, qnk, gznk, &            CALL cv3_undilute2(klon, ncum, klev, icb, icbs, nk, tnk, qnk, gznk, &
# Line 390  contains Line 394  contains
394                 sigp, frac)                 sigp, frac)
395         endif         endif
396    
397         ! --- CLOSURE         ! CLOSURE
398    
399         if (iflag_con == 3) then         if (iflag_con == 3) then
400            CALL cv3_closure(klon, ncum, klev, icb, inb, pbase, p, ph, tv, &            CALL cv3_closure(klon, ncum, klev, icb, inb, pbase, p, ph, tv, &
# Line 401  contains Line 405  contains
405                 plcl, cpn, iflag, cbmf)                 plcl, cpn, iflag, cbmf)
406         endif         endif
407    
408         ! --- MIXING         ! MIXING
409    
410         if (iflag_con == 3) then         if (iflag_con == 3) then
411            CALL cv3_mixing(klon, ncum, klev, klev, icb, nk, inb, t, q, qs, u, &            CALL cv3_mixing(klon, ncum, klev, klev, icb, nk, inb, t, q, qs, u, &
# Line 414  contains Line 418  contains
418                 uent, vent, nent, sij, elij)                 uent, vent, nent, sij, elij)
419         endif         endif
420    
421         ! --- UNSATURATED (PRECIPITATING) DOWNDRAFTS         ! UNSATURATED (PRECIPITATING) DOWNDRAFTS
422    
423         if (iflag_con == 3) then         if (iflag_con == 3) then
424            CALL cv3_unsat(klon, ncum, klev, klev, icb, inb, t, q, qs, gz, u, &            CALL cv3_unsat(klon, ncum, klev, klev, icb, inb, t, q, qs, gz, u, &
# Line 427  contains Line 431  contains
431                 water, evap)                 water, evap)
432         endif         endif
433    
434         ! --- YIELD         ! YIELD
435         ! (tendencies, precipitation, variables of interface with other         ! (tendencies, precipitation, variables of interface with other
436         ! processes, etc)         ! processes, etc)
437    
# Line 446  contains Line 450  contains
450                 qcondc)                 qcondc)
451         endif         endif
452    
453         ! --- passive tracers         ! passive tracers
454    
455         if (iflag_con == 3) CALL cv3_tracer(klon, ncum, klev, ment, sij, da, phi)         if (iflag_con == 3) CALL cv3_tracer(klon, ncum, klev, ment, sij, da, phi)
456    
457         ! --- UNCOMPRESS THE FIELDS         ! UNCOMPRESS THE FIELDS
458    
459         ! set iflag1 = 42 for non convective points         ! set iflag1 = 42 for non convective points
460         do i = 1, klon         do i = 1, klon

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

  ViewVC Help
Powered by ViewVC 1.1.21