! ! ! SUBROUTINE thermcell_plume(itap,ngrid,nlay,ptimestep,ztv, & zthl,po,zl,rhobarz,zlev,pplev,pphi,zpspsk, & alim_star,alim_star_tot,lalim,f0,detr_star, & entr_star,f_star,ztva,ztla,zqla,zqta,zha, & zw2,w_est,ztva_est,zqsatth,lmix,lmix_bis, & lmin,lev_out,lunout1,igout) !============================================================================== ! thermcell_plume: calcule les valeurs de qt, thetal et w dans l ascendance ! AB : ql means "liquid water mass mixing ratio" ! qt means "total water mass mixing ratio" ! TP means "potential temperature" ! TRPV means "virtual potential temperature with latent heat release" ! TPV means "virtual potential temperature" ! TR means "temperature with latent heat release" !============================================================================== USE print_control_mod, ONLY: prt_level USE watercommon_h, ONLY: RLvCp, RETV, Psat_water USE thermcell_mod IMPLICIT NONE !============================================================================== ! Declaration !============================================================================== ! inputs: ! ------- INTEGER itap INTEGER ngrid INTEGER nlay INTEGER lunout1 INTEGER igout INTEGER lev_out ! niveau pour les print REAL ptimestep ! time step REAL ztv(ngrid,nlay) ! TRPV environment REAL zthl(ngrid,nlay) ! TP environment REAL po(ngrid,nlay) ! qt environment REAL zl(ngrid,nlay) ! ql environment REAL rhobarz(ngrid,nlay) ! levels density REAL zlev(ngrid,nlay+1) ! levels altitude REAL pplev(ngrid,nlay+1) ! levels pressure REAL pphi(ngrid,nlay) ! geopotential REAL zpspsk(ngrid,nlay) ! Exner function ! outputs: ! -------- INTEGER lmin(ngrid) ! plume base level (first unstable level) INTEGER lalim(ngrid) ! higher alimentation level INTEGER lmix(ngrid) ! maximum vertical speed level INTEGER lmix_bis(ngrid) ! maximum vertical speed level (modified) REAL alim_star(ngrid,nlay) ! normalized alimentation REAL alim_star_tot(ngrid) ! integrated alimentation REAL f0(ngrid) ! previous time step mass flux norm REAL detr_star(ngrid,nlay) ! normalized detrainment REAL entr_star(ngrid,nlay) ! normalized entrainment REAL f_star(ngrid,nlay+1) ! normalized mass flux REAL ztva(ngrid,nlay) ! TRPV plume (after mixing) REAL ztva_est(ngrid,nlay) ! TRPV plume (before mixing) REAL ztla(ngrid,nlay) ! TP plume REAL zqla(ngrid,nlay) ! ql plume (after mixing) REAL zqta(ngrid,nlay) ! qt plume REAL zha(ngrid,nlay) ! TRPV plume REAL w_est(ngrid,nlay+1) ! updraft square vertical speed (before mixing) REAL zw2(ngrid,nlay+1) ! updraft square vertical speed (after mixing) REAL zqsatth(ngrid,nlay) ! saturation vapor pressure (after mixing) ! local: ! ------ INTEGER ig, l, k INTEGER lt INTEGER lm REAL zqla_est(ngrid,nlay) ! ql plume (before mixing) REAL zta_est(ngrid,nlay) ! TR plume (before mixing) REAL zbuoy(ngrid,nlay) ! plume buoyancy REAL zbuoyjam(ngrid,nlay) ! plume buoyancy (modified) REAL ztemp(ngrid) ! temperature for saturation vapor pressure computation in plume REAL zqsat(ngrid) ! saturation vapor pressure (before mixing) REAL zdz ! layers height REAL ztv2(ngrid,nlay) ! ztv + d_temp * Dirac(l=lmin) REAL zalpha ! REAL zdqt(ngrid,nlay) ! REAL zbetalpha ! REAL zdw2 ! REAL zdw2bis ! REAL zw2fact ! REAL zw2factbis ! REAL zw2m ! REAL zdzbis ! REAL coefzlmel ! REAL zdz2 ! REAL zdz3 ! REAL lmel ! REAL zlmel ! REAL zlmelup ! REAL zlmeldwn ! REAL zlt ! REAL zltdwn ! REAL zltup ! useless here REAL psat ! dummy argument for Psat_water() LOGICAL active(ngrid) ! if the plume is active at ig,l (speed and incoming mass flux > 0 or l=lmin) LOGICAL activetmp(ngrid) ! if the plus is active at ig,l (active=true and outgoing mass flux > 0) LOGICAL, SAVE :: first = .true. ! if it is the first time step !$OMP THREADPRIVATE(first) !============================================================================== ! Initialization !============================================================================== zbetalpha = betalpha / (1. + betalpha) ztva(:,:) = ztv(:,:) ! ztva is set to the virtual potential temperature without latent heat release ztva_est(:,:) = ztva(:,:) ! ztva_est is set to the virtual potential temperature without latent heat release ztla(:,:) = zthl(:,:) ! ztla is set to the potential temperature zqta(:,:) = po(:,:) ! zqta is set to qt zqla(:,:) = 0. ! zqla is set to ql zqla_est(:,:) = 0. ! zqla_est is set to ql zha(:,:) = ztva(:,:) ! zha is set to the plume virtual potential temperature without latent heat release zqsat(:) = 0. zqsatth(:,:) = 0. w_est(:,:) = 0. zw2(:,:) = 0. zbuoy(:,:) = 0. zbuoyjam(:,:) = 0. f_star(:,:) = 0. detr_star(:,:) = 0. entr_star(:,:) = 0. alim_star(:,:) = 0. alim_star_tot(:) = 0. lmix(:) = 1 lmix_bis(:) = 2 lalim(:) = 1 lmin(:) = linf ztv2(:,:) = ztv(:,:) ztv2(:,linf) = ztv(:,linf) + d_temp !============================================================================== ! 0. Calcul de l'alimentation !============================================================================== !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ! AB : Convective plumes can go off from every layer above the linf-th and ! where pressure is lesser than pres_limit (cf. thermcell_plume). ! The second constraint is added to avoid the parametrization occurs too ! high when the low atmosphere is stable. ! However, once there is a triggered plume, it can rise as high as its ! velocity allows it (it can overshoot). !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ DO ig=1,ngrid active(ig) = .false. l = linf DO WHILE ((.not.active(ig)) .and. pplev(ig,l+1).gt.pres_limit .and. l.lt.nlay) IF (ztv2(ig,l).gt.ztv2(ig,l+1)) THEN active(ig) = .true. lmin(ig) = l ENDIF l = l + 1 ENDDO ENDDO !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ! AB : On pourrait n'appeler thermcell_alim que si la plume est active !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ CALL thermcell_alim(ngrid,nlay,ztv2,zlev,alim_star,lalim,lmin) !============================================================================== ! 1. Calcul dans la premiere couche !============================================================================== DO ig=1,ngrid IF (active(ig)) THEN !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ! AB : plume takes the environment features for every layer below lmin. !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ DO l=1,lmin(ig) ztla(ig,l) = zthl(ig,l) zqta(ig,l) = po(ig,l) zqla(ig,l) = zl(ig,l) ENDDO l = lmin(ig) f_star(ig,l+1) = alim_star(ig,l) zw2(ig,l+1) = 2. * RG * (zlev(ig,l+1) - zlev(ig,l)) & & * (ztv2(ig,l) - ztv2(ig,l+1)) / ztv2(ig,l+1) w_est(ig,l+1) = zw2(ig,l+1) ENDIF ENDDO !============================================================================== ! 2. Boucle de calcul de la vitesse verticale dans le thermique !============================================================================== DO l=2,nlay-1 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ! AB : we decide here if the plume is still active or not. When the plume's ! first level is reached, we set active to "true". Otherwise, it is given ! by zw2, f_star, alim_star and entr_star. !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ DO ig=1,ngrid IF (l==lmin(ig)+1) THEN active(ig) = .true. ENDIF active(ig) = active(ig) & & .and. zw2(ig,l)>1.e-10 & & .and. f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l)>1.e-10 ENDDO ztemp(:) = zpspsk(:,l) * ztla(:,l-1) DO ig=1,ngrid CALL Psat_water(ztemp(ig), pplev(ig,l), psat, zqsat(ig)) ENDDO !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ! AB : we compute thermodynamical values and speed in the plume in the layer l ! without mixing with environment. !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ DO ig=1,ngrid IF (active(ig)) THEN zqla_est(ig,l) = max(0.,zqta(ig,l-1)-zqsat(ig)) ! zqla_est set to ql plume ztva_est(ig,l) = ztla(ig,l-1)*zpspsk(ig,l)+RLvCp*zqla_est(ig,l) ! ztva_est set to TR plume zta_est(ig,l) = ztva_est(ig,l) ! zta_est set to TR plume ztva_est(ig,l) = ztva_est(ig,l)/zpspsk(ig,l) ! ztva_est set to TRP plume ztva_est(ig,l) = ztva_est(ig,l)*(1.+RETV*(zqta(ig,l-1) & ! ztva_est set to TRPV plume & - zqla_est(ig,l))-zqla_est(ig,l)) zbuoy(ig,l) = RG * (ztva_est(ig,l)-ztv(ig,l)) / ztv(ig,l) zdz = zlev(ig,l+1) - zlev(ig,l) !============================================================================== ! 3. Calcul de la flotabilite modifiee par melange avec l'air au dessus !============================================================================== lmel = fact_thermals_ed_dz * zlev(ig,l) zlmel = zlev(ig,l) + lmel lt = l + 1 zlt = zlev(ig,lt) zdz2 = zlev(ig,lt) - zlev(ig,l) DO while (lmel.gt.zdz2) lt = lt + 1 zlt = zlev(ig,lt) zdz2 = zlev(ig,lt) - zlev(ig,l) ENDDO ! IF (lt-l.gt.1) THEN ! print *, 'WARNING: lt is greater than l+1!' ! print *, 'l,lt', l, lt ! ENDIF zdz3 = zlev(ig,lt+1) - zlt zltdwn = zlev(ig,lt) - zdz3 / 2 zlmelup = zlmel + (zdz / 2) coefzlmel = Min(1.,(zlmelup - zltdwn) / zdz) zbuoyjam(ig,l) = 1.* RG * (coefzlmel * & & (ztva_est(ig,l) - ztv(ig,lt)) / ztv(ig,lt) & & + (1. - coefzlmel) * & & (ztva_est(ig,l) - ztv(ig,lt-1)) / ztv(ig,lt-1)) & & + 0. * zbuoy(ig,l) !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ! AB : initial formulae !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ! zw2fact = fact_epsilon * 2. * zdz / (1. + betalpha) ! zdw2 = afact * zbuoy(ig,l) / fact_epsilon ! zdw2bis = afact * zbuoy(ig,l-1) / fact_epsilon ! w_est(ig,l+1) = Max(0.0001,exp(-zw2fact)*(w_est(ig,l)-zdw2)+zdw2) ! w_est(ig,l+1) = Max(0.0001,exp(-zw2fact)*(w_est(ig,l)-zdw2bis)+zdw2) !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ! AB : own derivation for w_est (Rio 2010 formula with e=d=0) !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ zw2fact = 2. * fact_epsilon * zdz zdw2 = 2. * afact * zbuoy(ig,l) * zdz w_est(ig,l+1) = Max(0., exp(-zw2fact) * w_est(ig,l) + zdw2) ! IF (w_est(ig,l+1).le.0.) THEN ! print *, 'WARNING: w_est is negative!' ! print *, 'l,w_est', l+1, w_est(ig,l+1) ! ENDIF ENDIF ENDDO !============================================================================== ! 4. Calcul de l'entrainement et du detrainement !============================================================================== DO ig=1,ngrid IF (active(ig)) THEN zdz = zlev(ig,l+1) - zlev(ig,l) !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ! AB : The next test is added to avoid divisions by zero when w_est vanishes. ! Indeed, entr and detr computed here are of no importance because w_est ! <= 0 means it will be the last layer reached by the plume and then they ! will be reset in thermcell_flux. !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ IF (w_est(ig,l+1).eq.0.) THEN zw2m = 1. zalpha = 0. ELSE zw2m = w_est(ig,l+1) zalpha = f0(ig) * f_star(ig,l) / sqrt(w_est(ig,l+1)) / rhobarz(ig,l) ENDIF !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ! AB : The next test is added to avoid a division by zero if there is no water ! in the environment. ! In the case where there is no water in the env. but water in the plume ! (ascending from depth) we set the effect on detrainment equal to zero ! but at the next time step, po will be positive thanks to the mixing and ! then the physical effect of the water gradient will be taken on board. !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ IF (po(ig,l).lt.1.e-6) THEN ! print *, 'WARNING: po=0 in layer',l,'!' ! print *, 'po,zqta', po(ig,l), zqta(ig,l-1) zdqt(ig,l) = 0.0 ELSE zdqt(ig,l) = max(zqta(ig,l-1)-po(ig,l),0.) / po(ig,l) ENDIF !------------------------------------------------------------------------------ ! Detrainment !------------------------------------------------------------------------------ detr_star(ig,l) = f_star(ig,l) * zdz * ( & & mix0 * 0.1 / (zalpha + 0.001) & & + MAX(detr_min, & & -afact * zbetalpha * zbuoyjam(ig,l) / zw2m & & + detr_q_coef*(zdqt(ig,l)/zw2m)**detr_q_power) ) ! IF (detr_star(ig,l).lt.0.) THEN ! print *, 'WARNING: detrainment is negative!' ! print *, 'l,detr', l, detr_star(ig,l) ! ENDIF !------------------------------------------------------------------------------ ! Entrainment !------------------------------------------------------------------------------ entr_star(ig,l) = f_star(ig,l) * zdz * ( & & mix0 * 0.1 / (zalpha+0.001) & & + MAX(entr_min, & & zbetalpha * afact * zbuoyjam(ig,l) / zw2m & & - zbetalpha * fact_epsilon) ) ! IF (entr_star(ig,l).lt.0.) THEN ! print *, 'WARNING: entrainment is negative!' ! print *, 'l,entr', l, entr_star(ig,l) ! ENDIF !------------------------------------------------------------------------------ ! Alimentation and entrainment !------------------------------------------------------------------------------ IF (l.lt.lalim(ig)) THEN alim_star(ig,l) = max(alim_star(ig,l),entr_star(ig,l)) entr_star(ig,l) = 0. ENDIF !------------------------------------------------------------------------------ ! Mass flux !------------------------------------------------------------------------------ f_star(ig,l+1) = f_star(ig,l) + alim_star(ig,l) & & + entr_star(ig,l) - detr_star(ig,l) ! IF (f_star(ig,l+1).le.0.) THEN ! print *, 'WARNING: mass flux is negative!' ! print *, 'l,f_star', l+1, f_star(ig,l+1) ! ENDIF ENDIF ENDDO !============================================================================== ! 5. Calcul de la vitesse verticale en melangeant Tl et qt du thermique !============================================================================== activetmp(:) = active(:) .and. f_star(:,l+1)>1.e-10 !------------------------------------------------------------------------------ ! Calcul du melange avec l'environnement !------------------------------------------------------------------------------ DO ig=1,ngrid IF (activetmp(ig)) THEN ztla(ig,l) = (f_star(ig,l) * ztla(ig,l-1) & ! ztla is set to TP in plume (mixed) & + (alim_star(ig,l) + entr_star(ig,l)) * zthl(ig,l)) & & / (f_star(ig,l+1) + detr_star(ig,l)) zqta(ig,l) = (f_star(ig,l) * zqta(ig,l-1) + & ! zqta is set to qt in plume (mixed) & + (alim_star(ig,l) + entr_star(ig,l)) * po(ig,l)) & & / (f_star(ig,l+1) + detr_star(ig,l)) ENDIF ENDDO ztemp(:) = zpspsk(:,l) * ztla(:,l) DO ig=1,ngrid IF (activetmp(ig)) THEN CALL Psat_water(ztemp(ig), pplev(ig,l), psat, zqsatth(ig,l)) ENDIF ENDDO !------------------------------------------------------------------------------ ! Calcul de la vitesse verticale zw2 apres le melange !------------------------------------------------------------------------------ DO ig=1,ngrid IF (activetmp(ig)) THEN zqla(ig,l) = max(0.,zqta(ig,l)-zqsatth(ig,l)) ! zqla is set to ql plume (mixed) ztva(ig,l) = ztla(ig,l) * zpspsk(ig,l)+RLvCp*zqla(ig,l) ! ztva is set to TR plume (mixed) ztva(ig,l) = ztva(ig,l) / zpspsk(ig,l) ! ztva is set to TRP plume (mixed) zha(ig,l) = ztva(ig,l) ! zha is set to TRP plume (mixed) ztva(ig,l) = ztva(ig,l) * (1. + RETV*(zqta(ig,l)-zqla(ig,l)) & ! ztva is set to TRPV plume (mixed) & - zqla(ig,l)) zbuoy(ig,l) = RG * (ztva(ig,l) - ztv(ig,l)) / ztv(ig,l) zdz = zlev(ig,l+1) - zlev(ig,l) !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ! AB : initial formula !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ! zw2fact = fact_epsilon * 2. * zdz / (1. + betalpha) ! zdw2 = afact * zbuoy(ig,l) / fact_epsilon ! zdw2bis = afact * zbuoy(ig,l-1) / fact_epsilon ! zw2(ig,l+1) = Max(0.0001,exp(-zw2fact)*(zw2(ig,l)-zdw2)+zdw2) !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ! AB : own derivation for zw2 (Rio 2010 formula) !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ zw2fact = 2. * (fact_epsilon * zdz + entr_star(ig,l) / f_star(ig,l)) zdw2 = 2. * afact * zbuoy(ig,l) * zdz zw2(ig,l+1) = Max(0., exp(-zw2fact) * zw2(ig,l) + zdw2) ! IF (zw2(ig,l+1).le.0.) THEN ! print *, 'WARNING: zw2 is negative!' ! print *, 'l,zw2', l+1, zw2(ig,l+1) ! ENDIF ENDIF ENDDO ENDDO !============================================================================== ! 6. New computation of alim_star_tot !============================================================================== DO ig=1,ngrid alim_star_tot(ig) = 0. ENDDO DO ig=1,ngrid DO l=1,lalim(ig)-1 alim_star_tot(ig) = alim_star_tot(ig) + alim_star(ig,l) ENDDO ENDDO RETURN END