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

Annotation of /trunk/Sources/phylmd/physiq.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 207 - (hide annotations)
Thu Sep 1 10:30:53 2016 UTC (7 years, 8 months ago) by guez
File size: 41535 byte(s)
New philosophy on compiler options.

Removed source code for thermcep = f. (Not used in LMDZ either.)

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

  ViewVC Help
Powered by ViewVC 1.1.21