MODULE lmdz_thermcell_plume_5B CONTAINS SUBROUTINE thermcell_plume_5B(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,csc,ztva, & & ztla,zqla,zqta,zha,zw2,w_est,ztva_est,zqsatth,lmix,lmix_bis,linter & & ,lev_out,lunout1,igout) !& ,lev_out,lunout1,igout,zbuoy,zbuoyjam) !-------------------------------------------------------------------------- !thermcell_plume: calcule les valeurs de qt, thetal et w dans l ascendance ! Version conforme a l'article de Rio et al. 2010. ! Code ecrit par Catherine Rio, Arnaud Jam et Frederic Hourdin !-------------------------------------------------------------------------- USE lmdz_thermcell_ini, ONLY: prt_level,fact_thermals_ed_dz,iflag_thermals_ed,RLvCP,RETV,RG USE lmdz_thermcell_qsat, ONLY : thermcell_qsat IMPLICIT NONE INTEGER itap INTEGER lunout1,igout INTEGER ngrid,nlay REAL ptimestep REAL ztv(ngrid,nlay) REAL zthl(ngrid,nlay) REAL, INTENT(IN) :: po(ngrid,nlay) REAL zl(ngrid,nlay) REAL rhobarz(ngrid,nlay) REAL zlev(ngrid,nlay+1) REAL pplev(ngrid,nlay+1) REAL pphi(ngrid,nlay) REAL zpspsk(ngrid,nlay) REAL alim_star(ngrid,nlay) REAL f0(ngrid) INTEGER lalim(ngrid) integer lev_out ! niveau pour les print integer nbpb real alim_star_tot(ngrid) REAL ztva(ngrid,nlay) REAL ztla(ngrid,nlay) REAL zqla(ngrid,nlay) REAL zqta(ngrid,nlay) REAL zha(ngrid,nlay) REAL detr_star(ngrid,nlay) REAL coefc REAL entr_star(ngrid,nlay) REAL detr(ngrid,nlay) REAL entr(ngrid,nlay) REAL csc(ngrid,nlay) REAL zw2(ngrid,nlay+1) REAL w_est(ngrid,nlay+1) REAL f_star(ngrid,nlay+1) REAL wa_moy(ngrid,nlay+1) REAL ztva_est(ngrid,nlay) REAL zqla_est(ngrid,nlay) REAL zqsatth(ngrid,nlay) REAL zta_est(ngrid,nlay) REAL zbuoyjam(ngrid,nlay) REAL ztemp(ngrid),zqsat(ngrid) REAL zdw2 REAL zw2modif REAL zw2fact REAL zeps(ngrid,nlay) REAL linter(ngrid) INTEGER lmix(ngrid) INTEGER lmix_bis(ngrid) REAL wmaxa(ngrid) INTEGER ig,l,k real zdz,zbuoy(ngrid,nlay),zalpha,gamma(ngrid,nlay),zdqt(ngrid,nlay),zw2m real zbuoybis real zcor,zdelta,zcvm5,qlbef,zdz2 real betalpha,zbetalpha real eps, afact logical Zsat LOGICAL active(ngrid),activetmp(ngrid) REAL fact_gamma,fact_epsilon,fact_gamma2,fact_epsilon2 REAL c2(ngrid,nlay) Zsat=.false. ! Initialisation fact_epsilon=0.002 betalpha=0.9 afact=2./3. zbetalpha=betalpha/(1.+betalpha) ! Initialisations des variables reeles if (1==1) then ztva(:,:)=ztv(:,:) ztva_est(:,:)=ztva(:,:) ztla(:,:)=zthl(:,:) zqta(:,:)=po(:,:) zha(:,:) = ztva(:,:) else ztva(:,:)=0. ztva_est(:,:)=0. ztla(:,:)=0. zqta(:,:)=0. zha(:,:) =0. endif zqla_est(:,:)=0. zqsatth(:,:)=0. zqla(:,:)=0. detr_star(:,:)=0. entr_star(:,:)=0. alim_star(:,:)=0. alim_star_tot(:)=0. csc(:,:)=0. detr(:,:)=0. entr(:,:)=0. zw2(:,:)=0. zbuoy(:,:)=0. zbuoyjam(:,:)=0. gamma(:,:)=0. zeps(:,:)=0. w_est(:,:)=0. f_star(:,:)=0. wa_moy(:,:)=0. linter(:)=1. ! linter(:)=1. ! Initialisation des variables entieres lmix(:)=1 lmix_bis(:)=2 wmaxa(:)=0. lalim(:)=1 !------------------------------------------------------------------------- ! On ne considere comme actif que les colonnes dont les deux premieres ! couches sont instables. !------------------------------------------------------------------------- active(:)=ztv(:,1)>ztv(:,2) !------------------------------------------------------------------------- ! Definition de l'alimentation !------------------------------------------------------------------------- do l=1,nlay-1 do ig=1,ngrid if (ztv(ig,l)> ztv(ig,l+1) .and. ztv(ig,1)>=ztv(ig,l) ) then alim_star(ig,l)=MAX((ztv(ig,l)-ztv(ig,l+1)),0.) & & *sqrt(zlev(ig,l+1)) lalim(ig)=l+1 alim_star_tot(ig)=alim_star_tot(ig)+alim_star(ig,l) endif enddo enddo do l=1,nlay do ig=1,ngrid if (alim_star_tot(ig) > 1.e-10 ) then alim_star(ig,l)=alim_star(ig,l)/alim_star_tot(ig) endif enddo enddo alim_star_tot(:)=1. !------------------------------------------------------------------------------ ! Calcul dans la premiere couche ! On decide dans cette version que le thermique n'est actif que si la premiere ! couche est instable. ! Pourrait etre change si on veut que le thermiques puisse se d??clencher ! dans une couche l>1 !------------------------------------------------------------------------------ do ig=1,ngrid ! Le panache va prendre au debut les caracteristiques de l'air contenu ! dans cette couche. if (active(ig)) then ztla(ig,1)=zthl(ig,1) zqta(ig,1)=po(ig,1) zqla(ig,1)=zl(ig,1) !cr: attention, prise en compte de f*(1)=1 f_star(ig,2)=alim_star(ig,1) zw2(ig,2)=2.*RG*(ztv(ig,1)-ztv(ig,2))/ztv(ig,2) & & *(zlev(ig,2)-zlev(ig,1)) & & *0.4*pphi(ig,1)/(pphi(ig,2)-pphi(ig,1)) w_est(ig,2)=zw2(ig,2) endif enddo ! !============================================================================== !boucle de calcul de la vitesse verticale dans le thermique !============================================================================== do l=2,nlay-1 !============================================================================== ! On decide si le thermique est encore actif ou non ! AFaire : Il faut sans doute ajouter entr_star a alim_star dans ce test do ig=1,ngrid active(ig)=active(ig) & & .and. zw2(ig,l)>1.e-10 & & .and. f_star(ig,l)+alim_star(ig,l)>1.e-10 enddo !--------------------------------------------------------------------------- ! calcul des proprietes thermodynamiques et de la vitesse de la couche l ! sans tenir compte du detrainement et de l'entrainement dans cette ! couche ! C'est a dire qu'on suppose ! ztla(l)=ztla(l-1) et zqta(l)=zqta(l-1) ! Ici encore, on doit pouvoir ajouter entr_star (qui peut etre calculer ! avant) a l'alimentation pour avoir un calcul plus propre !--------------------------------------------------------------------------- ztemp(:)=zpspsk(:,l)*ztla(:,l-1) call thermcell_qsat(ngrid, 1, active,pplev(:,l),ztemp,zqta(:,l-1),zqsat(:)) do ig=1,ngrid ! print*,'active',active(ig),ig,l if(active(ig)) then zqla_est(ig,l)=max(0.,zqta(ig,l-1)-zqsat(ig)) ztva_est(ig,l) = ztla(ig,l-1)*zpspsk(ig,l)+RLvCp*zqla_est(ig,l) zta_est(ig,l)=ztva_est(ig,l) ztva_est(ig,l) = ztva_est(ig,l)/zpspsk(ig,l) ztva_est(ig,l) = ztva_est(ig,l)*(1.+RETV*(zqta(ig,l-1) & & -zqla_est(ig,l))-zqla_est(ig,l)) !------------------------------------------------ !AJAM:nouveau calcul de w? !------------------------------------------------ zdz=zlev(ig,l+1)-zlev(ig,l) zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l) zw2fact=fact_epsilon*2.*zdz/(1.+betalpha) zdw2=(afact)*zbuoy(ig,l)/(fact_epsilon) w_est(ig,l+1)=Max(0.0001,exp(-zw2fact)*(w_est(ig,l)-zdw2)+zdw2) if (w_est(ig,l+1).lt.0.) then w_est(ig,l+1)=zw2(ig,l) endif endif enddo !------------------------------------------------- !calcul des taux d'entrainement et de detrainement !------------------------------------------------- do ig=1,ngrid if (active(ig)) then zw2m=max(0.5*(w_est(ig,l)+w_est(ig,l+1)),0.1) zw2m=w_est(ig,l+1) zdz=zlev(ig,l+1)-zlev(ig,l) zbuoy(ig,l)=RG*(ztva_est(ig,l)-ztv(ig,l))/ztv(ig,l) ! zbuoybis=zbuoy(ig,l)+RG*0.1/300. zbuoybis=zbuoy(ig,l) zalpha=f0(ig)*f_star(ig,l)/sqrt(w_est(ig,l+1))/rhobarz(ig,l) zdqt(ig,l)=max(zqta(ig,l-1)-po(ig,l),0.)/po(ig,l) entr_star(ig,l)=f_star(ig,l)*zdz* zbetalpha*MAX(0., & & afact*zbuoybis/zw2m - fact_epsilon ) detr_star(ig,l)=f_star(ig,l)*zdz & & *MAX(1.e-3, -afact*zbetalpha*zbuoy(ig,l)/zw2m & & + 0.012*(zdqt(ig,l)/zw2m)**0.5 ) ! En dessous de lalim, on prend le max de alim_star et entr_star pour ! alim_star et 0 sinon 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 ! Calcul du flux montant normalise f_star(ig,l+1)=f_star(ig,l)+alim_star(ig,l)+entr_star(ig,l) & & -detr_star(ig,l) endif enddo !---------------------------------------------------------------------------- !calcul de la vitesse verticale en melangeant Tl et qt du thermique !--------------------------------------------------------------------------- activetmp(:)=active(:) .and. f_star(:,l+1)>1.e-10 do ig=1,ngrid if (activetmp(ig)) then Zsat=.false. ztla(ig,l)=(f_star(ig,l)*ztla(ig,l-1)+ & & (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)+ & & (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) call thermcell_qsat(ngrid, 1, activetmp,pplev(:,l),ztemp,zqta(:,l),zqsatth(:,l)) do ig=1,ngrid if (activetmp(ig)) then ! on ecrit de maniere conservative (sat ou non) ! T = Tl +Lv/Cp ql zqla(ig,l)=max(0.,zqta(ig,l)-zqsatth(ig,l)) ztva(ig,l) = ztla(ig,l)*zpspsk(ig,l)+RLvCp*zqla(ig,l) ztva(ig,l) = ztva(ig,l)/zpspsk(ig,l) !on rajoute le calcul de zha pour diagnostiques (temp potentielle) zha(ig,l) = ztva(ig,l) ztva(ig,l) = ztva(ig,l)*(1.+RETV*(zqta(ig,l) & & -zqla(ig,l))-zqla(ig,l)) zbuoy(ig,l)=RG*(ztva(ig,l)-ztv(ig,l))/ztv(ig,l) zdz=zlev(ig,l+1)-zlev(ig,l) zeps(ig,l)=(entr_star(ig,l)+alim_star(ig,l))/(f_star(ig,l)*zdz) zw2fact=fact_epsilon*2.*zdz/(1.+betalpha) zdw2=afact*zbuoy(ig,l)/(fact_epsilon) zw2(ig,l+1)=Max(0.0001,exp(-zw2fact)*(zw2(ig,l)-zdw2)+zdw2) endif enddo if (prt_level.ge.20) print*,'coucou calcul detr 460: ig, l',ig, l ! !--------------------------------------------------------------------------- !initialisations pour le calcul de la hauteur du thermique, de l'inversion et de la vitesse verticale max !--------------------------------------------------------------------------- nbpb=0 do ig=1,ngrid if (zw2(ig,l+1)>0. .and. zw2(ig,l+1).lt.1.e-10) then ! stop'On tombe sur le cas particulier de thermcell_dry' ! print*,'On tombe sur le cas particulier de thermcell_plume' nbpb=nbpb+1 zw2(ig,l+1)=0. linter(ig)=l+1 endif if (zw2(ig,l+1).lt.0.) then linter(ig)=(l*(zw2(ig,l+1)-zw2(ig,l)) & & -zw2(ig,l))/(zw2(ig,l+1)-zw2(ig,l)) zw2(ig,l+1)=0. elseif (f_star(ig,l+1).lt.0.) then linter(ig)=(l*(f_star(ig,l+1)-f_star(ig,l)) & & -f_star(ig,l))/(f_star(ig,l+1)-f_star(ig,l)) ! print*,"linter plume", linter(ig) zw2(ig,l+1)=0. endif wa_moy(ig,l+1)=sqrt(zw2(ig,l+1)) if (wa_moy(ig,l+1).gt.wmaxa(ig)) then ! lmix est le niveau de la couche ou w (wa_moy) est maximum !on rajoute le calcul de lmix_bis if (zqla(ig,l).lt.1.e-10) then lmix_bis(ig)=l+1 endif lmix(ig)=l+1 wmaxa(ig)=wa_moy(ig,l+1) endif enddo if (nbpb>0) then print*,'WARNING on tombe ',nbpb,' x sur un pb pour l=',l,' dans thermcell_plume' endif !========================================================================= ! FIN DE LA BOUCLE VERTICALE enddo !========================================================================= !on recalcule 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 if (prt_level.ge.20) print*,'coucou calcul detr 470: ig, l', ig, l return END SUBROUTINE thermcell_plume_5B END MODULE lmdz_thermcell_plume_5B