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

Contents of /trunk/phylmd/physiq.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 338 - (show annotations)
Mon Sep 16 17:25:30 2019 UTC (4 years, 8 months ago) by guez
File size: 35940 byte(s)
Inline the list of files in `phylmd/CMakeLists.txt`. The drawback of
reading a separate file `file_list` is that cmake seems not to
reconfigure automatically when `file_list` is modified.

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

  ViewVC Help
Powered by ViewVC 1.1.21