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

Contents of /trunk/phylmd/physiq.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 215 - (show annotations)
Tue Mar 28 12:46:28 2017 UTC (7 years, 1 month ago) by guez
Original Path: trunk/Sources/phylmd/physiq.f
File size: 40577 byte(s)
size(snow) is now knon in interfsurf_hq.

Renamed snow to fsnow in clmain, same name as corresponding actual
argument. We can then rename ysnow to simply snow in clmain, same name
as corresponding dummy argument of clqh. No need to initialize local
snow to 0 since it is only used with indices 1:knon and already
initialized from fsnow for each type of surface. If there is no point
for a given type of surface, fsnow should be reset to 0 for this
type. We need to give a valid value to fsnow in this case even if it
will be multiplied by pctsrf = 0 in physiq.

In physiq, no need for intermediate zxsnow for output.

Removed unused arguments tsurf, p1lay, beta, coef1lay, ps, t1lay,
q1lay, u1lay, v1lay, petAcoef, peqAcoef, petBcoef, peqBcoef of
fonte_neige, with unused computations of zx_qs and zcor. (Same was
done in LMDZ.)

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

  ViewVC Help
Powered by ViewVC 1.1.21