/[lmdze]/trunk/Sources/phylmd/coefkz.f
ViewVC logotype

Annotation of /trunk/Sources/phylmd/coefkz.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 12 - (hide annotations)
Mon Jul 21 16:05:07 2008 UTC (15 years, 9 months ago) by guez
Original Path: trunk/libf/phylmd/coefkz.f
File size: 10247 byte(s)
-- Minor modification of input/output:

Created procedure "read_logic". Variables of module "logic" are read
by "read_logic" instead of "conf_gcm". Variable "offline" of module
"conf_gcm" is read from namelist instead of "*.def".

Deleted arguments "dtime", "co2_ppm_etat0", "solaire_etat0",
"tabcntr0" and local variables "radpas", "tab_cntrl" of
"phyetat0". "phyetat0" does not read "controle" in "startphy.nc" any
longer. "phyetat0" now reads global attribute "itau_phy" from
"startphy.nc". "phyredem" does not create variable "controle" in
"startphy.nc" any longer. "phyredem" now writes global attribute
"itau_phy" of "startphy.nc". Deleted argument "tabcntr0" of
"printflag". Removed diagnostic messages written by "printflag" for
comparison of the variable "controle" of "startphy.nc" and the
variables read from "*.def" or namelist input.

-- Removing unwanted functionality:

Removed variable "lunout" from module "iniprint", replaced everywhere
by standard output.

Removed case "ocean == 'couple'" in "clmain", "interfsurf_hq" and
"physiq". Removed procedure "interfoce_cpl".

-- Should not change anything at run time:

Automated creation of graphs in documentation. More documentation on
input files.

Converted Fortran files to free format: "phyredem.f90", "printflag.f90".

Split module "clesphy" into "clesphys" and "clesphys2".

Removed variables "conser", "leapf", "forward", "apphys", "apdiss" and
"statcl" from module "logic". Added arguments "conser" to "advect",
"leapf" to "integrd". Added local variables "forward", "leapf",
"apphys", "conser", "apdiss" in "leapfrog".

Added intent attributes.

Deleted arguments "dtime" of "phyredem", "pdtime" of "flxdtdq", "sh"
of "phytrac", "dt" of "yamada".

Deleted local variables "dtime", "co2_ppm_etat0", "solaire_etat0",
"length", "tabcntr0" in "physiq". Replaced all references to "dtime"
by references to "pdtphys".

1 guez 3 SUBROUTINE coefkz(nsrf, knon, paprs, pplay,
2     cIM 261103
3     . ksta, ksta_ter,
4     cIM 261103
5     . ts, rugos,
6     . u,v,t,q,
7     . qsurf,
8     . pcfm, pcfh)
9     use dimens_m
10     use indicesol
11     use dimphy
12     use iniprint
13     use YOMCST
14     use yoethf
15     use fcttre
16     use conf_phys_m
17     IMPLICIT none
18     c======================================================================
19     c Auteur(s) F. Hourdin, M. Forichon, Z.X. Li (LMD/CNRS) date: 19930922
20     c (une version strictement identique a l'ancien modele)
21     c Objet: calculer le coefficient du frottement du sol (Cdrag) et les
22     c coefficients d'echange turbulent dans l'atmosphere.
23     c Arguments:
24     c nsrf-----input-I- indicateur de la nature du sol
25     c knon-----input-I- nombre de points a traiter
26     c paprs----input-R- pression a chaque intercouche (en Pa)
27     c pplay----input-R- pression au milieu de chaque couche (en Pa)
28     c ts-------input-R- temperature du sol (en Kelvin)
29     c rugos----input-R- longeur de rugosite (en m)
30     c u--------input-R- vitesse u
31     c v--------input-R- vitesse v
32     c t--------input-R- temperature (K)
33     c q--------input-R- vapeur d'eau (kg/kg)
34     c
35     c itop-----output-I- numero de couche du sommet de la couche limite
36     c pcfm-----output-R- coefficients a calculer (vitesse)
37     c pcfh-----output-R- coefficients a calculer (chaleur et humidite)
38     c======================================================================
39     c
40     c Arguments:
41     c
42     INTEGER knon, nsrf
43     REAL ts(klon)
44     REAL paprs(klon,klev+1), pplay(klon,klev)
45     REAL u(klon,klev), v(klon,klev), t(klon,klev), q(klon,klev)
46     REAL rugos(klon)
47     c
48     REAL pcfm(klon,klev), pcfh(klon,klev)
49     INTEGER itop(klon)
50     c
51     c Quelques constantes et options:
52     c
53     REAL cepdu2, ckap, cb, cc, cd, clam
54     PARAMETER (cepdu2 =(0.1)**2)
55     PARAMETER (CKAP=0.4)
56     PARAMETER (cb=5.0)
57     PARAMETER (cc=5.0)
58     PARAMETER (cd=5.0)
59     PARAMETER (clam=160.0)
60     REAL ratqs ! largeur de distribution de vapeur d'eau
61     PARAMETER (ratqs=0.05)
62     LOGICAL richum ! utilise le nombre de Richardson humide
63     PARAMETER (richum=.TRUE.)
64     REAL ric ! nombre de Richardson critique
65     PARAMETER(ric=0.4)
66     REAL prandtl
67     PARAMETER (prandtl=0.4)
68     REAL kstable ! diffusion minimale (situation stable)
69     ! GKtest
70     ! PARAMETER (kstable=1.0e-10)
71     REAL ksta, ksta_ter
72     cIM: 261103 REAL kstable_ter, kstable_sinon
73     cIM: 211003 cf GK PARAMETER (kstable_ter = 1.0e-6)
74     cIM: 261103 PARAMETER (kstable_ter = 1.0e-8)
75     cIM: 261103 PARAMETER (kstable_ter = 1.0e-10)
76     cIM: 261103 PARAMETER (kstable_sinon = 1.0e-10)
77     ! fin GKtest
78     REAL mixlen ! constante controlant longueur de melange
79     PARAMETER (mixlen=35.0)
80     INTEGER isommet ! le sommet de la couche limite
81     PARAMETER (isommet=klev)
82     LOGICAL tvirtu ! calculer Ri d'une maniere plus performante
83     PARAMETER (tvirtu=.TRUE.)
84     LOGICAL opt_ec ! formule du Centre Europeen dans l'atmosphere
85     PARAMETER (opt_ec=.FALSE.)
86    
87     c
88     c Variables locales:
89     c
90     INTEGER i, k, kk !IM 120704
91     REAL zgeop(klon,klev)
92     REAL zmgeom(klon)
93     REAL zri(klon)
94     REAL zl2(klon)
95    
96     REAL u1(klon), v1(klon), t1(klon), q1(klon), z1(klon)
97     REAL pcfm1(klon), pcfh1(klon)
98     c
99     REAL zdphi, zdu2, ztvd, ztvu, zcdn
100     REAL zscf
101     REAL zt, zq, zdelta, zcvm5, zcor, zqs, zfr, zdqs
102     REAL z2geomf, zalh2, zalm2, zscfh, zscfm
103     REAL t_coup
104     PARAMETER (t_coup=273.15)
105     cIM
106     LOGICAL check
107     PARAMETER (check=.false.)
108     c
109     c contre-gradient pour la chaleur sensible: Kelvin/metre
110     REAL gamt(2:klev)
111     real qsurf(klon)
112     c
113     LOGICAL appel1er
114     SAVE appel1er
115     c
116     c Fonctions thermodynamiques et fonctions d'instabilite
117     REAL fsta, fins, x
118     LOGICAL zxli ! utiliser un jeu de fonctions simples
119     PARAMETER (zxli=.FALSE.)
120     c
121     fsta(x) = 1.0 / (1.0+10.0*x*(1+8.0*x))
122     fins(x) = SQRT(1.0-18.0*x)
123     c
124     DATA appel1er /.TRUE./
125     c
126     IF (appel1er) THEN
127     if (prt_level > 9) THEN
128 guez 12 print *,'coefkz, opt_ec:', opt_ec
129     print *,'coefkz, richum:', richum
130     IF (richum) print *,'coefkz, ratqs:', ratqs
131     print *,'coefkz, isommet:', isommet
132     print *,'coefkz, tvirtu:', tvirtu
133 guez 3 appel1er = .FALSE.
134     endif
135     ENDIF
136     c
137     c Initialiser les sorties
138     c
139     DO k = 1, klev
140     DO i = 1, knon
141     pcfm(i,k) = 0.0
142     pcfh(i,k) = 0.0
143     ENDDO
144     ENDDO
145     DO i = 1, knon
146     itop(i) = 0
147     ENDDO
148    
149     c
150     c Prescrire la valeur de contre-gradient
151     c
152     if (iflag_pbl.eq.1) then
153     DO k = 3, klev
154     gamt(k) = -1.0E-03
155     ENDDO
156     gamt(2) = -2.5E-03
157     else
158     DO k = 2, klev
159     gamt(k) = 0.0
160     ENDDO
161     ENDIF
162     cIM cf JLD/ GKtest
163     IF ( nsrf .NE. is_oce ) THEN
164     cIM 261103 kstable = kstable_ter
165     kstable = ksta_ter
166     ELSE
167     cIM 261103 kstable = kstable_sinon
168     kstable = ksta
169     ENDIF
170     cIM cf JLD/ GKtest fin
171     c
172     c Calculer les geopotentiels de chaque couche
173     c
174     DO i = 1, knon
175     zgeop(i,1) = RD * t(i,1) / (0.5*(paprs(i,1)+pplay(i,1)))
176     . * (paprs(i,1)-pplay(i,1))
177     ENDDO
178     DO k = 2, klev
179     DO i = 1, knon
180     zgeop(i,k) = zgeop(i,k-1)
181     . + RD * 0.5*(t(i,k-1)+t(i,k)) / paprs(i,k)
182     . * (pplay(i,k-1)-pplay(i,k))
183     ENDDO
184     ENDDO
185     c
186     c Calculer le frottement au sol (Cdrag)
187     c
188     DO i = 1, knon
189     u1(i) = u(i,1)
190     v1(i) = v(i,1)
191     t1(i) = t(i,1)
192     q1(i) = q(i,1)
193     z1(i) = zgeop(i,1)
194     ENDDO
195     c
196     CALL clcdrag(klon, knon, nsrf, zxli,
197     $ u1, v1, t1, q1, z1,
198     $ ts, qsurf, rugos,
199     $ pcfm1, pcfh1)
200     cIM $ ts, qsurf, rugos,
201     C
202     DO i = 1, knon
203     pcfm(i,1)=pcfm1(i)
204     pcfh(i,1)=pcfh1(i)
205     ENDDO
206     c
207     c Calculer les coefficients turbulents dans l'atmosphere
208     c
209     DO i = 1, knon
210     itop(i) = isommet
211     ENDDO
212    
213    
214     DO k = 2, isommet
215     DO i = 1, knon
216     zdu2=MAX(cepdu2,(u(i,k)-u(i,k-1))**2
217     . +(v(i,k)-v(i,k-1))**2)
218     zmgeom(i)=zgeop(i,k)-zgeop(i,k-1)
219     zdphi =zmgeom(i) / 2.0
220     zt = (t(i,k)+t(i,k-1)) * 0.5
221     zq = (q(i,k)+q(i,k-1)) * 0.5
222     c
223     c calculer Qs et dQs/dT:
224     c
225     IF (thermcep) THEN
226     zdelta = MAX(0.,SIGN(1.,RTT-zt))
227     zcvm5 = R5LES*RLVTT/RCPD/(1.0+RVTMP2*zq)*(1.-zdelta)
228     . + R5IES*RLSTT/RCPD/(1.0+RVTMP2*zq)*zdelta
229     zqs = R2ES * FOEEW(zt,zdelta) / pplay(i,k)
230     zqs = MIN(0.5,zqs)
231     zcor = 1./(1.-RETV*zqs)
232     zqs = zqs*zcor
233     zdqs = FOEDE(zt,zdelta,zcvm5,zqs,zcor)
234     ELSE
235     IF (zt .LT. t_coup) THEN
236     zqs = qsats(zt) / pplay(i,k)
237     zdqs = dqsats(zt,zqs)
238     ELSE
239     zqs = qsatl(zt) / pplay(i,k)
240     zdqs = dqsatl(zt,zqs)
241     ENDIF
242     ENDIF
243     c
244     c calculer la fraction nuageuse (processus humide):
245     c
246     zfr = (zq+ratqs*zq-zqs) / (2.0*ratqs*zq)
247     zfr = MAX(0.0,MIN(1.0,zfr))
248     IF (.NOT.richum) zfr = 0.0
249     c
250     c calculer le nombre de Richardson:
251     c
252     IF (tvirtu) THEN
253     ztvd =( t(i,k)
254     . + zdphi/RCPD/(1.+RVTMP2*zq)
255     . *( (1.-zfr) + zfr*(1.+RLVTT*zqs/RD/zt)/(1.+zdqs) )
256     . )*(1.+RETV*q(i,k))
257     ztvu =( t(i,k-1)
258     . - zdphi/RCPD/(1.+RVTMP2*zq)
259     . *( (1.-zfr) + zfr*(1.+RLVTT*zqs/RD/zt)/(1.+zdqs) )
260     . )*(1.+RETV*q(i,k-1))
261     zri(i) =zmgeom(i)*(ztvd-ztvu)/(zdu2*0.5*(ztvd+ztvu))
262     zri(i) = zri(i)
263     . + zmgeom(i)*zmgeom(i)/RG*gamt(k)
264     . *(paprs(i,k)/101325.0)**RKAPPA
265     . /(zdu2*0.5*(ztvd+ztvu))
266     c
267     ELSE ! calcul de Ridchardson compatible LMD5
268     c
269     zri(i) =(RCPD*(t(i,k)-t(i,k-1))
270     . -RD*0.5*(t(i,k)+t(i,k-1))/paprs(i,k)
271     . *(pplay(i,k)-pplay(i,k-1))
272     . )*zmgeom(i)/(zdu2*0.5*RCPD*(t(i,k-1)+t(i,k)))
273     zri(i) = zri(i) +
274     . zmgeom(i)*zmgeom(i)*gamt(k)/RG
275     cSB . /(paprs(i,k)/101325.0)**RKAPPA
276     . *(paprs(i,k)/101325.0)**RKAPPA
277     . /(zdu2*0.5*(t(i,k-1)+t(i,k)))
278     ENDIF
279     c
280     c finalement, les coefficients d'echange sont obtenus:
281     c
282     zcdn=SQRT(zdu2) / zmgeom(i) * RG
283     c
284     IF (opt_ec) THEN
285     z2geomf=zgeop(i,k-1)+zgeop(i,k)
286     zalm2=(0.5*ckap/RG*z2geomf
287     . /(1.+0.5*ckap/rg/clam*z2geomf))**2
288     zalh2=(0.5*ckap/rg*z2geomf
289     . /(1.+0.5*ckap/RG/(clam*SQRT(1.5*cd))*z2geomf))**2
290     IF (zri(i).LT.0.0) THEN ! situation instable
291     zscf = ((zgeop(i,k)/zgeop(i,k-1))**(1./3.)-1.)**3
292     . / (zmgeom(i)/RG)**3 / (zgeop(i,k-1)/RG)
293     zscf = SQRT(-zri(i)*zscf)
294     zscfm = 1.0 / (1.0+3.0*cb*cc*zalm2*zscf)
295     zscfh = 1.0 / (1.0+3.0*cb*cc*zalh2*zscf)
296     pcfm(i,k)=zcdn*zalm2*(1.-2.0*cb*zri(i)*zscfm)
297     pcfh(i,k)=zcdn*zalh2*(1.-3.0*cb*zri(i)*zscfh)
298     ELSE ! situation stable
299     zscf=SQRT(1.+cd*zri(i))
300     pcfm(i,k)=zcdn*zalm2/(1.+2.0*cb*zri(i)/zscf)
301     pcfh(i,k)=zcdn*zalh2/(1.+3.0*cb*zri(i)*zscf)
302     ENDIF
303     ELSE
304     zl2(i)=(mixlen*MAX(0.0,(paprs(i,k)-paprs(i,itop(i)+1))
305     . /(paprs(i,2)-paprs(i,itop(i)+1)) ))**2
306     pcfm(i,k)=sqrt(max(zcdn*zcdn*(ric-zri(i))/ric, kstable))
307     pcfm(i,k)= zl2(i)* pcfm(i,k)
308     pcfh(i,k) = pcfm(i,k) /prandtl ! h et m different
309     ENDIF
310     ENDDO
311     ENDDO
312     c
313     c Au-dela du sommet, pas de diffusion turbulente:
314     c
315     DO i = 1, knon
316     IF (itop(i)+1 .LE. klev) THEN
317     DO k = itop(i)+1, klev
318     pcfh(i,k) = 0.0
319     pcfm(i,k) = 0.0
320     ENDDO
321     ENDIF
322     ENDDO
323     c
324     RETURN
325     END

  ViewVC Help
Powered by ViewVC 1.1.21