! $Id: cva_driver.F90 2007 2014-04-06 12:20:38Z fhourdin $ SUBROUTINE cva_driver(len, nd, ndp1, ntra, nloc, & iflag_con, iflag_mix, iflag_ice_thermo, iflag_clos, ok_conserv_q, & delt, t1, q1, qs1, t1_wake, q1_wake, qs1_wake, s1_wake, & u1, v1, tra1, & p1, ph1, & Ale1, Alp1, & sig1feed1, sig2feed1, wght1, & iflag1, ft1, fq1, fu1, fv1, ftra1, & precip1, kbas1, ktop1, & cbmf1, plcl1, plfc1, wbeff1, & sig1, w01, & !input/output ptop21, sigd1, & ma1, mip1, Vprecip1, upwd1, dnwd1, dnwd01, & qcondc1, wd1, & cape1, cin1, tvp1, & ftd1, fqd1, & Plim11, Plim21, asupmax1, supmax01, asupmaxmin1, & lalim_conv, & !! da1,phi1,mp1,phi21,d1a1,dam1,sigij1,clw1, & ! RomP !! elij1,evap1,ep1,epmlmMm1,eplaMm1, & ! RomP da1, phi1, mp1, phi21, d1a1, dam1, sigij1, wghti1, & ! RomP, RL clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, & ! RomP, RL wdtrainA1, wdtrainM1) ! RomP ! ************************************************************** ! * ! CV_DRIVER * ! * ! * ! written by : Sandrine Bony-Lena , 17/05/2003, 11.19.41 * ! modified by : * ! ************************************************************** ! ************************************************************** USE dimphy IMPLICIT NONE ! .............................START PROLOGUE............................ ! All argument names (except len,nd,ntra,nloc,delt and the flags) have a "1" appended. ! The "1" is removed for the corresponding compressed variables. ! PARAMETERS: ! Name Type Usage Description ! ---------- ---------- ------- ---------------------------- ! len Integer Input first (i) dimension ! nd Integer Input vertical (k) dimension ! ndp1 Integer Input nd + 1 ! ntra Integer Input number of tracors ! iflag_con Integer Input version of convect (3/4) ! iflag_mix Integer Input version of mixing (0/1/2) ! iflag_ice_thermo Integer Input accounting for ice thermodynamics (0/1) ! iflag_clos Integer Input version of closure (0/1) ! ok_conserv_q Logical Input when true corrections for water conservation are swtiched on ! delt Real Input time step ! t1 Real Input temperature (sat draught envt) ! q1 Real Input specific hum (sat draught envt) ! qs1 Real Input sat specific hum (sat draught envt) ! t1_wake Real Input temperature (unsat draught envt) ! q1_wake Real Input specific hum(unsat draught envt) ! qs1_wake Real Input sat specific hum(unsat draughts envt) ! s1_wake Real Input fractionnal area covered by wakes ! u1 Real Input u-wind ! v1 Real Input v-wind ! tra1 Real Input tracors ! p1 Real Input full level pressure ! ph1 Real Input half level pressure ! ALE1 Real Input Available lifting Energy ! ALP1 Real Input Available lifting Power ! sig1feed1 Real Input sigma coord at lower bound of feeding layer ! sig2feed1 Real Input sigma coord at upper bound of feeding layer ! wght1 Real Input weight density determining the feeding mixture ! iflag1 Integer Output flag for Emanuel conditions ! ft1 Real Output temp tend ! fq1 Real Output spec hum tend ! fu1 Real Output u-wind tend ! fv1 Real Output v-wind tend ! ftra1 Real Output tracor tend ! precip1 Real Output precipitation ! kbas1 Integer Output cloud base level ! ktop1 Integer Output cloud top level ! cbmf1 Real Output cloud base mass flux ! sig1 Real In/Out section adiabatic updraft ! w01 Real In/Out vertical velocity within adiab updraft ! ptop21 Real In/Out top of entraining zone ! Ma1 Real Output mass flux adiabatic updraft ! mip1 Real Output mass flux shed by the adiabatic updraft ! Vprecip1 Real Output vertical profile of precipitations ! upwd1 Real Output total upward mass flux (adiab+mixed) ! dnwd1 Real Output saturated downward mass flux (mixed) ! dnwd01 Real Output unsaturated downward mass flux ! qcondc1 Real Output in-cld mixing ratio of condensed water ! wd1 Real Output downdraft velocity scale for sfc fluxes ! cape1 Real Output CAPE ! cin1 Real Output CIN ! tvp1 Real Output adiab lifted parcell virt temp ! ftd1 Real Output precip temp tend ! fqt1 Real Output precip spec hum tend ! Plim11 Real Output ! Plim21 Real Output ! asupmax1 Real Output ! supmax01 Real Output ! asupmaxmin1 Real Output ! ftd1 Real Output Array of temperature tendency due to precipitations (K/s) of dimension ND, ! defined at same grid levels as T, Q, QS and P. ! fqd1 Real Output Array of specific humidity tendencies due to precipitations ((gm/gm)/s) ! of dimension ND, defined at same grid levels as T, Q, QS and P. ! wdtrainA1 Real Output precipitation detrained from adiabatic draught; ! used in tracer transport (cvltr) ! wdtrainM1 Real Output precipitation detrained from mixed draughts; ! used in tracer transport (cvltr) ! da1 Real Output used in tracer transport (cvltr) ! phi1 Real Output used in tracer transport (cvltr) ! mp1 Real Output used in tracer transport (cvltr) ! phi21 Real Output used in tracer transport (cvltr) ! d1a1 Real Output used in tracer transport (cvltr) ! dam1 Real Output used in tracer transport (cvltr) ! epmlmMm1 Real Output used in tracer transport (cvltr) ! eplaMm1 Real Output used in tracer transport (cvltr) ! evap1 Real Output ! ep1 Real Output ! sigij1 Real Output used in tracer transport (cvltr) ! elij1 Real Output ! wghti1 Real Output final weight of the feeding layers, ! used in tracer transport (cvltr) ! S. Bony, Mar 2002: ! * Several modules corresponding to different physical processes ! * Several versions of convect may be used: ! - iflag_con=3: version lmd (previously named convect3) ! - iflag_con=4: version 4.3b (vect. version, previously convect1/2) ! + tard: - iflag_con=5: version lmd with ice (previously named convectg) ! S. Bony, Oct 2002: ! * Vectorization of convect3 (ie version lmd) ! ..............................END PROLOGUE............................. include "dimensions.h" !!!!!#include "dimphy.h" include 'iniprint.h' ! Input INTEGER len INTEGER nd INTEGER ndp1 INTEGER ntra INTEGER iflag_con INTEGER iflag_mix INTEGER iflag_ice_thermo INTEGER iflag_clos LOGICAL ok_conserv_q REAL delt REAL t1(len, nd) REAL q1(len, nd) REAL qs1(len, nd) REAL t1_wake(len, nd) REAL q1_wake(len, nd) REAL qs1_wake(len, nd) REAL s1_wake(len) REAL u1(len, nd) REAL v1(len, nd) REAL tra1(len, nd, ntra) REAL p1(len, nd) REAL ph1(len, ndp1) REAL Ale1(len) REAL Alp1(len) REAL sig1feed1 ! pressure at lower bound of feeding layer REAL sig2feed1 ! pressure at upper bound of feeding layer REAL wght1(nd) ! weight density determining the feeding mixture ! Output INTEGER iflag1(len) REAL ft1(len, nd) REAL fq1(len, nd) REAL fu1(len, nd) REAL fv1(len, nd) REAL ftra1(len, nd, ntra) REAL precip1(len) INTEGER kbas1(len) INTEGER ktop1(len) REAL cbmf1(len) REAL plcl1(klon) REAL plfc1(klon) REAL wbeff1(klon) REAL sig1(len, klev) !input/output REAL w01(len, klev) !input/output REAL ptop21(len) REAL sigd1(len) REAL ma1(len, nd) REAL mip1(len, nd) ! real Vprecip1(len,nd) REAL vprecip1(len, nd+1) REAL upwd1(len, nd) REAL dnwd1(len, nd) REAL dnwd01(len, nd) REAL qcondc1(len, nd) ! cld REAL wd1(len) ! gust REAL cape1(len) REAL cin1(len) REAL tvp1(len, nd) !AC! !! real da1(len,nd),phi1(len,nd,nd) !! real da(len,nd),phi(len,nd,nd) !AC! REAL ftd1(len, nd) REAL fqd1(len, nd) REAL Plim11(len) REAL Plim21(len) REAL asupmax1(len, nd) REAL supmax01(len) REAL asupmaxmin1(len) INTEGER lalim_conv(len) ! RomP >>> REAL wdtrainA1(len, nd), wdtrainM1(len, nd) REAL da1(len, nd), phi1(len, nd, nd), mp1(len, nd) REAL epmlmMm1(len, nd, nd), eplaMm1(len, nd) REAL evap1(len, nd), ep1(len, nd) REAL sigij1(len, nd, nd), elij1(len, nd, nd) !JYG,RL REAL wghti1(len, nd) ! final weight of the feeding layers !JYG,RL REAL phi21(len, nd, nd) REAL d1a1(len, nd), dam1(len, nd) ! RomP <<< ! ------------------------------------------------------------------- ! Prolog by Kerry Emanuel. ! ------------------------------------------------------------------- ! --- ARGUMENTS ! ------------------------------------------------------------------- ! --- On input: ! t: Array of absolute temperature (K) of dimension ND, 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 ND, 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 ND, 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. ! t_wake: Array of absolute temperature (K), seen by unsaturated draughts, ! of dimension ND, with first index corresponding to lowest model level. ! q_wake: Array of specific humidity (gm/gm), seen by unsaturated draughts, ! of dimension ND, with first index corresponding to lowest model level. ! Must be defined at same grid levels as T. ! qs_wake: Array of saturation specific humidity, seen by unsaturated draughts, ! of dimension ND, with first index corresponding to lowest model level. ! Must be defined at same grid levels as T. ! s_wake: Array of fractionnal area occupied by the wakes. ! u: Array of zonal wind velocity (m/s) of dimension ND, 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. ! tra: Array of passive tracer mixing ratio, of dimensions (ND,NTRA), ! where NTRA is the number of different tracers. If no ! convective tracer transport is needed, define a dummy ! input array of dimension (ND,1). Tracers are defined at ! same vertical levels as T. Note that this array will be altered ! if dry convective adjustment occurs and if IPBL is not equal to 0. ! p: Array of pressure (mb) of dimension ND, with first ! index corresponding to lowest model level. Must be defined ! at same grid levels as T. ! ph: Array of pressure (mb) of dimension ND+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. ! ALE: Available lifting Energy ! ALP: Available lifting Power ! nl: The maximum number of levels to which convection can penetrate, plus 1. ! NL MUST be less than or equal to ND-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 ND, defined at same ! grid levels as T, Q, QS and P. ! fq: Array of specific humidity tendencies ((gm/gm)/s) of dimension ND, ! defined at same grid levels as T, Q, QS and P. ! fu: Array of forcing of zonal velocity (m/s^2) of dimension ND, ! defined at same grid levels as T. ! fv: Same as FU, but for forcing of meridional velocity. ! ftra: Array of forcing of tracer content, in tracer mixing ratio per ! second, defined at same levels as T. Dimensioned (ND,NTRA). ! precip: Scalar convective precipitation rate (mm/day). ! 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 ND. ! ------------------------------------------------------------------- ! Local (non compressed) arrays INTEGER i, k, n, il, j INTEGER nword1, nword2, nword3, nword4 INTEGER icbmax INTEGER nk1(klon) INTEGER icb1(klon) INTEGER icbs1(klon) LOGICAL ok_inhib ! True => possible inhibition of convection by dryness LOGICAL, SAVE :: debut = .TRUE. !$OMP THREADPRIVATE(debut) REAL tnk1(klon) REAL thnk1(klon) REAL qnk1(klon) REAL gznk1(klon) REAL pnk1(klon) REAL qsnk1(klon) REAL unk1(klon) REAL vnk1(klon) REAL cpnk1(klon) REAL hnk1(klon) REAL pbase1(klon) REAL buoybase1(klon) REAL lf1(klon, klev), lf1_wake(klon, klev) REAL lv1(klon, klev), lv1_wake(klon, klev) REAL cpn1(klon, klev), cpn1_wake(klon, klev) REAL tv1(klon, klev), tv1_wake(klon, klev) REAL gz1(klon, klev), gz1_wake(klon, klev) REAL hm1(klon, klev), hm1_wake(klon, klev) REAL h1(klon, klev), h1_wake(klon, klev) REAL tp1(klon, klev) REAL clw1(klon, klev) REAL th1(klon, klev), th1_wake(klon, klev) REAL bid(klon, klev) ! dummy array INTEGER ncum INTEGER j1feed(klon) INTEGER j2feed(klon) REAL p1feed1(len) ! pressure at lower bound of feeding layer REAL p2feed1(len) ! pressure at upper bound of feeding layer !JYG,RL !! real wghti1(len,nd) ! weights of the feeding layers !JYG,RL ! (local) compressed fields: INTEGER nloc ! parameter (nloc=klon) ! pour l'instant INTEGER idcum(nloc) INTEGER iflag(nloc), nk(nloc), icb(nloc) INTEGER nent(nloc, klev) INTEGER icbs(nloc) INTEGER inb(nloc), inbis(nloc) REAL cbmf(nloc), plcl(nloc), plfc(nloc), wbeff(nloc) REAL t(nloc, klev), q(nloc, klev), qs(nloc, klev) REAL t_wake(nloc, klev), q_wake(nloc, klev), qs_wake(nloc, klev) REAL s_wake(nloc) REAL u(nloc, klev), v(nloc, klev) REAL gz(nloc, klev), h(nloc, klev), hm(nloc, klev) REAL h_wake(nloc, klev), hm_wake(nloc, klev) REAL lv(nloc, klev), lf(nloc, klev), cpn(nloc, klev) REAL lv_wake(nloc, klev), lf_wake(nloc, klev), cpn_wake(nloc, klev) REAL p(nloc, klev), ph(nloc, klev+1), tv(nloc, klev), tp(nloc, klev) REAL tv_wake(nloc, klev) REAL clw(nloc, klev) REAL dph(nloc, klev) REAL pbase(nloc), buoybase(nloc), th(nloc, klev) REAL th_wake(nloc, klev) REAL tvp(nloc, klev) REAL sig(nloc, klev), w0(nloc, klev), ptop2(nloc) REAL hp(nloc, klev), ep(nloc, klev), sigp(nloc, klev) REAL buoy(nloc, klev) REAL cape(nloc) REAL cin(nloc) REAL m(nloc, klev) REAL ment(nloc, klev, klev), sigij(nloc, klev, klev) REAL qent(nloc, klev, klev) REAL hent(nloc, klev, klev) REAL uent(nloc, klev, klev), vent(nloc, klev, klev) REAL ments(nloc, klev, klev), qents(nloc, klev, klev) REAL elij(nloc, klev, klev) REAL supmax(nloc, klev) REAL Ale(nloc), Alp(nloc), coef_clos(nloc) REAL sigd(nloc) ! real mp(nloc,klev), qp(nloc,klev), up(nloc,klev), vp(nloc,klev) ! real wt(nloc,klev), water(nloc,klev), evap(nloc,klev), ice(nloc,klev) ! real b(nloc,klev), sigd(nloc) ! save mp,qp,up,vp,wt,water,evap,b REAL, SAVE, ALLOCATABLE :: mp(:, :), qp(:, :), up(:, :), vp(:, :) REAL, SAVE, ALLOCATABLE :: wt(:, :), water(:, :), evap(:, :) REAL, SAVE, ALLOCATABLE :: ice(:, :), fondue(:, :), b(:, :) REAL, SAVE, ALLOCATABLE :: frac(:, :), faci(:, :) !$OMP THREADPRIVATE(mp,qp,up,vp,wt,water,evap,ice,fondue,b,frac,faci) REAL ft(nloc, klev), fq(nloc, klev) REAL ftd(nloc, klev), fqd(nloc, klev) REAL fu(nloc, klev), fv(nloc, klev) REAL upwd(nloc, klev), dnwd(nloc, klev), dnwd0(nloc, klev) REAL ma(nloc, klev), mip(nloc, klev), tls(nloc, klev) REAL tps(nloc, klev), qprime(nloc), tprime(nloc) REAL precip(nloc) ! real Vprecip(nloc,klev) REAL vprecip(nloc, klev+1) REAL tra(nloc, klev, ntra), trap(nloc, klev, ntra) REAL ftra(nloc, klev, ntra), traent(nloc, klev, klev, ntra) REAL qcondc(nloc, klev) ! cld REAL wd(nloc) ! gust REAL Plim1(nloc), plim2(nloc) REAL asupmax(nloc, klev) REAL supmax0(nloc) REAL asupmaxmin(nloc) REAL tnk(nloc), qnk(nloc), gznk(nloc) REAL wghti(nloc, nd) REAL hnk(nloc), unk(nloc), vnk(nloc) ! RomP >>> REAL wdtrainA(nloc, klev), wdtrainM(nloc, klev) REAL da(len, nd), phi(len, nd, nd) REAL epmlmMm(nloc, klev, klev), eplaMm(nloc, klev) REAL phi2(len, nd, nd) REAL d1a(len, nd), dam(len, nd) ! RomP <<< LOGICAL, SAVE :: first = .TRUE. !$OMP THREADPRIVATE(first) CHARACTER (LEN=20) :: modname = 'cva_driver' CHARACTER (LEN=80) :: abort_message ! print *, 't1, t1_wake ',(k,t1(1,k),t1_wake(1,k),k=1,klev) ! print *, 'q1, q1_wake ',(k,q1(1,k),q1_wake(1,k),k=1,klev) ! ------------------------------------------------------------------- ! --- SET CONSTANTS AND PARAMETERS ! ------------------------------------------------------------------- IF (first) THEN ALLOCATE (mp(nloc,klev), qp(nloc,klev), up(nloc,klev)) ALLOCATE (vp(nloc,klev), wt(nloc,klev), water(nloc,klev)) ALLOCATE (ice(nloc,klev), fondue(nloc,klev)) ALLOCATE (evap(nloc,klev), b(nloc,klev)) ALLOCATE (frac(nloc,klev), faci(nloc,klev)) first = .FALSE. END IF ! -- set simulation flags: ! (common cvflag) CALL cv_flag(iflag_ice_thermo) ! -- set thermodynamical constants: ! (common cvthermo) CALL cv_thermo(iflag_con) ! -- set convect parameters ! includes microphysical parameters and parameters that ! control the rate of approach to quasi-equilibrium) ! (common cvparam) IF (iflag_con==3) THEN CALL cv3_param(nd, delt) END IF IF (iflag_con==4) THEN CALL cv_param(nd) END IF ! --------------------------------------------------------------------- ! --- INITIALIZE OUTPUT ARRAYS AND PARAMETERS ! --------------------------------------------------------------------- nword1 = len nword2 = len*nd nword3 = len*nd*ntra nword4 = len*nd*nd iflag1(:) = 0 ktop1(:) = 0 kbas1(:) = 0 ft1(:, :) = 0.0 fq1(:, :) = 0.0 fu1(:, :) = 0.0 fv1(:, :) = 0.0 ftra1(:, :, :) = 0. precip1(:) = 0. cbmf1(:) = 0. ptop21(:) = 0. sigd1(:) = 0. ma1(:, :) = 0. mip1(:, :) = 0. vprecip1(:, :) = 0. upwd1(:, :) = 0. dnwd1(:, :) = 0. dnwd01(:, :) = 0. qcondc1(:, :) = 0. wd1(:) = 0. cape1(:) = 0. cin1(:) = 0. tvp1(:, :) = 0. ftd1(:, :) = 0. fqd1(:, :) = 0. Plim11(:) = 0. Plim21(:) = 0. asupmax1(:, :) = 0. supmax01(:) = 0. asupmaxmin1(:) = 0. DO il = 1, len cin1(il) = -100000. cape1(il) = -1. END DO IF (iflag_con==3) THEN DO il = 1, len sig1(il, nd) = sig1(il, nd) + 1. sig1(il, nd) = amin1(sig1(il,nd), 12.1) END DO END IF ! RomP >>> wdtrainA1(:, :) = 0. wdtrainM1(:, :) = 0. da1(:, :) = 0. phi1(:, :, :) = 0. epmlmMm1(:, :, :) = 0. eplaMm1(:, :) = 0. mp1(:, :) = 0. evap1(:, :) = 0. ep1(:, :) = 0. sigij1(:, :, :) = 0. elij1(:, :, :) = 0. phi21(:, :, :) = 0. d1a1(:, :) = 0. dam1(:, :) = 0. ! RomP <<< ! --------------------------------------------------------------------- ! --- INITIALIZE LOCAL ARRAYS AND PARAMETERS ! --------------------------------------------------------------------- DO il = 1, nloc coef_clos(il) = 1. END DO ! -------------------------------------------------------------------- ! --- CALCULATE ARRAYS OF GEOPOTENTIAL, HEAT CAPACITY & STATIC ENERGY ! -------------------------------------------------------------------- IF (iflag_con==3) THEN IF (debut) THEN PRINT *, 'Emanuel version 3 nouvelle' END IF ! print*,'t1, q1 ',t1,q1 CALL cv3_prelim(len, nd, ndp1, t1, q1, p1, ph1, & ! nd->na lv1, lf1, cpn1, tv1, gz1, h1, hm1, th1) CALL cv3_prelim(len, nd, ndp1, t1_wake, q1_wake, p1, ph1, & ! nd->na lv1_wake, lf1_wake, cpn1_wake, tv1_wake, gz1_wake, & h1_wake, bid, th1_wake) END IF IF (iflag_con==4) THEN PRINT *, 'Emanuel version 4 ' CALL cv_prelim(len, nd, ndp1, t1, q1, p1, ph1, & lv1, cpn1, tv1, gz1, h1, hm1) END IF ! -------------------------------------------------------------------- ! --- CONVECTIVE FEED ! -------------------------------------------------------------------- ! compute feeding layer potential temperature and mixing ratio : ! get bounds of feeding layer ! test niveaux couche alimentation KE IF (sig1feed1==sig2feed1) THEN WRITE (lunout, *) 'impossible de choisir sig1feed=sig2feed' WRITE (lunout, *) 'changer la valeur de sig2feed dans physiq.def' abort_message = '' CALL abort_gcm(modname, abort_message, 1) END IF DO i = 1, len p1feed1(i) = sig1feed1*ph1(i, 1) p2feed1(i) = sig2feed1*ph1(i, 1) !test maf ! p1feed1(i)=ph1(i,1) ! p2feed1(i)=ph1(i,2) ! p2feed1(i)=ph1(i,3) !testCR: on prend la couche alim des thermiques ! p2feed1(i)=ph1(i,lalim_conv(i)+1) ! print*,'lentr=',lentr(i),ph1(i,lentr(i)+1),ph1(i,2) END DO IF (iflag_con==3) THEN END IF DO i = 1, len ! print*,'avant cv3_feed Plim',p1feed1(i),p2feed1(i) END DO IF (iflag_con==3) THEN ! print*, 'IFLAG1 avant cv3_feed' ! print*,'len,nd',len,nd ! write(*,'(64i1)') iflag1(2:klon-1) CALL cv3_feed(len, nd, ok_conserv_q, & ! nd->na t1, q1, u1, v1, p1, ph1, hm1, gz1, & p1feed1, p2feed1, wght1, & wghti1, tnk1, thnk1, qnk1, qsnk1, unk1, vnk1, & cpnk1, hnk1, nk1, icb1, icbmax, iflag1, gznk1, plcl1) END IF ! print*, 'IFLAG1 apres cv3_feed' ! print*,'len,nd',len,nd ! write(*,'(64i1)') iflag1(2:klon-1) IF (iflag_con==4) THEN CALL cv_feed(len, nd, t1, q1, qs1, p1, hm1, gz1, & nk1, icb1, icbmax, iflag1, tnk1, qnk1, gznk1, plcl1) END IF ! print *, 'cv3_feed-> iflag1, plcl1 ',iflag1(1),plcl1(1) ! -------------------------------------------------------------------- ! --- 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. ! -------------------------------------------------------------------- IF (iflag_con==3) THEN CALL cv3_undilute1(len, nd, t1, qs1, gz1, plcl1, p1, icb1, tnk1, qnk1, & ! nd->na gznk1, tp1, tvp1, clw1, icbs1) END IF IF (iflag_con==4) THEN CALL cv_undilute1(len, nd, t1, q1, qs1, gz1, p1, nk1, icb1, icbmax, & tp1, tvp1, clw1) END IF ! ------------------------------------------------------------------- ! --- TRIGGERING ! ------------------------------------------------------------------- ! print *,' avant triggering, iflag_con ',iflag_con IF (iflag_con==3) THEN CALL cv3_trigger(len, nd, icb1, plcl1, p1, th1, tv1, tvp1, thnk1, & ! nd->na pbase1, buoybase1, iflag1, sig1, w01) ! print*, 'IFLAG1 apres cv3_triger' ! print*,'len,nd',len,nd ! write(*,'(64i1)') iflag1(2:klon-1) ! call dump2d(iim,jjm-1,sig1(2) END IF IF (iflag_con==4) THEN CALL cv_trigger(len, nd, icb1, cbmf1, tv1, tvp1, iflag1) END IF ! ===================================================================== ! --- IF THIS POINT IS REACHED, MOIST CONVECTIVE ADJUSTMENT IS NECESSARY ! ===================================================================== ncum = 0 DO i = 1, len IF (iflag1(i)==0) THEN ncum = ncum + 1 idcum(ncum) = i END IF END DO ! print*,'klon, ncum = ',len,ncum IF (ncum>0) THEN ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ! --- COMPRESS THE FIELDS ! (-> vectorization over convective gridpoints) ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ IF (iflag_con==3) THEN ! print*,'ncum tv1 ',ncum,tv1 ! print*,'tvp1 ',tvp1 CALL cv3a_compress(len, nloc, ncum, nd, ntra, & iflag1, nk1, icb1, icbs1, & plcl1, tnk1, qnk1, gznk1, hnk1, unk1, vnk1, & wghti1, pbase1, buoybase1, & t1, q1, qs1, t1_wake, q1_wake, qs1_wake, s1_wake, & u1, v1, gz1, th1, th1_wake, & tra1, & h1, lv1, lf1, cpn1, p1, ph1, tv1, tp1, tvp1, clw1, & h1_wake, lv1_wake, lf1_wake, cpn1_wake, tv1_wake, & sig1, w01, ptop21, & Ale1, Alp1, & iflag, nk, icb, icbs, & plcl, tnk, qnk, gznk, hnk, unk, vnk, & wghti, pbase, buoybase, & t, q, qs, t_wake, q_wake, qs_wake, s_wake, & u, v, gz, th, th_wake, & tra, & h, lv, lf, cpn, p, ph, tv, tp, tvp, clw, & h_wake, lv_wake, lf_wake, cpn_wake, tv_wake, & sig, w0, ptop2, & Ale, Alp) ! print*,'tv ',tv ! print*,'tvp ',tvp END IF IF (iflag_con==4) THEN CALL cv_compress(len, nloc, ncum, nd, & 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) END IF ! ------------------------------------------------------------------- ! --- 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(nloc, ncum, nd, icb, icbs, nk, & !na->nd tnk, qnk, gznk, hnk, t, q, qs, gz, & p, h, tv, lv, lf, pbase, buoybase, plcl, & inb, tp, tvp, clw, hp, ep, sigp, buoy, & frac) END IF IF (iflag_con==4) THEN CALL cv_undilute2(nloc, ncum, nd, icb, nk, & tnk, qnk, gznk, t, q, qs, gz, & p, dph, h, tv, lv, & inb, inbis, tp, tvp, clw, hp, ep, sigp, frac) END IF ! ------------------------------------------------------------------- ! --- MIXING(1) (if iflag_mix .ge. 1) ! ------------------------------------------------------------------- IF (iflag_con==3) THEN IF ((iflag_ice_thermo==1) .AND. (iflag_mix/=0)) THEN WRITE (*, *) ' iflag_ice_thermo==1 requires iflag_mix==0', ' but iflag_mix=', iflag_mix, & '. Might as well stop here.' STOP END IF IF (iflag_mix>=1) THEN CALL zilch(supmax, nloc*klev) CALL cv3p_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb, & ! na->nd ph, t, q, qs, u, v, tra, h, lv, qnk, & unk, vnk, hp, tv, tvp, ep, clw, sig, & ment, qent, hent, uent, vent, nent, & sigij, elij, supmax, ments, qents, traent) ! print*, 'cv3p_mixing-> supmax ', (supmax(1,k), k=1,nd) ELSE CALL zilch(supmax, nloc*klev) END IF END IF ! ------------------------------------------------------------------- ! --- CLOSURE ! ------------------------------------------------------------------- IF (iflag_con==3) THEN IF (iflag_clos==0) THEN CALL cv3_closure(nloc, ncum, nd, icb, inb, & ! na->nd pbase, p, ph, tv, buoy, & sig, w0, cape, m, iflag) END IF ok_inhib = iflag_mix == 2 IF (iflag_clos==1) THEN PRINT *, ' pas d appel cv3p_closure' ! c CALL cv3p_closure(nloc,ncum,nd,icb,inb ! na->nd ! c : ,pbase,plcl,p,ph,tv,tvp,buoy ! c : ,supmax ! c o ,sig,w0,ptop2,cape,cin,m) END IF IF (iflag_clos==2) THEN CALL cv3p1_closure(nloc, ncum, nd, icb, inb, & ! na->nd pbase, plcl, p, ph, tv, tvp, buoy, & supmax, ok_inhib, Ale, Alp, & sig, w0, ptop2, cape, cin, m, iflag, coef_clos, & Plim1, plim2, asupmax, supmax0, & asupmaxmin, cbmf, plfc, wbeff) PRINT *, 'cv3p1_closure-> plfc,wbeff ', plfc(1), wbeff(1) END IF END IF ! iflag_con.eq.3 IF (iflag_con==4) THEN CALL cv_closure(nloc, ncum, nd, nk, icb, & tv, tvp, p, ph, dph, plcl, cpn, & iflag, cbmf) END IF ! print *,'cv_closure-> cape ',cape(1) ! ------------------------------------------------------------------- ! --- MIXING(2) ! ------------------------------------------------------------------- IF (iflag_con==3) THEN IF (iflag_mix==0) THEN CALL cv3_mixing(nloc, ncum, nd, nd, ntra, icb, nk, inb, & ! na->nd ph, t, q, qs, u, v, tra, h, lv, lf, frac, qnk, & unk, vnk, hp, tv, tvp, ep, clw, m, sig, & ment, qent, uent, vent, nent, sigij, elij, ments, qents, traent) CALL zilch(hent, nloc*klev*klev) ELSE CALL cv3_mixscale(nloc, ncum, nd, ment, m) IF (debut) THEN PRINT *, ' cv3_mixscale-> ' END IF !(debut) THEN END IF END IF IF (iflag_con==4) THEN CALL cv_mixing(nloc, ncum, nd, 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, sigij, elij) END IF IF (debut) THEN PRINT *, ' cv_mixing ->' END IF !(debut) THEN ! do i = 1,klev ! print*,'cv_mixing-> i,ment ',i,(ment(1,i,j),j=1,klev) ! enddo ! ------------------------------------------------------------------- ! --- UNSATURATED (PRECIPITATING) DOWNDRAFTS ! ------------------------------------------------------------------- IF (iflag_con==3) THEN IF (debut) THEN PRINT *, ' cva_driver -> cv3_unsat ' END IF !(debut) THEN CALL cv3_unsat(nloc, ncum, nd, nd, ntra, icb, inb, iflag, & ! na->nd t_wake, q_wake, qs_wake, gz, u, v, tra, p, ph, & th_wake, tv_wake, lv_wake, lf_wake, cpn_wake, & ep, sigp, clw, & m, ment, elij, delt, plcl, coef_clos, & mp, qp, up, vp, trap, wt, water, evap, fondue, ice, & faci, b, sigd, & wdtrainA, wdtrainM) ! RomP END IF IF (iflag_con==4) THEN CALL cv_unsat(nloc, ncum, nd, 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) END IF IF (debut) THEN PRINT *, 'cv_unsat-> ' END IF !(debut) THEN ! print *,'cv_unsat-> mp ',mp ! print *,'cv_unsat-> water ',water ! ------------------------------------------------------------------- ! --- YIELD ! (tendencies, precipitation, variables of interface with other ! processes, etc) ! ------------------------------------------------------------------- IF (iflag_con==3) THEN CALL cv3_yield(nloc, ncum, nd, nd, ntra, ok_conserv_q, & ! na->nd icb, inb, delt, & t, q, t_wake, q_wake, s_wake, u, v, tra, & gz, p, ph, h, hp, lv, lf, cpn, th, th_wake, & ep, clw, m, tp, mp, qp, up, vp, trap, & wt, water, ice, evap, fondue, faci, b, sigd, & ment, qent, hent, iflag_mix, uent, vent, & nent, elij, traent, sig, & tv, tvp, wghti, & iflag, precip, vprecip, ft, fq, fu, fv, ftra, & cbmf, upwd, dnwd, dnwd0, ma, mip, & tls, tps, qcondc, wd, & ftd, fqd) END IF IF (debut) THEN PRINT *, ' cv3_yield -> fqd(1) = ', fqd(1, 1) END IF !(debut) THEN IF (iflag_con==4) THEN CALL cv_yield(nloc, ncum, nd, 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) END IF !AC! !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ !--- passive tracers !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ IF (iflag_con==3) THEN !RomP >>> CALL cv3_tracer(nloc, len, ncum, nd, nd, & ment, sigij, da, phi, phi2, d1a, dam, & ep, vprecip, elij, clw, epmlmMm, eplaMm, & icb, inb) !RomP <<< END IF !AC! ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ! --- UNCOMPRESS THE FIELDS ! ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ IF (iflag_con==3) THEN CALL cv3a_uncompress(nloc, len, ncum, nd, ntra, idcum, & iflag, icb, inb, & precip, cbmf, plcl, plfc, wbeff, sig, w0, ptop2, & ft, fq, fu, fv, ftra, & sigd, ma, mip, vprecip, upwd, dnwd, dnwd0, & qcondc, wd, cape, cin, & tvp, & ftd, fqd, & Plim1, plim2, asupmax, supmax0, & asupmaxmin, & da, phi, mp, phi2, d1a, dam, sigij, & ! RomP clw, elij, evap, ep, epmlmMm, eplaMm, & ! RomP wdtrainA, wdtrainM, & ! RomP iflag1, kbas1, ktop1, & precip1, cbmf1, plcl1, plfc1, wbeff1, sig1, w01, ptop21, & ft1, fq1, fu1, fv1, ftra1, & sigd1, ma1, mip1, vprecip1, upwd1, dnwd1, dnwd01, & qcondc1, wd1, cape1, cin1, & tvp1, & ftd1, fqd1, & Plim11, plim21, asupmax1, supmax01, & asupmaxmin1, & da1, phi1, mp1, phi21, d1a1, dam1, sigij1, & ! RomP clw1, elij1, evap1, ep1, epmlmMm1, eplaMm1, & ! RomP wdtrainA1, wdtrainM1) ! RomP END IF IF (iflag_con==4) THEN CALL cv_uncompress(nloc, len, ncum, nd, idcum, & iflag, & precip, cbmf, & ft, fq, fu, fv, & ma, qcondc, & iflag1, & precip1,cbmf1, & ft1, fq1, fu1, fv1, & ma1, qcondc1) END IF END IF ! ncum>0 IF (debut) THEN PRINT *, ' cv_compress -> ' debut = .FALSE. END IF !(debut) THEN RETURN END SUBROUTINE cva_driver