1 SUBROUTINE calcratqs(klon,klev,prt_level,lunout, &
3 ratqsbas,ratqshaut,tau_ratqs,fact_cldcon, &
4 ptconv,ptconvth,clwcon0th, rnebcon0th, &
20 integer,
intent(in) :: klon,klev,prt_level,lunout
21 integer,
intent(in) :: iflag_con,iflag_cld_th,iflag_ratqs
22 real,
intent(in) :: pdtphys,ratqsbas,ratqshaut,fact_cldcon,tau_ratqs
23 real,
dimension(klon,klev+1),
intent(in) :: paprs
24 real,
dimension(klon,klev),
intent(in) :: pplay,q_seri,zqsat,fm_therm
25 logical,
dimension(klon,klev),
intent(in) :: ptconv
26 real,
dimension(klon,klev),
intent(in) :: rnebcon0th,clwcon0th
29 real,
dimension(klon,klev),
intent(inout) :: ratqs,ratqsc
30 logical,
dimension(klon,klev),
intent(inout) :: ptconvth
34 real,
dimension(klon,klev) :: ratqss
35 real facteur,zfratqs1,zfratqs2
45 if (iflag_cld_th.eq.1)
then
49 ratqsc(i,k)=ratqsbas &
50 +fact_cldcon*(q_seri(i,1)-q_seri(i,k))/q_seri(i,k)
60 else if (iflag_cld_th.eq.4)
then
63 if(prt_level.ge.9) print*,
'avant clouds_gno thermique'
65 (klon,klev,q_seri,zqsat,clwcon0th,ptconvth,ratqsc,rnebcon0th)
66 if(prt_level.ge.9) print*,
' CLOUDS_GNO OK'
73 if (iflag_ratqs.eq.0)
then
78 ratqss(i,k)=ratqsbas+(ratqshaut-ratqsbas)* &
79 min((paprs(i,1)-pplay(i,k))/(paprs(i,1)-30000.),1.)
90 else if (iflag_ratqs.eq.1)
then
94 if (pplay(i,k).ge.60000.)
then
96 else if ((pplay(i,k).ge.30000.).and.(pplay(i,k).lt.60000.))
then
97 ratqss(i,k)=ratqsbas+(ratqshaut-ratqsbas)*(60000.-pplay(i,k))/(60000.-30000.)
104 else if (iflag_ratqs.eq.2)
then
108 if (pplay(i,k).ge.60000.)
then
109 ratqss(i,k)=ratqsbas*(paprs(i,1)-pplay(i,k))/(paprs(i,1)-60000.)
110 else if ((pplay(i,k).ge.30000.).and.(pplay(i,k).lt.60000.))
then
111 ratqss(i,k)=ratqsbas+(ratqshaut-ratqsbas)*(60000.-pplay(i,k))/(60000.-30000.)
113 ratqss(i,k)=ratqshaut
118 else if (iflag_ratqs==3)
then
120 ratqss(:,k)=ratqsbas+(ratqshaut-ratqsbas) &
121 *min( ((paprs(:,1)-pplay(:,k))/70000.)**2 , 1. )
124 else if (iflag_ratqs==4)
then
126 ratqss(:,k)=ratqsbas+0.5*(ratqshaut-ratqsbas) &
127 *( tanh( (50000.-pplay(:,k))/20000.) + 1.)
138 if (iflag_cld_th.eq.1 .or.iflag_cld_th.eq.2.or.iflag_cld_th.eq.4)
then
145 if ((fm_therm(i,k).gt.1.e-10))
then
146 ratqsc(i,k)=sqrt(ratqsc(i,k)**2+0.05**2)
152 if(prt_level.ge.9)
write(lunout,*)
'PHYLMD NOUVEAU TAU_RATQS ',tau_ratqs
154 if (tau_ratqs>1.e-10)
then
155 facteur=exp(-pdtphys/tau_ratqs)
159 ratqs(:,:)=ratqsc(:,:)*(1.-facteur)+ratqs(:,:)*facteur
166 ratqs(:,:)=max(ratqs(:,:),ratqss(:,:))
167 else if (iflag_cld_th<=6)
then
169 ratqs(:,:)=ratqss(:,:)
171 zfratqs1=exp(-pdtphys/10800.)
172 zfratqs2=exp(-pdtphys/10800.)
175 if (ratqsc(i,k).gt.1.e-10)
then
176 ratqs(i,k)=ratqs(i,k)*zfratqs2+(iflag_cld_th/100.)*ratqsc(i,k)*(1.-zfratqs2)
178 ratqs(i,k)=min(ratqs(i,k)*zfratqs1+ratqss(i,k)*(1.-zfratqs1),0.5)
!$Id ok_orolf LOGICAL ok_limitvrai LOGICAL ok_all_xml INTEGER iflag_con
subroutine clouds_gno(klon, nd, r, rs, qsub, ptconv, ratqsc, cldf)
!$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 pplay
!$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 &zphi geo500!IM on interpole a chaque pas de temps le paprs
!$Id zjulian!correction pour l heure initiale!jyg!jyg CALL pdtphys
subroutine calcratqs(klon, klev, prt_level, lunout, iflag_ratqs, iflag_con, iflag_cld_th, pdtphys, ratqsbas, ratqshaut, tau_ratqs, fact_cldcon, ptconv, ptconvth, clwcon0th, rnebcon0th, paprs, pplay, q_seri, zqsat, fm_therm, ratqs, ratqsc)