--- trunk/Sources/phylmd/cv_driver.f 2016/03/22 16:31:39 188 +++ trunk/Sources/phylmd/cv_driver.f 2016/03/29 15:20:23 189 @@ -5,8 +5,8 @@ contains SUBROUTINE cv_driver(t1, q1, qs1, u1, v1, p1, ph1, iflag1, ft1, fq1, fu1, & - fv1, precip1, VPrecip1, sig1, w01, icb1, inb1, delt, Ma1, upwd1, & - dnwd1, dnwd01, qcondc1, wd1, cape1, da1, phi1, mp1) + fv1, precip1, VPrecip1, sig1, w01, icb1, inb1, delt, Ma1, upwd1, dnwd1, & + dnwd01, qcondc1, cape1, da1, phi1, mp1) ! From LMDZ4/libf/phylmd/cv_driver.F, version 1.3, 2005/04/15 12:36:17 ! Main driver for convection @@ -21,41 +21,27 @@ use cv30_param_m, only: cv30_param, nl use cv30_prelim_m, only: cv30_prelim use cv30_tracer_m, only: cv30_tracer + use cv30_trigger_m, only: cv30_trigger use cv30_uncompress_m, only: cv30_uncompress use cv30_undilute2_m, only: cv30_undilute2 use cv30_unsat_m, only: cv30_unsat use cv30_yield_m, only: cv30_yield USE dimphy, ONLY: klev, klon - real, intent(in):: t1(klon, klev) - ! temperature (K), with first index corresponding to lowest model - ! level - - real, intent(in):: q1(klon, klev) - ! Specific humidity, with first index corresponding to lowest - ! model level. Must be defined at same grid levels as T1. - - real, intent(in):: qs1(klon, klev) - ! Saturation specific humidity, with first index corresponding to - ! lowest model level. Must be defined at same grid levels as - ! T1. + real, intent(in):: t1(klon, klev) ! temperature (K) + real, intent(in):: q1(klon, klev) ! specific humidity + real, intent(in):: qs1(klon, klev) ! saturation specific humidity real, intent(in):: u1(klon, klev), v1(klon, klev) - ! Zonal wind and meridional velocity (m/s), witth first index - ! corresponding with the lowest model level. Defined at same - ! levels as T1. - - real, intent(in):: p1(klon, klev) - ! Full level pressure (mb) of dimension KLEV, with first index - ! corresponding to lowest model level. Must be defined at same - ! grid levels as T1. + ! zonal wind and meridional velocity (m/s) + + real, intent(in):: p1(klon, klev) ! full level pressure (hPa) real, intent(in):: ph1(klon, klev + 1) - ! Half level pressure (mb), with first index corresponding to - ! lowest level. These pressures are defined at levels intermediate - ! between those of P1, T1, Q1 and QS1. The first value of PH - ! should be greater than (i.e. at a lower level than) the first - ! value of the array P1. + ! Half level pressure (hPa). These pressures are defined at levels + ! intermediate between those of P1, T1, Q1 and QS1. The first + ! value of PH should be greater than (i.e. at a lower level than) + ! the first value of the array P1. integer, intent(out):: iflag1(klon) ! Flag for Emanuel conditions. @@ -82,24 +68,18 @@ ! 9: No moist convection: cloud base is higher then the level NL-1. - real, intent(out):: ft1(klon, klev) - ! Temperature tendency (K/s), defined at same grid levels as T1, - ! Q1, QS1 and P1. - - real, intent(out):: fq1(klon, klev) - ! Specific humidity tendencies (s-1), defined at same grid levels - ! as T1, Q1, QS1 and P1. + real, intent(out):: ft1(klon, klev) ! temperature tendency (K/s) + real, intent(out):: fq1(klon, klev) ! specific humidity tendency (s-1) real, intent(out):: fu1(klon, klev), fv1(klon, klev) - ! Forcing (tendency) of zonal and meridional velocity (m/s^2), - ! defined at same grid levels as T1. + ! forcing (tendency) of zonal and meridional velocity (m/s^2) real, intent(out):: precip1(klon) ! convective precipitation rate (mm/day) real, intent(out):: VPrecip1(klon, klev + 1) ! vertical profile of convective precipitation (kg/m2/s) - real, intent(inout):: sig1(klon, klev) ! section adiabatic updraft + real, intent(inout):: sig1(klon, klev) ! section of adiabatic updraft real, intent(inout):: w01(klon, klev) ! vertical velocity within adiabatic updraft @@ -108,41 +88,34 @@ integer, intent(inout):: inb1(klon) real, intent(in):: delt ! the model time step (sec) between calls - real Ma1(klon, klev) ! Output mass flux adiabatic updraft + real, intent(out):: Ma1(klon, klev) ! mass flux of adiabatic updraft real, intent(out):: upwd1(klon, klev) - ! total upward mass flux (adiab + mixed) + ! total upward mass flux (adiabatic + 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) ! Output in-cld mixing ratio of condensed water - - real wd1(klon) ! gust - ! Output downdraft velocity scale for surface fluxes - ! A convective downdraft velocity scale. For use in surface - ! flux parameterizations. See convect.ps file for details. + real, intent(out):: qcondc1(klon, klev) + ! in-cloud mixing ratio of condensed water - real cape1(klon) ! Output + real, intent(out):: cape1(klon) real, intent(inout):: da1(klon, klev), phi1(klon, klev, klev) real, intent(inout):: mp1(klon, klev) ! Local: real da(klon, klev), phi(klon, klev, klev), mp(klon, klev) - integer i, k, il integer icbmax integer nk1(klon) integer icbs1(klon) - real plcl1(klon) real tnk1(klon) real qnk1(klon) real gznk1(klon) real pbase1(klon) real buoybase1(klon) - real lv1(klon, klev) real cpn1(klon, klev) real tv1(klon, klev) @@ -153,17 +126,14 @@ real tvp1(klon, klev) real clw1(klon, klev) real th1(klon, klev) - integer ncum ! Compressed fields: - integer idcum(klon) integer iflag(klon), nk(klon), icb(klon) integer nent(klon, klev) integer icbs(klon) integer inb(klon) - real plcl(klon), tnk(klon), qnk(klon), gznk(klon) real t(klon, klev), q(klon, klev), qs(klon, klev) real u(klon, klev), v(klon, klev) @@ -182,7 +152,7 @@ real sij(klon, klev, klev), elij(klon, klev, klev) real qp(klon, klev), up(klon, klev), vp(klon, klev) real wt(klon, klev), water(klon, klev), evap(klon, klev) - real, allocatable:: b(:, :) ! (ncum, nl) + real, allocatable:: b(:, :) ! (ncum, nl - 1) real ft(klon, klev), fq(klon, klev) real fu(klon, klev), fv(klon, klev) real upwd(klon, klev), dnwd(klon, klev), dnwd0(klon, klev) @@ -191,7 +161,6 @@ real precip(klon) real VPrecip(klon, klev + 1) real qcondc(klon, klev) ! cld - real wd(klon) ! gust !------------------------------------------------------------------- @@ -232,7 +201,6 @@ do i = 1, klon precip1(i) = 0. iflag1(i) = 0 - wd1(i) = 0. cape1(i) = 0. VPrecip1(i, klev + 1) = 0. end do @@ -250,10 +218,6 @@ CALL cv30_feed(klon, klev, t1, q1, qs1, p1, ph1, gz1, nk1, icb1, & icbmax, iflag1, tnk1, qnk1, gznk1, plcl1) ! klev->na - ! UNDILUTE (ADIABATIC) UPDRAFT / 1st part - ! (up through ICB for convect4, up through ICB + 1 for convect3) - ! Calculates the lifted parcel virtual temperature at nk, the - ! actual temperature, and the adiabatic liquid water content. CALL cv30_undilute1(klon, klev, t1, q1, qs1, gz1, plcl1, p1, nk1, icb1, & tp1, tvp1, clw1, icbs1) ! klev->na @@ -272,17 +236,12 @@ end do IF (ncum > 0) THEN - allocate(b(ncum, nl)) - - ! COMPRESS THE FIELDS - ! (-> vectorization over convective gridpoints) - CALL cv30_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) - + allocate(b(ncum, nl - 1)) + CALL cv30_compress(ncum, 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) CALL cv30_undilute2(ncum, icb, icbs, nk, tnk, qnk, gznk, t, qs, gz, p, & h, tv, lv, pbase, buoybase, plcl, inb(:ncum), tp, tvp, clw, hp, & ep, sigp, buoy) @@ -298,8 +257,8 @@ ! Unsaturated (precipitating) downdrafts CALL cv30_unsat(icb(:ncum), inb(:ncum), 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) + tv, lv, cpn, ep, sigp, clw, m, ment, elij, delt, plcl, mp, & + qp(:ncum, :nl), up(:ncum, :nl), vp(:ncum, :nl), wt, water, evap, b) ! Yield (tendencies, precipitation, variables of interface with ! other processes, etc) @@ -307,21 +266,17 @@ h, hp, lv, cpn, th, ep, clw, m, tp, mp, qp, up, vp, wt, & water(:ncum, :nl), evap(:ncum, :nl), 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) + upwd, dnwd, dnwd0, ma, mike, tls, tps, qcondc) - ! passive tracers CALL cv30_tracer(klon, ncum, klev, ment, sij, da, phi) ! UNCOMPRESS THE FIELDS - - ! set iflag1 = 42 for non convective points - iflag1 = 42 - + iflag1 = 42 ! for non convective points CALL cv30_uncompress(idcum(:ncum), iflag, precip, VPrecip, sig, w0, & - ft, fq, fu, fv, inb, Ma, upwd, dnwd, dnwd0, qcondc, wd, cape, & + ft, fq, fu, fv, inb, Ma, upwd, dnwd, dnwd0, qcondc, cape, & da, phi, mp, iflag1, precip1, VPrecip1, sig1, w01, ft1, fq1, & - fu1, fv1, inb1, Ma1, upwd1, dnwd1, dnwd01, qcondc1, wd1, & - cape1, da1, phi1, mp1) + fu1, fv1, inb1, Ma1, upwd1, dnwd1, dnwd01, qcondc1, cape1, da1, & + phi1, mp1) ENDIF end SUBROUTINE cv_driver