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

Contents of /trunk/phylmd/physiq.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 204 - (show annotations)
Wed Jun 8 15:27:32 2016 UTC (7 years, 11 months ago) by guez
Original Path: trunk/Sources/phylmd/physiq.f
File size: 44314 byte(s)
Removed calls to diagphy and diagetpq. Those were debugging
procedures, which printed to standard output and were called several
times per time step of physics.

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

  ViewVC Help
Powered by ViewVC 1.1.21