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

Annotation of /trunk/phylmd/physiq.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 305 - (hide annotations)
Tue Sep 11 11:08:38 2018 UTC (5 years, 8 months ago) by guez
File size: 37155 byte(s)
We want to keep the same variable names throughout procedures. In
pbl_surface, rain_fall and snow_fall were passed to clqh and became
precip_rain and precip_snow. Which name should we choose?
Precipitation normally refers to water in all phases. Rainfall and
snowfall seem to be more common names to distinguish liquid water and
snow. Cf. CF standard names. So change everywhere precip_rain to
rain_fall and precip_snow to snow_fall.

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

  ViewVC Help
Powered by ViewVC 1.1.21