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

Contents of /trunk/phylmd/physiq.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 343 - (show annotations)
Mon Oct 28 08:14:26 2019 UTC (4 years, 7 months ago) by guez
File size: 35492 byte(s)
Add output variables rld and rldcs

Add output variables rld and rldcs (following LMDZ).

In procedure cdrag, rename variables zdu2, ztsolv, ztvd, zri to du2,
tsolv, tvd, ri. Replace `exp(log(psol))` by psol.

In procedure `pbl_surface`, rename u, v to `u_seri`, `v_seri`.

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

  ViewVC Help
Powered by ViewVC 1.1.21