4 SUBROUTINE top_bound(vcov,ucov,teta,masse,dt)
7 #include "dimensions.h"
53 #include "comdissipn.h"
59 real,
intent(inout) :: ucov(iip1,
jjp1,
llm)
60 real,
intent(inout) :: vcov(iip1,jjm,
llm)
61 real,
intent(inout) :: teta(iip1,
jjp1,
llm)
62 real,
intent(in) :: masse(iip1,
jjp1,
llm)
68 REAL massebx(iip1,
jjp1,
llm),masseby(iip1,jjm,
llm),zm
72 REAL,
SAVE :: rdamp(
llm)
73 real,
save :: lambda(
llm)
75 LOGICAL,
SAVE :: first=.
true.
98 rdamp(:)=1.-exp(-lambda(:)*dt)
100 write(
lunout,*)
'TOP_BOUND mode',mode_top_bound
101 write(
lunout,*)
'Sponge layer coefficients'
102 write(
lunout,*)
'p (Pa) z(km) tau(s) 1./tau (Hz)'
104 if (rdamp(l).ne.0.)
then
105 write(
lunout,
'(6(1pe12.4,1x))')
107 & 1./lambda(l),lambda(l)
113 CALL massbar(masse,massebx,masseby)
116 if (mode_top_bound.ge.2)
then
124 vzon(j,l)=vzon(j,l)+vcov(i,j,l)*masseby(i,j,l)
127 vzon(j,l)=vzon(j,l)/zm
136 uzon(j,l)=uzon(j,l)+massebx(i,j,l)*ucov(i,j,l)/
cu(i,j)
139 uzon(j,l)=uzon(j,l)/zm
148 if (mode_top_bound.ge.3)
then
154 tzon(j,l)=tzon(j,l)+teta(i,j,l)*masse(i,j,l)
157 tzon(j,l)=tzon(j,l)/zm
162 if (mode_top_bound.ge.1)
then
167 vcov(i,j,l)=vcov(i,j,l)
168 & -rdamp(l)*(vcov(i,j,l)-vzon(j,l))
177 ucov(i,j,l)=ucov(i,j,l)
178 & -rdamp(l)*(ucov(i,j,l)-
cu(i,j)*uzon(j,l))
184 if (mode_top_bound.ge.3)
then
189 teta(i,j,l)=teta(i,j,l)
190 & -rdamp(l)*(teta(i,j,l)-tzon(j,l))
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref dt_dice swup_dice vg_dice omega_dice tg_prof vg_profd w_profd omega_profd!do llm!print llm l llm
!$Id mode_top_bound COMMON comconstr omeg dissip_zref tau_top_bound
subroutine massbar(masse, massebx, masseby)
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
!$Id!Parameters for parameters that control the rate of approach!to quasi equilibrium noff nlm real tlcrit real entp real sigd real coeffs real dtmax real cu real betad real damp real delta COMMON cvparam nlm tlcrit sigd coeffs cu
c c zjulian c cym CALL iim cym klev iim
subroutine top_bound(vcov, ucov, teta, masse, dt)
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout