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

Contents of /trunk/phylmd/physiq.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 309 - (show annotations)
Thu Sep 27 14:58:10 2018 UTC (5 years, 8 months ago) by guez
File size: 36674 byte(s)
Remove variable pourc_* in histins.nc, redundant with fract_*.

In procedure physiq, change the meaning of variable "sens" to avoid
changing the sign several times needlessly. Also the meaning of
variable "sens" in physiq is now the same than the meaning of netCDF
variable "sens". Also the convention for "sens" is now the same than
for radsol, zxfluxlat, and flux_t.

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

  ViewVC Help
Powered by ViewVC 1.1.21