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

Annotation of /trunk/phylmd/physiq.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 206 - (hide annotations)
Tue Aug 30 12:52:46 2016 UTC (7 years, 8 months ago) by guez
Original Path: trunk/Sources/phylmd/physiq.f
File size: 41996 byte(s)
Removed dimension klev of flux_[tquv] and y_flux_[tquv] in
clmain. Removed dimension klev of flux_[tquv] in physiq. Removed
dimension klev of flux_[tq] in hbtm. Removed dimension klev of
flux_[tq] in clqh and computations for layers other than the surface
layer. Removed dimension klev of flux_v in clvent and computations for
layers other than the surface layer. Values for layers other than the
surface layer were not used nor output (not even in LMDZ).

Removed argument dnwd0 of concvl. Simply write - mp in physiq
(following LMDZ).

Removed useless intermediary variables zxflux[tquv] in physiq.

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

  ViewVC Help
Powered by ViewVC 1.1.21