/[lmdze]/trunk/phylmd/physiq.f
ViewVC logotype

Annotation of /trunk/phylmd/physiq.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 244 - (hide annotations)
Tue Nov 14 14:56:42 2017 UTC (6 years, 6 months ago) by guez
Original Path: trunk/Sources/phylmd/physiq.f
File size: 38552 byte(s)
In procedure clmain, rename ycoefh to coefh and coefh to ycoefh. Also
rename coefm to ycoefm. The convention is that variables beginning
with "y" are packed to knon. (Following LMDZ.) In physiq, rename
ycoefh to coefh.

1 guez 3 module physiq_m
2    
3     IMPLICIT none
4    
5     contains
6    
7 guez 154 SUBROUTINE physiq(lafin, dayvrai, time, paprs, play, pphi, pphis, u, v, t, &
8     qx, omega, d_u, d_v, d_t, d_qx)
9 guez 3
10 guez 72 ! From phylmd/physiq.F, version 1.22 2006/02/20 09:38:28
11     ! (subversion revision 678)
12    
13 guez 154 ! Author: Z. X. Li (LMD/CNRS) 1993
14 guez 3
15 guez 49 ! This is the main procedure for the "physics" part of the program.
16 guez 3
17 guez 56 use aaam_bud_m, only: aaam_bud
18 guez 51 USE abort_gcm_m, ONLY: abort_gcm
19 guez 53 use ajsec_m, only: ajsec
20 guez 52 use calltherm_m, only: calltherm
21 guez 202 USE clesphys, ONLY: cdhmax, cdmmax, ecrit_ins, ksta, ksta_ter, ok_kzmin, &
22     ok_instan
23 guez 209 USE clesphys2, ONLY: conv_emanuel, nbapp_rad, new_oliq, ok_orodr, ok_orolf
24 guez 51 USE clmain_m, ONLY: clmain
25 guez 72 use clouds_gno_m, only: clouds_gno
26 guez 154 use comconst, only: dtphys
27 guez 137 USE comgeomphy, ONLY: airephy
28 guez 51 USE concvl_m, ONLY: concvl
29 guez 224 USE conf_gcm_m, ONLY: lmt_pas
30 guez 51 USE conf_phys_m, ONLY: conf_phys
31 guez 62 use conflx_m, only: conflx
32 guez 51 USE ctherm, ONLY: iflag_thermals, nsplit_thermals
33 guez 52 use diagcld2_m, only: diagcld2
34 guez 90 USE dimens_m, ONLY: llm, nqmx
35 guez 98 USE dimphy, ONLY: klon
36 guez 51 USE dimsoil, ONLY: nsoilmx
37 guez 52 use drag_noro_m, only: drag_noro
38 guez 129 use dynetat0_m, only: day_ref, annee_ref
39 guez 221 USE fcttre, ONLY: foeew
40 guez 68 use fisrtilp_m, only: fisrtilp
41 guez 51 USE hgardfou_m, ONLY: hgardfou
42 guez 191 USE histsync_m, ONLY: histsync
43     USE histwrite_phy_m, ONLY: histwrite_phy
44 guez 51 USE indicesol, ONLY: clnsurf, epsfra, is_lic, is_oce, is_sic, is_ter, &
45     nbsrf
46 guez 191 USE ini_histins_m, ONLY: ini_histins, nid_ins
47 guez 227 use lift_noro_m, only: lift_noro
48 guez 157 use netcdf95, only: NF95_CLOSE
49 guez 68 use newmicro_m, only: newmicro
50 guez 191 use nr_util, only: assert
51 guez 175 use nuage_m, only: nuage
52 guez 98 USE orbite_m, ONLY: orbite
53 guez 51 USE ozonecm_m, ONLY: ozonecm
54 guez 227 USE phyetat0_m, ONLY: phyetat0
55 guez 51 USE phyredem_m, ONLY: phyredem
56 guez 157 USE phyredem0_m, ONLY: phyredem0
57 guez 51 USE phytrac_m, ONLY: phytrac
58 guez 53 use radlwsw_m, only: radlwsw
59 guez 158 use yoegwd, only: sugwd
60 guez 212 USE suphec_m, ONLY: rcpd, retv, rg, rlvtt, romega, rsigma, rtt, rmo3, md
61 guez 191 use time_phylmdz, only: itap, increment_itap
62 guez 169 use transp_m, only: transp
63 guez 178 use transp_lay_m, only: transp_lay
64 guez 68 use unit_nml_m, only: unit_nml
65 guez 92 USE ymds2ju_m, ONLY: ymds2ju
66 guez 51 USE yoethf_m, ONLY: r2es, rvtmp2
67 guez 98 use zenang_m, only: zenang
68 guez 3
69 guez 91 logical, intent(in):: lafin ! dernier passage
70 guez 3
71 guez 130 integer, intent(in):: dayvrai
72     ! current day number, based at value 1 on January 1st of annee_ref
73 guez 15
74 guez 90 REAL, intent(in):: time ! heure de la journ\'ee en fraction de jour
75 guez 3
76 guez 98 REAL, intent(in):: paprs(:, :) ! (klon, llm + 1)
77     ! pression pour chaque inter-couche, en Pa
78 guez 15
79 guez 98 REAL, intent(in):: play(:, :) ! (klon, llm)
80     ! pression pour le mileu de chaque couche (en Pa)
81 guez 3
82 guez 190 REAL, intent(in):: pphi(:, :) ! (klon, llm)
83 guez 97 ! géopotentiel de chaque couche (référence sol)
84 guez 3
85 guez 98 REAL, intent(in):: pphis(:) ! (klon) géopotentiel du sol
86 guez 3
87 guez 98 REAL, intent(in):: u(:, :) ! (klon, llm)
88 guez 202 ! vitesse dans la direction X (de O a E) en m / s
89 guez 51
90 guez 202 REAL, intent(in):: v(:, :) ! (klon, llm) vitesse Y (de S a N) en m / s
91 guez 98 REAL, intent(in):: t(:, :) ! (klon, llm) temperature (K)
92 guez 3
93 guez 98 REAL, intent(in):: qx(:, :, :) ! (klon, llm, nqmx)
94 guez 90 ! (humidit\'e sp\'ecifique et fractions massiques des autres traceurs)
95 guez 3
96 guez 202 REAL, intent(in):: omega(:, :) ! (klon, llm) vitesse verticale en Pa / s
97 guez 98 REAL, intent(out):: d_u(:, :) ! (klon, llm) tendance physique de "u" (m s-2)
98     REAL, intent(out):: d_v(:, :) ! (klon, llm) tendance physique de "v" (m s-2)
99 guez 202 REAL, intent(out):: d_t(:, :) ! (klon, llm) tendance physique de "t" (K / s)
100 guez 3
101 guez 98 REAL, intent(out):: d_qx(:, :, :) ! (klon, llm, nqmx)
102     ! tendance physique de "qx" (s-1)
103    
104 guez 91 ! Local:
105    
106 guez 35 LOGICAL:: firstcal = .true.
107    
108 guez 51 LOGICAL, PARAMETER:: ok_stratus = .FALSE.
109 guez 49 ! Ajouter artificiellement les stratus
110    
111 guez 200 ! pour phystoke avec thermiques
112 guez 51 REAL fm_therm(klon, llm + 1)
113 guez 3 REAL entr_therm(klon, llm)
114 guez 51 real, save:: q2(klon, llm + 1, nbsrf)
115 guez 3
116 guez 98 INTEGER, PARAMETER:: ivap = 1 ! indice de traceur pour vapeur d'eau
117     INTEGER, PARAMETER:: iliq = 2 ! indice de traceur pour eau liquide
118 guez 3
119 guez 49 REAL, save:: t_ancien(klon, llm), q_ancien(klon, llm)
120     LOGICAL, save:: ancien_ok
121 guez 3
122 guez 202 REAL d_t_dyn(klon, llm) ! tendance dynamique pour "t" (K / s)
123     REAL d_q_dyn(klon, llm) ! tendance dynamique pour "q" (kg / kg / s)
124 guez 3
125     real da(klon, llm), phi(klon, llm, llm), mp(klon, llm)
126    
127 guez 205 REAL, save:: swdn0(klon, llm + 1), swdn(klon, llm + 1)
128     REAL, save:: swup0(klon, llm + 1), swup(klon, llm + 1)
129 guez 3
130 guez 205 REAL, save:: lwdn0(klon, llm + 1), lwdn(klon, llm + 1)
131     REAL, save:: lwup0(klon, llm + 1), lwup(klon, llm + 1)
132 guez 3
133     ! prw: precipitable water
134     real prw(klon)
135    
136 guez 202 ! flwp, fiwp = Liquid Water Path & Ice Water Path (kg / m2)
137     ! flwc, fiwc = Liquid Water Content & Ice Water Content (kg / kg)
138 guez 3 REAL flwp(klon), fiwp(klon)
139     REAL flwc(klon, llm), fiwc(klon, llm)
140    
141     ! Variables propres a la physique
142    
143     INTEGER, save:: radpas
144 guez 125 ! Radiative transfer computations are made every "radpas" call to
145     ! "physiq".
146 guez 3
147 guez 205 REAL, save:: radsol(klon) ! bilan radiatif au sol calcule par code radiatif
148 guez 49 REAL, save:: ftsol(klon, nbsrf) ! skin temperature of surface fraction
149 guez 3
150 guez 49 REAL, save:: ftsoil(klon, nsoilmx, nbsrf)
151     ! soil temperature of surface fraction
152 guez 3
153 guez 71 REAL, save:: fevap(klon, nbsrf) ! evaporation
154 guez 214 REAL fluxlat(klon, nbsrf)
155 guez 3
156 guez 98 REAL, save:: fqsurf(klon, nbsrf)
157     ! humidite de l'air au contact de la surface
158 guez 3
159 guez 215 REAL, save:: qsol(klon) ! column-density of water in soil, in kg m-2
160     REAL, save:: fsnow(klon, nbsrf) ! \'epaisseur neigeuse
161 guez 155 REAL, save:: falbe(klon, nbsrf) ! albedo visible par type de surface
162 guez 3
163 guez 90 ! Param\`etres de l'orographie \`a l'\'echelle sous-maille (OESM) :
164 guez 13 REAL, save:: zmea(klon) ! orographie moyenne
165     REAL, save:: zstd(klon) ! deviation standard de l'OESM
166     REAL, save:: zsig(klon) ! pente de l'OESM
167     REAL, save:: zgam(klon) ! anisotropie de l'OESM
168     REAL, save:: zthe(klon) ! orientation de l'OESM
169     REAL, save:: zpic(klon) ! Maximum de l'OESM
170     REAL, save:: zval(klon) ! Minimum de l'OESM
171     REAL, save:: rugoro(klon) ! longueur de rugosite de l'OESM
172 guez 3 REAL zulow(klon), zvlow(klon)
173 guez 178 INTEGER igwd, itest(klon)
174 guez 3
175 guez 189 REAL, save:: agesno(klon, nbsrf) ! age de la neige
176     REAL, save:: run_off_lic_0(klon)
177 guez 3
178 guez 189 ! Variables li\'ees \`a la convection d'Emanuel :
179     REAL, save:: Ma(klon, llm) ! undilute upward mass flux
180     REAL, save:: qcondc(klon, llm) ! in-cld water content from convect
181 guez 72 REAL, save:: sig1(klon, llm), w01(klon, llm)
182 guez 3
183 guez 189 ! Variables pour la couche limite (Alain Lahellec) :
184 guez 3 REAL cdragh(klon) ! drag coefficient pour T and Q
185     REAL cdragm(klon) ! drag coefficient pour vent
186    
187 guez 244 REAL coefh(klon, 2:llm) ! coef d'echange pour phytrac
188 guez 191
189 guez 205 REAL, save:: ffonte(klon, nbsrf)
190     ! flux thermique utilise pour fondre la neige
191    
192     REAL, save:: fqcalving(klon, nbsrf)
193 guez 191 ! flux d'eau "perdue" par la surface et necessaire pour limiter la
194 guez 202 ! hauteur de neige, en kg / m2 / s
195 guez 191
196 guez 3 REAL zxffonte(klon), zxfqcalving(klon)
197    
198 guez 205 REAL, save:: pfrac_impa(klon, llm)! Produits des coefs lessivage impaction
199     REAL, save:: pfrac_nucl(klon, llm)! Produits des coefs lessivage nucleation
200    
201     REAL, save:: pfrac_1nucl(klon, llm)
202     ! Produits des coefs lessi nucl (alpha = 1)
203    
204 guez 213 REAL frac_impa(klon, llm) ! fraction d'a\'erosols lessiv\'es (impaction)
205 guez 3 REAL frac_nucl(klon, llm) ! idem (nucleation)
206    
207 guez 101 REAL, save:: rain_fall(klon)
208 guez 202 ! liquid water mass flux (kg / m2 / s), positive down
209 guez 62
210 guez 101 REAL, save:: snow_fall(klon)
211 guez 202 ! solid water mass flux (kg / m2 / s), positive down
212 guez 101
213 guez 3 REAL rain_tiedtke(klon), snow_tiedtke(klon)
214    
215 guez 206 REAL evap(klon) ! flux d'\'evaporation au sol
216     real devap(klon) ! derivative of the evaporation flux at the surface
217     REAL sens(klon) ! flux de chaleur sensible au sol
218     real dsens(klon) ! derivee du flux de chaleur sensible au sol
219 guez 223 REAL, save:: dlw(klon) ! derivative of infra-red flux
220 guez 3 REAL bils(klon) ! bilan de chaleur au sol
221 guez 223 REAL fder(klon) ! Derive de flux (sensible et latente)
222 guez 3 REAL ve(klon) ! integr. verticale du transport meri. de l'energie
223     REAL vq(klon) ! integr. verticale du transport meri. de l'eau
224     REAL ue(klon) ! integr. verticale du transport zonal de l'energie
225     REAL uq(klon) ! integr. verticale du transport zonal de l'eau
226    
227 guez 98 REAL, save:: frugs(klon, nbsrf) ! longueur de rugosite
228 guez 3 REAL zxrugs(klon) ! longueur de rugosite
229    
230     ! Conditions aux limites
231    
232     INTEGER julien
233 guez 70 REAL, save:: pctsrf(klon, nbsrf) ! percentage of surface
234 guez 217 REAL, save:: albsol(klon) ! albedo du sol total, visible, moyen par maille
235 guez 17 REAL, SAVE:: wo(klon, llm) ! column density of ozone in a cell, in kDU
236 guez 212 real, parameter:: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
237 guez 3
238 guez 72 real, save:: clwcon(klon, llm), rnebcon(klon, llm)
239     real, save:: clwcon0(klon, llm), rnebcon0(klon, llm)
240 guez 3
241 guez 47 REAL rhcl(klon, llm) ! humiditi relative ciel clair
242     REAL dialiq(klon, llm) ! eau liquide nuageuse
243     REAL diafra(klon, llm) ! fraction nuageuse
244     REAL cldliq(klon, llm) ! eau liquide nuageuse
245     REAL cldfra(klon, llm) ! fraction nuageuse
246     REAL cldtau(klon, llm) ! epaisseur optique
247     REAL cldemi(klon, llm) ! emissivite infrarouge
248 guez 3
249 guez 206 REAL flux_q(klon, nbsrf) ! flux turbulent d'humidite à la surface
250     REAL flux_t(klon, nbsrf) ! flux turbulent de chaleur à la surface
251 guez 3
252 guez 229 REAL flux_u(klon, nbsrf), flux_v(klon, nbsrf)
253     ! tension du vent (flux turbulent de vent) à la surface, en Pa
254    
255 guez 90 ! Le rayonnement n'est pas calcul\'e tous les pas, il faut donc que
256     ! les variables soient r\'emanentes.
257 guez 53 REAL, save:: heat(klon, llm) ! chauffage solaire
258 guez 154 REAL, save:: heat0(klon, llm) ! chauffage solaire ciel clair
259 guez 62 REAL, save:: cool(klon, llm) ! refroidissement infrarouge
260 guez 154 REAL, save:: cool0(klon, llm) ! refroidissement infrarouge ciel clair
261 guez 72 REAL, save:: topsw(klon), toplw(klon), solsw(klon)
262 guez 90 REAL, save:: sollw(klon) ! rayonnement infrarouge montant \`a la surface
263 guez 72 real, save:: sollwdown(klon) ! downward LW flux at surface
264 guez 62 REAL, save:: topsw0(klon), toplw0(klon), solsw0(klon), sollw0(klon)
265 guez 154 REAL, save:: albpla(klon)
266 guez 191 REAL fsollw(klon, nbsrf) ! bilan flux IR pour chaque sous-surface
267     REAL fsolsw(klon, nbsrf) ! flux solaire absorb\'e pour chaque sous-surface
268 guez 3
269 guez 202 REAL conv_q(klon, llm) ! convergence de l'humidite (kg / kg / s)
270     REAL conv_t(klon, llm) ! convergence of temperature (K / s)
271 guez 3
272 guez 191 REAL cldl(klon), cldm(klon), cldh(klon) ! nuages bas, moyen et haut
273     REAL cldt(klon), cldq(klon) ! nuage total, eau liquide integree
274 guez 3
275 guez 221 REAL zxfluxlat(klon)
276 guez 118 REAL dist, mu0(klon), fract(klon)
277     real longi
278 guez 3 REAL z_avant(klon), z_apres(klon), z_factor(klon)
279 guez 205 REAL zb
280 guez 103 REAL zx_t, zx_qs, zcor
281 guez 3 real zqsat(klon, llm)
282     INTEGER i, k, iq, nsrf
283     REAL zphi(klon, llm)
284    
285 guez 200 ! cf. Anne Mathieu, variables pour la couche limite atmosphérique (hbtm)
286 guez 3
287 guez 49 REAL, SAVE:: pblh(klon, nbsrf) ! Hauteur de couche limite
288     REAL, SAVE:: plcl(klon, nbsrf) ! Niveau de condensation de la CLA
289     REAL, SAVE:: capCL(klon, nbsrf) ! CAPE de couche limite
290     REAL, SAVE:: oliqCL(klon, nbsrf) ! eau_liqu integree de couche limite
291     REAL, SAVE:: cteiCL(klon, nbsrf) ! cloud top instab. crit. couche limite
292 guez 207 REAL, SAVE:: pblt(klon, nbsrf) ! T \`a la hauteur de couche limite
293 guez 49 REAL, SAVE:: therm(klon, nbsrf)
294     REAL, SAVE:: trmb1(klon, nbsrf) ! deep_cape
295 guez 190 REAL, SAVE:: trmb2(klon, nbsrf) ! inhibition
296 guez 49 REAL, SAVE:: trmb3(klon, nbsrf) ! Point Omega
297 guez 186 ! Grandeurs de sorties
298 guez 3 REAL s_pblh(klon), s_lcl(klon), s_capCL(klon)
299     REAL s_oliqCL(klon), s_cteiCL(klon), s_pblt(klon)
300     REAL s_therm(klon), s_trmb1(klon), s_trmb2(klon)
301     REAL s_trmb3(klon)
302    
303 guez 175 ! Variables pour la convection de K. Emanuel :
304 guez 3
305 guez 47 REAL upwd(klon, llm) ! saturated updraft mass flux
306     REAL dnwd(klon, llm) ! saturated downdraft mass flux
307 guez 205 REAL, save:: cape(klon)
308 guez 3
309 guez 47 INTEGER iflagctrl(klon) ! flag fonctionnement de convect
310 guez 3
311     ! Variables du changement
312    
313     ! con: convection
314 guez 51 ! lsc: large scale condensation
315 guez 3 ! ajs: ajustement sec
316 guez 90 ! eva: \'evaporation de l'eau liquide nuageuse
317 guez 51 ! vdf: vertical diffusion in boundary layer
318 guez 3 REAL d_t_con(klon, llm), d_q_con(klon, llm)
319 guez 205 REAL, save:: d_u_con(klon, llm), d_v_con(klon, llm)
320 guez 3 REAL d_t_lsc(klon, llm), d_q_lsc(klon, llm), d_ql_lsc(klon, llm)
321     REAL d_t_ajs(klon, llm), d_q_ajs(klon, llm)
322     REAL d_u_ajs(klon, llm), d_v_ajs(klon, llm)
323     REAL rneb(klon, llm)
324    
325 guez 71 REAL mfu(klon, llm), mfd(klon, llm)
326 guez 3 REAL pen_u(klon, llm), pen_d(klon, llm)
327     REAL pde_u(klon, llm), pde_d(klon, llm)
328     INTEGER kcbot(klon), kctop(klon), kdtop(klon)
329 guez 51 REAL pmflxr(klon, llm + 1), pmflxs(klon, llm + 1)
330     REAL prfl(klon, llm + 1), psfl(klon, llm + 1)
331 guez 3
332 guez 62 INTEGER, save:: ibas_con(klon), itop_con(klon)
333 guez 183 real ema_pct(klon) ! Emanuel pressure at cloud top, in Pa
334 guez 3
335 guez 205 REAL, save:: rain_con(klon)
336     real rain_lsc(klon)
337 guez 183 REAL, save:: snow_con(klon) ! neige (mm / s)
338 guez 180 real snow_lsc(klon)
339 guez 221 REAL d_ts(klon, nbsrf) ! variation of ftsol
340 guez 3
341     REAL d_u_vdf(klon, llm), d_v_vdf(klon, llm)
342     REAL d_t_vdf(klon, llm), d_q_vdf(klon, llm)
343    
344     REAL d_u_oro(klon, llm), d_v_oro(klon, llm)
345     REAL d_t_oro(klon, llm)
346     REAL d_u_lif(klon, llm), d_v_lif(klon, llm)
347     REAL d_t_lif(klon, llm)
348    
349 guez 68 REAL, save:: ratqs(klon, llm)
350     real ratqss(klon, llm), ratqsc(klon, llm)
351     real:: ratqsbas = 0.01, ratqshaut = 0.3
352 guez 3
353     ! Parametres lies au nouveau schema de nuages (SB, PDF)
354 guez 68 real:: fact_cldcon = 0.375
355     real:: facttemps = 1.e-4
356     logical:: ok_newmicro = .true.
357 guez 3 real facteur
358    
359 guez 68 integer:: iflag_cldcon = 1
360 guez 3 logical ptconv(klon, llm)
361    
362 guez 175 ! Variables pour effectuer les appels en s\'erie :
363 guez 3
364     REAL t_seri(klon, llm), q_seri(klon, llm)
365 guez 98 REAL ql_seri(klon, llm)
366 guez 3 REAL u_seri(klon, llm), v_seri(klon, llm)
367 guez 98 REAL tr_seri(klon, llm, nqmx - 2)
368 guez 3
369     REAL zx_rh(klon, llm)
370    
371     REAL zustrdr(klon), zvstrdr(klon)
372     REAL zustrli(klon), zvstrli(klon)
373     REAL aam, torsfc
374    
375     REAL ve_lay(klon, llm) ! transport meri. de l'energie a chaque niveau vert.
376     REAL vq_lay(klon, llm) ! transport meri. de l'eau a chaque niveau vert.
377     REAL ue_lay(klon, llm) ! transport zonal de l'energie a chaque niveau vert.
378     REAL uq_lay(klon, llm) ! transport zonal de l'eau a chaque niveau vert.
379    
380     real date0
381 guez 221 REAL tsol(klon)
382 guez 51
383 guez 202 REAL d_t_ec(klon, llm)
384 guez 213 ! tendance due \`a la conversion d'\'energie cin\'etique en
385     ! énergie thermique
386 guez 200
387 guez 205 REAL, save:: t2m(klon, nbsrf), q2m(klon, nbsrf)
388     ! temperature and humidity at 2 m
389    
390 guez 225 REAL, save:: u10m_srf(klon, nbsrf), v10m_srf(klon, nbsrf)
391     ! composantes du vent \`a 10 m
392    
393 guez 207 REAL zt2m(klon), zq2m(klon) ! température, humidité 2 m moyenne sur 1 maille
394 guez 225 REAL u10m(klon), v10m(klon) ! vent \`a 10 m moyenn\' sur les sous-surfaces
395 guez 3
396 guez 69 ! Aerosol effects:
397    
398 guez 205 REAL, save:: topswad(klon), solswad(klon) ! aerosol direct effect
399 guez 68 LOGICAL:: ok_ade = .false. ! apply aerosol direct effect
400 guez 3
401 guez 68 REAL:: bl95_b0 = 2., bl95_b1 = 0.2
402 guez 69 ! Parameters in equation (D) of Boucher and Lohmann (1995, Tellus
403     ! B). They link cloud droplet number concentration to aerosol mass
404     ! concentration.
405 guez 68
406 guez 190 real zmasse(klon, llm)
407 guez 17 ! (column-density of mass of air in a cell, in kg m-2)
408    
409 guez 191 integer, save:: ncid_startphy
410 guez 17
411 guez 204 namelist /physiq_nml/ fact_cldcon, facttemps, ok_newmicro, iflag_cldcon, &
412 guez 217 ratqsbas, ratqshaut, ok_ade, bl95_b0, bl95_b1, iflag_thermals, &
413     nsplit_thermals
414 guez 68
415 guez 3 !----------------------------------------------------------------
416    
417 guez 69 IF (nqmx < 2) CALL abort_gcm('physiq', &
418 guez 171 'eaux vapeur et liquide sont indispensables')
419 guez 3
420 guez 7 test_firstcal: IF (firstcal) THEN
421 guez 47 ! initialiser
422 guez 225 u10m_srf = 0.
423     v10m_srf = 0.
424 guez 51 t2m = 0.
425     q2m = 0.
426     ffonte = 0.
427     fqcalving = 0.
428 guez 98 rain_con = 0.
429     snow_con = 0.
430 guez 72 d_u_con = 0.
431     d_v_con = 0.
432     rnebcon0 = 0.
433     clwcon0 = 0.
434     rnebcon = 0.
435     clwcon = 0.
436 guez 47 pblh =0. ! Hauteur de couche limite
437     plcl =0. ! Niveau de condensation de la CLA
438     capCL =0. ! CAPE de couche limite
439     oliqCL =0. ! eau_liqu integree de couche limite
440     cteiCL =0. ! cloud top instab. crit. couche limite
441 guez 207 pblt =0.
442 guez 47 therm =0.
443     trmb1 =0. ! deep_cape
444 guez 190 trmb2 =0. ! inhibition
445 guez 47 trmb3 =0. ! Point Omega
446 guez 3
447 guez 68 iflag_thermals = 0
448     nsplit_thermals = 1
449     print *, "Enter namelist 'physiq_nml'."
450     read(unit=*, nml=physiq_nml)
451     write(unit_nml, nml=physiq_nml)
452    
453     call conf_phys
454 guez 3
455     ! Initialiser les compteurs:
456    
457     frugs = 0.
458 guez 191 CALL phyetat0(pctsrf, ftsol, ftsoil, fqsurf, qsol, fsnow, falbe, &
459     fevap, rain_fall, snow_fall, solsw, sollw, dlw, radsol, frugs, &
460     agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &
461     q_ancien, ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, &
462     w01, ncid_startphy)
463 guez 3
464 guez 47 ! ATTENTION : il faudra a terme relire q2 dans l'etat initial
465 guez 69 q2 = 1e-8
466 guez 3
467 guez 154 radpas = lmt_pas / nbapp_rad
468 guez 191 print *, "radpas = ", radpas
469 guez 154
470 guez 90 ! Initialisation pour le sch\'ema de convection d'Emanuel :
471 guez 182 IF (conv_emanuel) THEN
472 guez 69 ibas_con = 1
473     itop_con = 1
474 guez 3 ENDIF
475    
476     IF (ok_orodr) THEN
477 guez 13 rugoro = MAX(1e-5, zstd * zsig / 2)
478 guez 54 CALL SUGWD(paprs, play)
479 guez 13 else
480     rugoro = 0.
481 guez 3 ENDIF
482    
483 guez 202 ecrit_ins = NINT(ecrit_ins / dtphys)
484 guez 3
485 guez 47 ! Initialisation des sorties
486 guez 3
487 guez 217 call ini_histins(dtphys, ok_newmicro)
488 guez 129 CALL ymds2ju(annee_ref, 1, day_ref, 0., date0)
489 guez 69 ! Positionner date0 pour initialisation de ORCHIDEE
490     print *, 'physiq date0: ', date0
491 guez 202 CALL phyredem0
492 guez 7 ENDIF test_firstcal
493 guez 3
494 guez 91 ! We will modify variables *_seri and we will not touch variables
495 guez 98 ! u, v, t, qx:
496     t_seri = t
497     u_seri = u
498     v_seri = v
499     q_seri = qx(:, :, ivap)
500     ql_seri = qx(:, :, iliq)
501 guez 157 tr_seri = qx(:, :, 3:nqmx)
502 guez 3
503 guez 221 tsol = sum(ftsol * pctsrf, dim = 2)
504 guez 3
505 guez 51 ! Diagnostic de la tendance dynamique :
506 guez 3 IF (ancien_ok) THEN
507     DO k = 1, llm
508     DO i = 1, klon
509 guez 49 d_t_dyn(i, k) = (t_seri(i, k) - t_ancien(i, k)) / dtphys
510     d_q_dyn(i, k) = (q_seri(i, k) - q_ancien(i, k)) / dtphys
511 guez 3 ENDDO
512     ENDDO
513     ELSE
514     DO k = 1, llm
515     DO i = 1, klon
516 guez 72 d_t_dyn(i, k) = 0.
517     d_q_dyn(i, k) = 0.
518 guez 3 ENDDO
519     ENDDO
520     ancien_ok = .TRUE.
521     ENDIF
522    
523     ! Ajouter le geopotentiel du sol:
524     DO k = 1, llm
525     DO i = 1, klon
526     zphi(i, k) = pphi(i, k) + pphis(i)
527     ENDDO
528     ENDDO
529    
530 guez 49 ! Check temperatures:
531 guez 3 CALL hgardfou(t_seri, ftsol)
532    
533 guez 191 call increment_itap
534 guez 130 julien = MOD(dayvrai, 360)
535 guez 3 if (julien == 0) julien = 360
536    
537 guez 103 forall (k = 1: llm) zmasse(:, k) = (paprs(:, k) - paprs(:, k + 1)) / rg
538 guez 17
539 guez 90 ! \'Evaporation de l'eau liquide nuageuse :
540 guez 51 DO k = 1, llm
541 guez 3 DO i = 1, klon
542 guez 51 zb = MAX(0., ql_seri(i, k))
543     t_seri(i, k) = t_seri(i, k) &
544     - zb * RLVTT / RCPD / (1. + RVTMP2 * q_seri(i, k))
545 guez 3 q_seri(i, k) = q_seri(i, k) + zb
546     ENDDO
547     ENDDO
548 guez 51 ql_seri = 0.
549 guez 3
550 guez 98 frugs = MAX(frugs, 0.000015)
551     zxrugs = sum(frugs * pctsrf, dim = 2)
552 guez 3
553 guez 191 ! Calculs n\'ecessaires au calcul de l'albedo dans l'interface avec
554 guez 118 ! la surface.
555 guez 3
556 guez 118 CALL orbite(REAL(julien), longi, dist)
557 guez 209 CALL zenang(longi, time, dtphys * radpas, mu0, fract)
558 guez 98 albsol = sum(falbe * pctsrf, dim = 2)
559 guez 3
560 guez 90 ! R\'epartition sous maille des flux longwave et shortwave
561     ! R\'epartition du longwave par sous-surface lin\'earis\'ee
562 guez 3
563 guez 98 forall (nsrf = 1: nbsrf)
564 guez 221 fsollw(:, nsrf) = sollw + 4. * RSIGMA * tsol**3 &
565     * (tsol - ftsol(:, nsrf))
566 guez 98 fsolsw(:, nsrf) = solsw * (1. - falbe(:, nsrf)) / (1. - albsol)
567     END forall
568 guez 3
569 guez 202 CALL clmain(dtphys, pctsrf, t_seri, q_seri, u_seri, v_seri, julien, mu0, &
570     ftsol, cdmmax, cdhmax, ksta, ksta_ter, ok_kzmin, ftsoil, qsol, &
571     paprs, play, fsnow, fqsurf, fevap, falbe, fluxlat, rain_fall, &
572 guez 223 snow_fall, fsolsw, fsollw, frugs, agesno, rugoro, d_t_vdf, d_q_vdf, &
573     d_u_vdf, d_v_vdf, d_ts, flux_t, flux_q, flux_u, flux_v, cdragh, &
574 guez 244 cdragm, q2, dsens, devap, coefh, t2m, q2m, u10m_srf, v10m_srf, &
575 guez 226 pblh, capCL, oliqCL, cteiCL, pblT, therm, trmb1, trmb2, trmb3, plcl, &
576     fqcalving, ffonte, run_off_lic_0)
577 guez 3
578 guez 90 ! Incr\'ementation des flux
579 guez 40
580 guez 206 sens = - sum(flux_t * pctsrf, dim = 2)
581     evap = - sum(flux_q * pctsrf, dim = 2)
582     fder = dlw + dsens + devap
583 guez 3
584     DO k = 1, llm
585     DO i = 1, klon
586     t_seri(i, k) = t_seri(i, k) + d_t_vdf(i, k)
587     q_seri(i, k) = q_seri(i, k) + d_q_vdf(i, k)
588     u_seri(i, k) = u_seri(i, k) + d_u_vdf(i, k)
589     v_seri(i, k) = v_seri(i, k) + d_v_vdf(i, k)
590     ENDDO
591     ENDDO
592    
593 guez 49 ! Update surface temperature:
594 guez 3
595 guez 191 call assert(abs(sum(pctsrf, dim = 2) - 1.) <= EPSFRA, 'physiq: pctsrf')
596 guez 202 ftsol = ftsol + d_ts
597 guez 221 tsol = sum(ftsol * pctsrf, dim = 2)
598 guez 208 zxfluxlat = sum(fluxlat * pctsrf, dim = 2)
599     zt2m = sum(t2m * pctsrf, dim = 2)
600     zq2m = sum(q2m * pctsrf, dim = 2)
601 guez 225 u10m = sum(u10m_srf * pctsrf, dim = 2)
602     v10m = sum(v10m_srf * pctsrf, dim = 2)
603 guez 208 zxffonte = sum(ffonte * pctsrf, dim = 2)
604     zxfqcalving = sum(fqcalving * pctsrf, dim = 2)
605     s_pblh = sum(pblh * pctsrf, dim = 2)
606     s_lcl = sum(plcl * pctsrf, dim = 2)
607     s_capCL = sum(capCL * pctsrf, dim = 2)
608     s_oliqCL = sum(oliqCL * pctsrf, dim = 2)
609     s_cteiCL = sum(cteiCL * pctsrf, dim = 2)
610     s_pblT = sum(pblT * pctsrf, dim = 2)
611     s_therm = sum(therm * pctsrf, dim = 2)
612     s_trmb1 = sum(trmb1 * pctsrf, dim = 2)
613     s_trmb2 = sum(trmb2 * pctsrf, dim = 2)
614     s_trmb3 = sum(trmb3 * pctsrf, dim = 2)
615 guez 3
616 guez 205 ! Si une sous-fraction n'existe pas, elle prend la valeur moyenne :
617 guez 3 DO nsrf = 1, nbsrf
618     DO i = 1, klon
619 guez 205 IF (pctsrf(i, nsrf) < epsfra) then
620 guez 221 ftsol(i, nsrf) = tsol(i)
621 guez 205 t2m(i, nsrf) = zt2m(i)
622     q2m(i, nsrf) = zq2m(i)
623 guez 225 u10m_srf(i, nsrf) = u10m(i)
624     v10m_srf(i, nsrf) = v10m(i)
625 guez 205 ffonte(i, nsrf) = zxffonte(i)
626     fqcalving(i, nsrf) = zxfqcalving(i)
627     pblh(i, nsrf) = s_pblh(i)
628     plcl(i, nsrf) = s_lcl(i)
629     capCL(i, nsrf) = s_capCL(i)
630     oliqCL(i, nsrf) = s_oliqCL(i)
631     cteiCL(i, nsrf) = s_cteiCL(i)
632     pblT(i, nsrf) = s_pblT(i)
633     therm(i, nsrf) = s_therm(i)
634     trmb1(i, nsrf) = s_trmb1(i)
635     trmb2(i, nsrf) = s_trmb2(i)
636     trmb3(i, nsrf) = s_trmb3(i)
637     end IF
638 guez 3 ENDDO
639     ENDDO
640    
641 guez 223 dlw = - 4. * RSIGMA * tsol**3
642 guez 3
643 guez 190 ! Appeler la convection
644 guez 3
645 guez 182 if (conv_emanuel) then
646 guez 195 CALL concvl(paprs, play, t_seri, q_seri, u_seri, v_seri, sig1, w01, &
647     d_t_con, d_q_con, d_u_con, d_v_con, rain_con, ibas_con, itop_con, &
648 guez 206 upwd, dnwd, Ma, cape, iflagctrl, qcondc, pmflxr, da, phi, mp)
649 guez 183 snow_con = 0.
650 guez 62 clwcon0 = qcondc
651 guez 71 mfu = upwd + dnwd
652 guez 3
653 guez 207 zqsat = MIN(0.5, r2es * FOEEW(t_seri, rtt >= t_seri) / play)
654     zqsat = zqsat / (1. - retv * zqsat)
655 guez 3
656 guez 103 ! Properties of convective clouds
657 guez 71 clwcon0 = fact_cldcon * clwcon0
658 guez 62 call clouds_gno(klon, llm, q_seri, zqsat, clwcon0, ptconv, ratqsc, &
659     rnebcon0)
660 guez 72
661 guez 190 forall (i = 1:klon) ema_pct(i) = paprs(i, itop_con(i) + 1)
662 guez 72 mfd = 0.
663     pen_u = 0.
664     pen_d = 0.
665     pde_d = 0.
666     pde_u = 0.
667 guez 182 else
668     conv_q = d_q_dyn + d_q_vdf / dtphys
669     conv_t = d_t_dyn + d_t_vdf / dtphys
670     z_avant = sum((q_seri + ql_seri) * zmasse, dim=2)
671     CALL conflx(dtphys, paprs, play, t_seri(:, llm:1:- 1), &
672 guez 206 q_seri(:, llm:1:- 1), conv_t, conv_q, - evap, omega, &
673 guez 182 d_t_con, d_q_con, rain_con, snow_con, mfu(:, llm:1:- 1), &
674     mfd(:, llm:1:- 1), pen_u, pde_u, pen_d, pde_d, kcbot, kctop, &
675     kdtop, pmflxr, pmflxs)
676     WHERE (rain_con < 0.) rain_con = 0.
677     WHERE (snow_con < 0.) snow_con = 0.
678     ibas_con = llm + 1 - kcbot
679     itop_con = llm + 1 - kctop
680 guez 69 END if
681 guez 3
682     DO k = 1, llm
683     DO i = 1, klon
684     t_seri(i, k) = t_seri(i, k) + d_t_con(i, k)
685     q_seri(i, k) = q_seri(i, k) + d_q_con(i, k)
686     u_seri(i, k) = u_seri(i, k) + d_u_con(i, k)
687     v_seri(i, k) = v_seri(i, k) + d_v_con(i, k)
688     ENDDO
689     ENDDO
690    
691 guez 182 IF (.not. conv_emanuel) THEN
692 guez 69 z_apres = sum((q_seri + ql_seri) * zmasse, dim=2)
693     z_factor = (z_avant - (rain_con + snow_con) * dtphys) / z_apres
694 guez 3 DO k = 1, llm
695     DO i = 1, klon
696 guez 52 IF (z_factor(i) > 1. + 1E-8 .OR. z_factor(i) < 1. - 1E-8) THEN
697 guez 3 q_seri(i, k) = q_seri(i, k) * z_factor(i)
698     ENDIF
699     ENDDO
700     ENDDO
701     ENDIF
702    
703 guez 90 ! Convection s\`eche (thermiques ou ajustement)
704 guez 3
705 guez 51 d_t_ajs = 0.
706     d_u_ajs = 0.
707     d_v_ajs = 0.
708     d_q_ajs = 0.
709     fm_therm = 0.
710     entr_therm = 0.
711 guez 3
712 guez 47 if (iflag_thermals == 0) then
713     ! Ajustement sec
714     CALL ajsec(paprs, play, t_seri, q_seri, d_t_ajs, d_q_ajs)
715 guez 13 t_seri = t_seri + d_t_ajs
716     q_seri = q_seri + d_q_ajs
717 guez 3 else
718 guez 47 call calltherm(dtphys, play, paprs, pphi, u_seri, v_seri, t_seri, &
719     q_seri, d_u_ajs, d_v_ajs, d_t_ajs, d_q_ajs, fm_therm, entr_therm)
720 guez 3 endif
721    
722 guez 47 ! Caclul des ratqs
723 guez 3
724 guez 90 ! ratqs convectifs \`a l'ancienne en fonction de (q(z = 0) - q) / q
725     ! on \'ecrase le tableau ratqsc calcul\'e par clouds_gno
726 guez 3 if (iflag_cldcon == 1) then
727 guez 51 do k = 1, llm
728     do i = 1, klon
729 guez 3 if(ptconv(i, k)) then
730 guez 70 ratqsc(i, k) = ratqsbas + fact_cldcon &
731     * (q_seri(i, 1) - q_seri(i, k)) / q_seri(i, k)
732 guez 3 else
733 guez 51 ratqsc(i, k) = 0.
734 guez 3 endif
735     enddo
736     enddo
737     endif
738    
739 guez 47 ! ratqs stables
740 guez 51 do k = 1, llm
741     do i = 1, klon
742 guez 70 ratqss(i, k) = ratqsbas + (ratqshaut - ratqsbas) &
743 guez 190 * min((paprs(i, 1) - play(i, k)) / (paprs(i, 1) - 3e4), 1.)
744 guez 3 enddo
745     enddo
746    
747 guez 47 ! ratqs final
748 guez 69 if (iflag_cldcon == 1 .or. iflag_cldcon == 2) then
749 guez 47 ! les ratqs sont une conbinaison de ratqss et ratqsc
750     ! ratqs final
751     ! 1e4 (en gros 3 heures), en dur pour le moment, est le temps de
752     ! relaxation des ratqs
753 guez 70 ratqs = max(ratqs * exp(- dtphys * facttemps), ratqss)
754 guez 51 ratqs = max(ratqs, ratqsc)
755 guez 3 else
756 guez 47 ! on ne prend que le ratqs stable pour fisrtilp
757 guez 51 ratqs = ratqss
758 guez 3 endif
759    
760 guez 51 CALL fisrtilp(dtphys, paprs, play, t_seri, q_seri, ptconv, ratqs, &
761     d_t_lsc, d_q_lsc, d_ql_lsc, rneb, cldliq, rain_lsc, snow_lsc, &
762     pfrac_impa, pfrac_nucl, pfrac_1nucl, frac_impa, frac_nucl, prfl, &
763     psfl, rhcl)
764 guez 3
765     WHERE (rain_lsc < 0) rain_lsc = 0.
766     WHERE (snow_lsc < 0) snow_lsc = 0.
767     DO k = 1, llm
768     DO i = 1, klon
769     t_seri(i, k) = t_seri(i, k) + d_t_lsc(i, k)
770     q_seri(i, k) = q_seri(i, k) + d_q_lsc(i, k)
771     ql_seri(i, k) = ql_seri(i, k) + d_ql_lsc(i, k)
772     cldfra(i, k) = rneb(i, k)
773     IF (.NOT.new_oliq) cldliq(i, k) = ql_seri(i, k)
774     ENDDO
775     ENDDO
776    
777 guez 47 ! PRESCRIPTION DES NUAGES POUR LE RAYONNEMENT
778 guez 3
779     ! 1. NUAGES CONVECTIFS
780    
781 guez 174 IF (iflag_cldcon <= - 1) THEN
782 guez 62 ! seulement pour Tiedtke
783 guez 51 snow_tiedtke = 0.
784 guez 174 if (iflag_cldcon == - 1) then
785 guez 51 rain_tiedtke = rain_con
786 guez 3 else
787 guez 51 rain_tiedtke = 0.
788     do k = 1, llm
789     do i = 1, klon
790 guez 7 if (d_q_con(i, k) < 0.) then
791 guez 202 rain_tiedtke(i) = rain_tiedtke(i) - d_q_con(i, k) / dtphys &
792     * zmasse(i, k)
793 guez 3 endif
794     enddo
795     enddo
796     endif
797    
798     ! Nuages diagnostiques pour Tiedtke
799 guez 69 CALL diagcld1(paprs, play, rain_tiedtke, snow_tiedtke, ibas_con, &
800     itop_con, diafra, dialiq)
801 guez 3 DO k = 1, llm
802     DO i = 1, klon
803 guez 51 IF (diafra(i, k) > cldfra(i, k)) THEN
804 guez 3 cldliq(i, k) = dialiq(i, k)
805     cldfra(i, k) = diafra(i, k)
806     ENDIF
807     ENDDO
808     ENDDO
809     ELSE IF (iflag_cldcon == 3) THEN
810 guez 72 ! On prend pour les nuages convectifs le maximum du calcul de
811 guez 90 ! la convection et du calcul du pas de temps pr\'ec\'edent diminu\'e
812 guez 72 ! d'un facteur facttemps.
813     facteur = dtphys * facttemps
814 guez 51 do k = 1, llm
815     do i = 1, klon
816 guez 70 rnebcon(i, k) = rnebcon(i, k) * facteur
817 guez 72 if (rnebcon0(i, k) * clwcon0(i, k) &
818     > rnebcon(i, k) * clwcon(i, k)) then
819 guez 51 rnebcon(i, k) = rnebcon0(i, k)
820     clwcon(i, k) = clwcon0(i, k)
821 guez 3 endif
822     enddo
823     enddo
824    
825 guez 47 ! On prend la somme des fractions nuageuses et des contenus en eau
826 guez 51 cldfra = min(max(cldfra, rnebcon), 1.)
827 guez 202 cldliq = cldliq + rnebcon * clwcon
828 guez 3 ENDIF
829    
830 guez 51 ! 2. Nuages stratiformes
831 guez 3
832     IF (ok_stratus) THEN
833 guez 47 CALL diagcld2(paprs, play, t_seri, q_seri, diafra, dialiq)
834 guez 3 DO k = 1, llm
835     DO i = 1, klon
836 guez 51 IF (diafra(i, k) > cldfra(i, k)) THEN
837 guez 3 cldliq(i, k) = dialiq(i, k)
838     cldfra(i, k) = diafra(i, k)
839     ENDIF
840     ENDDO
841     ENDDO
842     ENDIF
843    
844     ! Precipitation totale
845     DO i = 1, klon
846     rain_fall(i) = rain_con(i) + rain_lsc(i)
847     snow_fall(i) = snow_con(i) + snow_lsc(i)
848     ENDDO
849    
850 guez 90 ! Humidit\'e relative pour diagnostic :
851 guez 3 DO k = 1, llm
852     DO i = 1, klon
853     zx_t = t_seri(i, k)
854 guez 207 zx_qs = r2es * FOEEW(zx_t, rtt >= zx_t) / play(i, k)
855     zx_qs = MIN(0.5, zx_qs)
856     zcor = 1. / (1. - retv * zx_qs)
857     zx_qs = zx_qs * zcor
858 guez 202 zx_rh(i, k) = q_seri(i, k) / zx_qs
859 guez 51 zqsat(i, k) = zx_qs
860 guez 3 ENDDO
861     ENDDO
862 guez 52
863 guez 97 ! Param\`etres optiques des nuages et quelques param\`etres pour
864     ! diagnostics :
865 guez 3 if (ok_newmicro) then
866 guez 69 CALL newmicro(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, &
867 guez 217 cldh, cldl, cldm, cldt, cldq, flwp, fiwp, flwc, fiwc)
868 guez 3 else
869 guez 52 CALL nuage(paprs, play, t_seri, cldliq, cldfra, cldtau, cldemi, cldh, &
870 guez 217 cldl, cldm, cldt, cldq)
871 guez 3 endif
872    
873 guez 154 IF (MOD(itap - 1, radpas) == 0) THEN
874 guez 212 wo = ozonecm(REAL(julien), paprs)
875 guez 155 albsol = sum(falbe * pctsrf, dim = 2)
876 guez 221 CALL radlwsw(dist, mu0, fract, paprs, play, tsol, albsol, t_seri, &
877 guez 155 q_seri, wo, cldfra, cldemi, cldtau, heat, heat0, cool, cool0, &
878     radsol, albpla, topsw, toplw, solsw, sollw, sollwdown, topsw0, &
879     toplw0, solsw0, sollw0, lwdn0, lwdn, lwup0, lwup, swdn0, swdn, &
880 guez 217 swup0, swup, ok_ade, topswad, solswad)
881 guez 3 ENDIF
882 guez 118
883 guez 3 ! Ajouter la tendance des rayonnements (tous les pas)
884     DO k = 1, llm
885     DO i = 1, klon
886 guez 202 t_seri(i, k) = t_seri(i, k) + (heat(i, k) - cool(i, k)) * dtphys &
887     / 86400.
888 guez 3 ENDDO
889     ENDDO
890    
891 guez 90 ! Calculer le bilan du sol et la d\'erive de temp\'erature (couplage)
892 guez 3 DO i = 1, klon
893     bils(i) = radsol(i) - sens(i) + zxfluxlat(i)
894     ENDDO
895    
896 guez 90 ! Param\'etrisation de l'orographie \`a l'\'echelle sous-maille :
897 guez 3
898     IF (ok_orodr) THEN
899 guez 174 ! S\'election des points pour lesquels le sch\'ema est actif :
900 guez 51 igwd = 0
901     DO i = 1, klon
902     itest(i) = 0
903 guez 174 IF (zpic(i) - zmea(i) > 100. .AND. zstd(i) > 10.) THEN
904 guez 51 itest(i) = 1
905     igwd = igwd + 1
906 guez 3 ENDIF
907     ENDDO
908    
909 guez 51 CALL drag_noro(klon, llm, dtphys, paprs, play, zmea, zstd, zsig, zgam, &
910 guez 150 zthe, zpic, zval, itest, t_seri, u_seri, v_seri, zulow, zvlow, &
911     zustrdr, zvstrdr, d_t_oro, d_u_oro, d_v_oro)
912 guez 3
913 guez 47 ! ajout des tendances
914 guez 3 DO k = 1, llm
915     DO i = 1, klon
916     t_seri(i, k) = t_seri(i, k) + d_t_oro(i, k)
917     u_seri(i, k) = u_seri(i, k) + d_u_oro(i, k)
918     v_seri(i, k) = v_seri(i, k) + d_v_oro(i, k)
919     ENDDO
920     ENDDO
921 guez 13 ENDIF
922 guez 3
923     IF (ok_orolf) THEN
924 guez 90 ! S\'election des points pour lesquels le sch\'ema est actif :
925 guez 51 igwd = 0
926     DO i = 1, klon
927     itest(i) = 0
928 guez 174 IF (zpic(i) - zmea(i) > 100.) THEN
929 guez 51 itest(i) = 1
930     igwd = igwd + 1
931 guez 3 ENDIF
932     ENDDO
933    
934 guez 227 CALL lift_noro(dtphys, paprs, play, zmea, zstd, zpic, itest, t_seri, &
935     u_seri, v_seri, zulow, zvlow, zustrli, zvstrli, d_t_lif, &
936     d_u_lif, d_v_lif)
937 guez 3
938 guez 51 ! Ajout des tendances :
939 guez 3 DO k = 1, llm
940     DO i = 1, klon
941     t_seri(i, k) = t_seri(i, k) + d_t_lif(i, k)
942     u_seri(i, k) = u_seri(i, k) + d_u_lif(i, k)
943     v_seri(i, k) = v_seri(i, k) + d_v_lif(i, k)
944     ENDDO
945     ENDDO
946 guez 49 ENDIF
947 guez 3
948 guez 229 CALL aaam_bud(rg, romega, pphis, zustrdr, zustrli, &
949     sum((u_seri - u) / dtphys * zmasse, dim = 2), zvstrdr, &
950     zvstrli, sum((v_seri - v) / dtphys * zmasse, dim = 2), paprs, u, v, &
951     aam, torsfc)
952 guez 3
953 guez 47 ! Calcul des tendances traceurs
954 guez 202 call phytrac(julien, time, firstcal, lafin, dtphys, t, paprs, play, mfu, &
955 guez 244 mfd, pde_u, pen_d, coefh, cdragh, fm_therm, entr_therm, u(:, 1), &
956 guez 242 v(:, 1), ftsol, pctsrf, frac_impa, frac_nucl, da, phi, mp, upwd, &
957     dnwd, tr_seri, zmasse, ncid_startphy)
958 guez 3
959     ! Calculer le transport de l'eau et de l'energie (diagnostique)
960 guez 171 CALL transp(paprs, t_seri, q_seri, u_seri, v_seri, zphi, ve, vq, ue, uq)
961 guez 3
962 guez 31 ! diag. bilKP
963 guez 3
964 guez 178 CALL transp_lay(paprs, t_seri, q_seri, u_seri, v_seri, zphi, &
965 guez 3 ve_lay, vq_lay, ue_lay, uq_lay)
966    
967     ! Accumuler les variables a stocker dans les fichiers histoire:
968    
969 guez 200 ! conversion Ec en énergie thermique
970 guez 3 DO k = 1, llm
971     DO i = 1, klon
972 guez 213 d_t_ec(i, k) = 0.5 / (RCPD * (1. + RVTMP2 * q_seri(i, k))) &
973 guez 51 * (u(i, k)**2 + v(i, k)**2 - u_seri(i, k)**2 - v_seri(i, k)**2)
974     t_seri(i, k) = t_seri(i, k) + d_t_ec(i, k)
975     d_t_ec(i, k) = d_t_ec(i, k) / dtphys
976 guez 3 END DO
977     END DO
978 guez 51
979 guez 47 ! SORTIES
980 guez 3
981 guez 69 ! prw = eau precipitable
982 guez 3 DO i = 1, klon
983     prw(i) = 0.
984     DO k = 1, llm
985 guez 202 prw(i) = prw(i) + q_seri(i, k) * zmasse(i, k)
986 guez 3 ENDDO
987     ENDDO
988    
989     ! Convertir les incrementations en tendances
990    
991     DO k = 1, llm
992     DO i = 1, klon
993 guez 49 d_u(i, k) = (u_seri(i, k) - u(i, k)) / dtphys
994     d_v(i, k) = (v_seri(i, k) - v(i, k)) / dtphys
995     d_t(i, k) = (t_seri(i, k) - t(i, k)) / dtphys
996     d_qx(i, k, ivap) = (q_seri(i, k) - qx(i, k, ivap)) / dtphys
997     d_qx(i, k, iliq) = (ql_seri(i, k) - qx(i, k, iliq)) / dtphys
998 guez 3 ENDDO
999     ENDDO
1000    
1001 guez 98 DO iq = 3, nqmx
1002     DO k = 1, llm
1003     DO i = 1, klon
1004 guez 174 d_qx(i, k, iq) = (tr_seri(i, k, iq - 2) - qx(i, k, iq)) / dtphys
1005 guez 3 ENDDO
1006     ENDDO
1007 guez 98 ENDDO
1008 guez 3
1009     ! Sauvegarder les valeurs de t et q a la fin de la physique:
1010     DO k = 1, llm
1011     DO i = 1, klon
1012     t_ancien(i, k) = t_seri(i, k)
1013     q_ancien(i, k) = q_seri(i, k)
1014     ENDDO
1015     ENDDO
1016    
1017 guez 191 CALL histwrite_phy("phis", pphis)
1018     CALL histwrite_phy("aire", airephy)
1019     CALL histwrite_phy("psol", paprs(:, 1))
1020     CALL histwrite_phy("precip", rain_fall + snow_fall)
1021     CALL histwrite_phy("plul", rain_lsc + snow_lsc)
1022     CALL histwrite_phy("pluc", rain_con + snow_con)
1023 guez 221 CALL histwrite_phy("tsol", tsol)
1024 guez 191 CALL histwrite_phy("t2m", zt2m)
1025     CALL histwrite_phy("q2m", zq2m)
1026 guez 225 CALL histwrite_phy("u10m", u10m)
1027     CALL histwrite_phy("v10m", v10m)
1028 guez 191 CALL histwrite_phy("snow", snow_fall)
1029     CALL histwrite_phy("cdrm", cdragm)
1030     CALL histwrite_phy("cdrh", cdragh)
1031     CALL histwrite_phy("topl", toplw)
1032     CALL histwrite_phy("evap", evap)
1033     CALL histwrite_phy("sols", solsw)
1034     CALL histwrite_phy("soll", sollw)
1035     CALL histwrite_phy("solldown", sollwdown)
1036     CALL histwrite_phy("bils", bils)
1037     CALL histwrite_phy("sens", - sens)
1038     CALL histwrite_phy("fder", fder)
1039     CALL histwrite_phy("dtsvdfo", d_ts(:, is_oce))
1040     CALL histwrite_phy("dtsvdft", d_ts(:, is_ter))
1041     CALL histwrite_phy("dtsvdfg", d_ts(:, is_lic))
1042     CALL histwrite_phy("dtsvdfi", d_ts(:, is_sic))
1043 guez 3
1044 guez 191 DO nsrf = 1, nbsrf
1045 guez 202 CALL histwrite_phy("pourc_"//clnsurf(nsrf), pctsrf(:, nsrf) * 100.)
1046 guez 191 CALL histwrite_phy("fract_"//clnsurf(nsrf), pctsrf(:, nsrf))
1047 guez 206 CALL histwrite_phy("sens_"//clnsurf(nsrf), flux_t(:, nsrf))
1048 guez 191 CALL histwrite_phy("lat_"//clnsurf(nsrf), fluxlat(:, nsrf))
1049     CALL histwrite_phy("tsol_"//clnsurf(nsrf), ftsol(:, nsrf))
1050 guez 206 CALL histwrite_phy("taux_"//clnsurf(nsrf), flux_u(:, nsrf))
1051     CALL histwrite_phy("tauy_"//clnsurf(nsrf), flux_v(:, nsrf))
1052 guez 191 CALL histwrite_phy("rugs_"//clnsurf(nsrf), frugs(:, nsrf))
1053     CALL histwrite_phy("albe_"//clnsurf(nsrf), falbe(:, nsrf))
1054 guez 225 CALL histwrite_phy("u10m_"//clnsurf(nsrf), u10m_srf(:, nsrf))
1055     CALL histwrite_phy("v10m_"//clnsurf(nsrf), v10m_srf(:, nsrf))
1056 guez 191 END DO
1057    
1058     CALL histwrite_phy("albs", albsol)
1059 guez 212 CALL histwrite_phy("tro3", wo * dobson_u * 1e3 / zmasse / rmo3 * md)
1060 guez 191 CALL histwrite_phy("rugs", zxrugs)
1061     CALL histwrite_phy("s_pblh", s_pblh)
1062     CALL histwrite_phy("s_pblt", s_pblt)
1063     CALL histwrite_phy("s_lcl", s_lcl)
1064     CALL histwrite_phy("s_capCL", s_capCL)
1065     CALL histwrite_phy("s_oliqCL", s_oliqCL)
1066     CALL histwrite_phy("s_cteiCL", s_cteiCL)
1067     CALL histwrite_phy("s_therm", s_therm)
1068     CALL histwrite_phy("s_trmb1", s_trmb1)
1069     CALL histwrite_phy("s_trmb2", s_trmb2)
1070     CALL histwrite_phy("s_trmb3", s_trmb3)
1071 guez 206
1072     if (conv_emanuel) then
1073     CALL histwrite_phy("ptop", ema_pct)
1074     CALL histwrite_phy("dnwd0", - mp)
1075     end if
1076    
1077 guez 191 CALL histwrite_phy("temp", t_seri)
1078     CALL histwrite_phy("vitu", u_seri)
1079     CALL histwrite_phy("vitv", v_seri)
1080     CALL histwrite_phy("geop", zphi)
1081     CALL histwrite_phy("pres", play)
1082     CALL histwrite_phy("dtvdf", d_t_vdf)
1083     CALL histwrite_phy("dqvdf", d_q_vdf)
1084     CALL histwrite_phy("rhum", zx_rh)
1085 guez 213 CALL histwrite_phy("d_t_ec", d_t_ec)
1086     CALL histwrite_phy("dtsw0", heat0 / 86400.)
1087     CALL histwrite_phy("dtlw0", - cool0 / 86400.)
1088 guez 215 CALL histwrite_phy("msnow", sum(fsnow * pctsrf, dim = 2))
1089 guez 221 call histwrite_phy("qsurf", sum(fqsurf * pctsrf, dim = 2))
1090 guez 191
1091     if (ok_instan) call histsync(nid_ins)
1092    
1093 guez 157 IF (lafin) then
1094     call NF95_CLOSE(ncid_startphy)
1095 guez 175 CALL phyredem(pctsrf, ftsol, ftsoil, fqsurf, qsol, &
1096 guez 157 fsnow, falbe, fevap, rain_fall, snow_fall, solsw, sollw, dlw, &
1097     radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &
1098     t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, &
1099     w01)
1100     end IF
1101 guez 3
1102 guez 35 firstcal = .FALSE.
1103    
1104 guez 3 END SUBROUTINE physiq
1105    
1106     end module physiq_m

  ViewVC Help
Powered by ViewVC 1.1.21