1 | !$Id: phytrac_mod.F90 3870 2021-04-08 20:58:58Z acozic $ |
---|
2 | MODULE phytrac_mod |
---|
3 | !================================================================================= |
---|
4 | ! Interface between the LMDZ physical package and tracer computation. |
---|
5 | ! Chemistry modules (INCA, Reprobus or the more specific traclmdz routine) |
---|
6 | ! are called from phytrac. |
---|
7 | ! |
---|
8 | !====================================================================== |
---|
9 | ! Auteur(s) FH |
---|
10 | ! Objet: Moniteur general des tendances traceurs |
---|
11 | ! |
---|
12 | ! iflag_vdf_trac : Options for activating transport by vertical diffusion : |
---|
13 | ! 1. notmal |
---|
14 | ! 0. emission is injected in the first layer only, without diffusion |
---|
15 | ! -1 no emission & no diffusion |
---|
16 | ! Modification 2013/07/22 : transformed into a module to pass tendencies to |
---|
17 | ! physics outputs. Additional keys for controling activation of sub processes. |
---|
18 | ! Modification R. Pilon 10 octobre 2012 large scale scavenging incloud_scav + bc_scav |
---|
19 | ! Modification R. Pilon 01 janvier 2012 transport+scavenging KE scheme : cvltr |
---|
20 | !================================================================================= |
---|
21 | |
---|
22 | ! |
---|
23 | ! Tracer tendencies, for outputs |
---|
24 | !------------------------------- |
---|
25 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: d_tr_cl ! Td couche limite/traceur |
---|
26 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: d_tr_dec !RomP |
---|
27 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: d_tr_cv ! Td convection/traceur |
---|
28 | ! RomP >>> |
---|
29 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: d_tr_insc |
---|
30 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: d_tr_bcscav |
---|
31 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: d_tr_evapls |
---|
32 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: d_tr_ls |
---|
33 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: d_tr_trsp |
---|
34 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: d_tr_sscav |
---|
35 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: d_tr_sat |
---|
36 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: d_tr_uscav |
---|
37 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: qPr,qDi ! concentration tra dans pluie,air descente insaturee |
---|
38 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: qPa,qMel |
---|
39 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: qTrdi,dtrcvMA ! conc traceur descente air insaturee et td convective MA |
---|
40 | ! RomP <<< |
---|
41 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: d_tr_th ! Td thermique |
---|
42 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: d_tr_lessi_impa ! Td du lessivage par impaction |
---|
43 | REAL,DIMENSION(:,:,:),ALLOCATABLE,SAVE :: d_tr_lessi_nucl ! Td du lessivage par nucleation |
---|
44 | REAL,DIMENSION(:,:),ALLOCATABLE,SAVE :: qPrls !jyg: concentration tra dans pluie LS a la surf. |
---|
45 | REAL,DIMENSION(:,:),ALLOCATABLE,SAVE :: d_tr_dry ! Td depot sec/traceur (1st layer),ALLOCATABLE,SAVE jyg |
---|
46 | REAL,DIMENSION(:,:),ALLOCATABLE,SAVE :: flux_tr_dry ! depot sec/traceur (surface),ALLOCATABLE,SAVE jyg |
---|
47 | |
---|
48 | !$OMP THREADPRIVATE(qPa,qMel,qTrdi,dtrcvMA,d_tr_th,d_tr_lessi_impa,d_tr_lessi_nucl) |
---|
49 | !$OMP THREADPRIVATE(d_tr_trsp,d_tr_sscav,d_tr_sat,d_tr_uscav,qPr,qDi) |
---|
50 | !$OMP THREADPRIVATE(d_tr_insc,d_tr_bcscav,d_tr_evapls,d_tr_ls,qPrls) |
---|
51 | !$OMP THREADPRIVATE(d_tr_cl,d_tr_dry,flux_tr_dry,d_tr_dec,d_tr_cv) |
---|
52 | |
---|
53 | |
---|
54 | CONTAINS |
---|
55 | |
---|
56 | SUBROUTINE phytrac_init() |
---|
57 | USE dimphy |
---|
58 | USE infotrac_phy, ONLY: nbtr, nqCO2, type_trac |
---|
59 | USE tracco2i_mod, ONLY: tracco2i_init |
---|
60 | IMPLICIT NONE |
---|
61 | |
---|
62 | ALLOCATE(d_tr_cl(klon,klev,nbtr),d_tr_dry(klon,nbtr)) |
---|
63 | ALLOCATE(flux_tr_dry(klon,nbtr),d_tr_dec(klon,klev,nbtr),d_tr_cv(klon,klev,nbtr)) |
---|
64 | ALLOCATE(d_tr_insc(klon,klev,nbtr),d_tr_bcscav(klon,klev,nbtr)) |
---|
65 | ALLOCATE(d_tr_evapls(klon,klev,nbtr),d_tr_ls(klon,klev,nbtr)) |
---|
66 | ALLOCATE(qPrls(klon,nbtr),d_tr_trsp(klon,klev,nbtr)) |
---|
67 | ALLOCATE(d_tr_sscav(klon,klev,nbtr),d_tr_sat(klon,klev,nbtr)) |
---|
68 | ALLOCATE(d_tr_uscav(klon,klev,nbtr),qPr(klon,klev,nbtr),qDi(klon,klev,nbtr)) |
---|
69 | ALLOCATE(qPa(klon,klev,nbtr),qMel(klon,klev,nbtr)) |
---|
70 | ALLOCATE(qTrdi(klon,klev,nbtr),dtrcvMA(klon,klev,nbtr)) |
---|
71 | ALLOCATE(d_tr_th(klon,klev,nbtr)) |
---|
72 | ALLOCATE(d_tr_lessi_impa(klon,klev,nbtr),d_tr_lessi_nucl(klon,klev,nbtr)) |
---|
73 | |
---|
74 | |
---|
75 | |
---|
76 | !=============================================================================== |
---|
77 | ! -- Do specific treatment according to chemestry model or local LMDZ tracers |
---|
78 | ! |
---|
79 | !=============================================================================== |
---|
80 | SELECT CASE(type_trac) |
---|
81 | CASE('co2i') |
---|
82 | ! -- CO2 interactif -- |
---|
83 | CALL tracco2i_init() |
---|
84 | CASE('inco') |
---|
85 | CALL tracco2i_init() |
---|
86 | END SELECT |
---|
87 | |
---|
88 | |
---|
89 | END SUBROUTINE phytrac_init |
---|
90 | |
---|
91 | SUBROUTINE phytrac( & |
---|
92 | nstep, julien, gmtime, debutphy, & |
---|
93 | lafin, pdtphys, u, v, t_seri, & |
---|
94 | paprs, pplay, pmfu, pmfd, & |
---|
95 | pen_u, pde_u, pen_d, pde_d, & |
---|
96 | cdragh, coefh, fm_therm, entr_therm, & |
---|
97 | yu1, yv1, ftsol, pctsrf, & |
---|
98 | ustar, u10m, v10m, & |
---|
99 | wstar, ale_bl, ale_wake, & |
---|
100 | xlat, xlon, & |
---|
101 | frac_impa,frac_nucl,beta_fisrt,beta_v1, & |
---|
102 | presnivs, pphis, pphi, albsol, & |
---|
103 | sh, ch, rh, cldfra, rneb, & |
---|
104 | diafra, cldliq, itop_con, ibas_con, & |
---|
105 | pmflxr, pmflxs, prfl, psfl, & |
---|
106 | da, phi, mp, upwd, & |
---|
107 | phi2, d1a, dam, sij, wght_cvfd, & ! RomP +RL |
---|
108 | wdtrainA, wdtrainM, sigd, clw, elij, & ! RomP |
---|
109 | evap, ep, epmlmMm, eplaMm, & ! RomP |
---|
110 | dnwd, aerosol_couple, flxmass_w, & |
---|
111 | tau_aero, piz_aero, cg_aero, ccm, & |
---|
112 | rfname, & |
---|
113 | d_tr_dyn, & ! RomP |
---|
114 | tr_seri, init_source) |
---|
115 | ! |
---|
116 | !====================================================================== |
---|
117 | ! Auteur(s) FH |
---|
118 | ! Objet: Moniteur general des tendances traceurs |
---|
119 | ! Modification R. Pilon 01 janvier 2012 transport+scavenging KE scheme : cvltr |
---|
120 | ! Modification R. Pilon 10 octobre 2012 large scale scavenging incloud_scav + bc_scav |
---|
121 | !====================================================================== |
---|
122 | |
---|
123 | USE ioipsl |
---|
124 | USE phys_cal_mod, only : hour |
---|
125 | USE dimphy |
---|
126 | USE infotrac_phy, ONLY: nbtr, nqCO2, type_trac, conv_flg, solsym, pbl_flg |
---|
127 | USE mod_grid_phy_lmdz |
---|
128 | USE mod_phys_lmdz_para |
---|
129 | USE iophy |
---|
130 | USE traclmdz_mod |
---|
131 | USE tracinca_mod |
---|
132 | USE tracreprobus_mod |
---|
133 | USE indice_sol_mod |
---|
134 | USE mod_phys_lmdz_mpi_data, ONLY : is_mpi_root |
---|
135 | USE print_control_mod, ONLY: lunout |
---|
136 | USE aero_mod, ONLY : naero_grp |
---|
137 | |
---|
138 | USE tracco2i_mod |
---|
139 | |
---|
140 | #ifdef CPP_StratAer |
---|
141 | USE traccoag_mod |
---|
142 | USE phys_local_var_mod, ONLY: mdw |
---|
143 | USE phys_local_var_mod, ONLY: budg_dep_dry_ocs, budg_dep_wet_ocs |
---|
144 | USE phys_local_var_mod, ONLY: budg_dep_dry_so2, budg_dep_wet_so2 |
---|
145 | USE phys_local_var_mod, ONLY: budg_dep_dry_h2so4, budg_dep_wet_h2so4 |
---|
146 | USE phys_local_var_mod, ONLY: budg_dep_dry_part, budg_dep_wet_part |
---|
147 | USE infotrac, ONLY: nbtr_sulgas, id_OCS_strat, id_SO2_strat, id_H2SO4_strat |
---|
148 | USE aerophys |
---|
149 | #endif |
---|
150 | |
---|
151 | IMPLICIT NONE |
---|
152 | |
---|
153 | INCLUDE "YOMCST.h" |
---|
154 | INCLUDE "clesphys.h" |
---|
155 | INCLUDE "thermcell.h" |
---|
156 | !========================================================================== |
---|
157 | ! -- ARGUMENT DESCRIPTION -- |
---|
158 | !========================================================================== |
---|
159 | |
---|
160 | ! Input arguments |
---|
161 | !---------------- |
---|
162 | !Configuration grille,temps: |
---|
163 | INTEGER,INTENT(IN) :: nstep ! Appel physique |
---|
164 | INTEGER,INTENT(IN) :: julien ! Jour julien |
---|
165 | REAL,INTENT(IN) :: gmtime ! Heure courante |
---|
166 | REAL,INTENT(IN) :: pdtphys ! Pas d'integration pour la physique (seconde) |
---|
167 | LOGICAL,INTENT(IN) :: debutphy ! le flag de l'initialisation de la physique |
---|
168 | LOGICAL,INTENT(IN) :: lafin ! le flag de la fin de la physique |
---|
169 | |
---|
170 | REAL,DIMENSION(klon),INTENT(IN) :: xlat ! latitudes pour chaque point |
---|
171 | REAL,DIMENSION(klon),INTENT(IN) :: xlon ! longitudes pour chaque point |
---|
172 | ! |
---|
173 | !Physique: |
---|
174 | !-------- |
---|
175 | REAL,DIMENSION(klon,klev),INTENT(IN) :: t_seri ! Temperature |
---|
176 | REAL,DIMENSION(klon,klev),INTENT(IN) :: u ! variable not used |
---|
177 | REAL,DIMENSION(klon,klev),INTENT(IN) :: v ! variable not used |
---|
178 | REAL,DIMENSION(klon,klev),INTENT(IN) :: sh ! humidite specifique |
---|
179 | REAL,DIMENSION(klon,klev),INTENT(IN) :: rh ! humidite relative |
---|
180 | REAL,DIMENSION(klon,klev),INTENT(IN) :: ch ! eau liquide (+ glace si le traceur existe) |
---|
181 | REAL,DIMENSION(klon,klev+1),INTENT(IN) :: paprs ! pression pour chaque inter-couche (en Pa) |
---|
182 | REAL,DIMENSION(klon,klev),INTENT(IN) :: pplay ! pression pour le mileu de chaque couche (en Pa) |
---|
183 | REAL,DIMENSION(klon,klev),INTENT(IN) :: pphi ! geopotentiel |
---|
184 | REAL,DIMENSION(klon),INTENT(IN) :: pphis |
---|
185 | REAL,DIMENSION(klev),INTENT(IN) :: presnivs |
---|
186 | REAL,DIMENSION(klon,klev),INTENT(IN) :: cldliq ! eau liquide nuageuse |
---|
187 | REAL,DIMENSION(klon,klev),INTENT(IN) :: cldfra ! fraction nuageuse (tous les nuages) |
---|
188 | REAL,DIMENSION(klon,klev),INTENT(IN) :: diafra ! fraction nuageuse (convection ou stratus artificiels) |
---|
189 | REAL,DIMENSION(klon,klev),INTENT(IN) :: rneb ! fraction nuageuse (grande echelle) |
---|
190 | ! |
---|
191 | REAL :: ql_incl ! contenu en eau liquide nuageuse dans le nuage ! ql_incl=oliq/rneb |
---|
192 | REAL,DIMENSION(klon,klev),INTENT(IN) :: beta_fisrt ! taux de conversion de l'eau cond (de fisrtilp) |
---|
193 | REAL,DIMENSION(klon,klev),INTENT(out) :: beta_v1 ! -- (originale version) |
---|
194 | |
---|
195 | ! |
---|
196 | INTEGER,DIMENSION(klon),INTENT(IN) :: itop_con |
---|
197 | INTEGER,DIMENSION(klon),INTENT(IN) :: ibas_con |
---|
198 | REAL,DIMENSION(klon),INTENT(IN) :: albsol ! albedo surface |
---|
199 | ! |
---|
200 | !Dynamique |
---|
201 | !-------- |
---|
202 | REAL,DIMENSION(klon,klev,nbtr),INTENT(IN) :: d_tr_dyn |
---|
203 | ! |
---|
204 | !Convection: |
---|
205 | !---------- |
---|
206 | REAL,DIMENSION(klon,klev),INTENT(IN) :: pmfu ! flux de masse dans le panache montant |
---|
207 | REAL,DIMENSION(klon,klev),INTENT(IN) :: pmfd ! flux de masse dans le panache descendant |
---|
208 | REAL,DIMENSION(klon,klev),INTENT(IN) :: pen_u ! flux entraine dans le panache montant |
---|
209 | REAL,DIMENSION(klon,klev),INTENT(IN) :: pde_u ! flux detraine dans le panache montant |
---|
210 | REAL,DIMENSION(klon,klev),INTENT(IN) :: pen_d ! flux entraine dans le panache descendant |
---|
211 | REAL,DIMENSION(klon,klev),INTENT(IN) :: pde_d ! flux detraine dans le panache descendant |
---|
212 | |
---|
213 | !...Tiedke |
---|
214 | REAL,DIMENSION(klon,klev+1),INTENT(IN) :: pmflxr, pmflxs ! Flux precipitant de pluie, neige aux interfaces [convection] |
---|
215 | REAL,DIMENSION(klon,klev+1),INTENT(IN) :: prfl, psfl ! Flux precipitant de pluie, neige aux interfaces [large-scale] |
---|
216 | |
---|
217 | LOGICAL,INTENT(IN) :: aerosol_couple |
---|
218 | REAL,DIMENSION(klon,klev),INTENT(IN) :: flxmass_w |
---|
219 | REAL,DIMENSION(klon,klev,naero_grp,2),INTENT(IN) :: tau_aero |
---|
220 | REAL,DIMENSION(klon,klev,naero_grp,2),INTENT(IN) :: piz_aero |
---|
221 | REAL,DIMENSION(klon,klev,naero_grp,2),INTENT(IN) :: cg_aero |
---|
222 | CHARACTER(len=4),DIMENSION(naero_grp),INTENT(IN) :: rfname |
---|
223 | REAL,DIMENSION(klon,klev,2),INTENT(IN) :: ccm |
---|
224 | !... K.Emanuel |
---|
225 | REAL,DIMENSION(klon,klev),INTENT(IN) :: da |
---|
226 | REAL,DIMENSION(klon,klev,klev),INTENT(IN):: phi |
---|
227 | ! RomP >>> |
---|
228 | REAL,DIMENSION(klon,klev),INTENT(IN) :: d1a,dam |
---|
229 | REAL,DIMENSION(klon,klev,klev),INTENT(IN) :: phi2 |
---|
230 | ! |
---|
231 | REAL,DIMENSION(klon,klev),INTENT(IN) :: wdtrainA |
---|
232 | REAL,DIMENSION(klon,klev),INTENT(IN) :: wdtrainM |
---|
233 | REAL,DIMENSION(klon),INTENT(IN) :: sigd |
---|
234 | ! ---- RomP flux entraine, detraine et precipitant kerry Emanuel |
---|
235 | REAL,DIMENSION(klon,klev),INTENT(IN) :: evap |
---|
236 | REAL,DIMENSION(klon,klev),INTENT(IN) :: ep |
---|
237 | REAL,DIMENSION(klon,klev,klev),INTENT(IN) :: sij |
---|
238 | REAL,DIMENSION(klon,klev),INTENT(IN) :: wght_cvfd !RL |
---|
239 | REAL,DIMENSION(klon,klev,klev),INTENT(IN) :: elij |
---|
240 | REAL,DIMENSION(klon,klev,klev),INTENT(IN) :: epmlmMm |
---|
241 | REAL,DIMENSION(klon,klev),INTENT(IN) :: eplaMm |
---|
242 | REAL,DIMENSION(klon,klev),INTENT(IN) :: clw |
---|
243 | ! RomP <<< |
---|
244 | |
---|
245 | ! |
---|
246 | REAL,DIMENSION(klon,klev),INTENT(IN) :: mp |
---|
247 | REAL,DIMENSION(klon,klev),INTENT(IN) :: upwd ! saturated updraft mass flux |
---|
248 | REAL,DIMENSION(klon,klev),INTENT(IN) :: dnwd ! saturated downdraft mass flux |
---|
249 | ! |
---|
250 | !Thermiques: |
---|
251 | !---------- |
---|
252 | REAL,DIMENSION(klon,klev+1),INTENT(IN) :: fm_therm |
---|
253 | REAL,DIMENSION(klon,klev),INTENT(IN) :: entr_therm |
---|
254 | ! |
---|
255 | !Couche limite: |
---|
256 | !-------------- |
---|
257 | ! |
---|
258 | REAL,DIMENSION(:),INTENT(IN) :: cdragh ! (klon) coeff drag pour T et Q |
---|
259 | REAL,DIMENSION(:,:),INTENT(IN) :: coefh ! (klon,klev) coeff melange CL (m**2/s) |
---|
260 | REAL,DIMENSION(:),INTENT(IN) :: ustar,u10m,v10m ! (klon) u* & vent a 10m (m/s) |
---|
261 | REAL,DIMENSION(:),INTENT(IN) :: wstar,ale_bl,ale_wake ! (klon) w* and Avail. Lifting Ener. |
---|
262 | REAL,DIMENSION(:),INTENT(IN) :: yu1 ! (klon) vents au premier niveau |
---|
263 | REAL,DIMENSION(:),INTENT(IN) :: yv1 ! (klon) vents au premier niveau |
---|
264 | ! |
---|
265 | !Lessivage: |
---|
266 | !---------- |
---|
267 | ! |
---|
268 | REAL, DIMENSION(:), ALLOCATABLE, SAVE :: ccntrAA |
---|
269 | REAL, DIMENSION(:), ALLOCATABLE, SAVE :: ccntrENV |
---|
270 | REAL, DIMENSION(:), ALLOCATABLE, SAVE :: coefcoli |
---|
271 | LOGICAL, DIMENSION(:), ALLOCATABLE, SAVE :: flag_cvltr |
---|
272 | !$OMP THREADPRIVATE(ccntrAA,ccntrENV,coefcoli,flag_cvltr) |
---|
273 | REAL, DIMENSION(klon,klev) :: ccntrAA_3d |
---|
274 | REAL, DIMENSION(klon,klev) :: ccntrENV_3d |
---|
275 | REAL, DIMENSION(klon,klev) :: coefcoli_3d |
---|
276 | ! |
---|
277 | ! pour le ON-LINE |
---|
278 | ! |
---|
279 | REAL,DIMENSION(klon,klev),INTENT(IN) :: frac_impa ! fraction d'aerosols non impactes |
---|
280 | REAL,DIMENSION(klon,klev),INTENT(IN) :: frac_nucl ! fraction d'aerosols non nuclees |
---|
281 | |
---|
282 | ! Arguments necessaires pour les sources et puits de traceur: |
---|
283 | REAL,DIMENSION(klon,nbsrf),INTENT(IN) :: ftsol ! Temperature du sol (surf)(Kelvin) |
---|
284 | REAL,DIMENSION(klon,nbsrf),INTENT(IN) :: pctsrf ! Pourcentage de sol (nature du sol) |
---|
285 | |
---|
286 | #ifdef CPP_StratAer |
---|
287 | REAL,DIMENSION(klon) :: v_dep_dry !dry deposition velocity of stratospheric sulfate in m/s |
---|
288 | #endif |
---|
289 | ! Output argument |
---|
290 | !---------------- |
---|
291 | REAL,DIMENSION(klon,klev,nbtr),INTENT(INOUT) :: tr_seri ! Concentration Traceur [U/KgA] |
---|
292 | REAL,DIMENSION(klon,klev) :: sourceBE |
---|
293 | REAL,DIMENSION(klon,nbtr), INTENT(IN) :: init_source |
---|
294 | |
---|
295 | !======================================================================================= |
---|
296 | ! -- LOCAL VARIABLES -- |
---|
297 | !======================================================================================= |
---|
298 | |
---|
299 | INTEGER :: i, k, it |
---|
300 | INTEGER :: nsplit |
---|
301 | |
---|
302 | !Sources et Reservoirs de traceurs (ex:Radon): |
---|
303 | !-------------------------------------------- |
---|
304 | ! |
---|
305 | REAL,DIMENSION(:,:),ALLOCATABLE,SAVE :: source ! a voir lorsque le flux de surface est prescrit |
---|
306 | !$OMP THREADPRIVATE(source) |
---|
307 | |
---|
308 | ! |
---|
309 | !Entrees/Sorties: (cf ini_histrac.h et write_histrac.h) |
---|
310 | !--------------- |
---|
311 | INTEGER :: iiq, ierr |
---|
312 | INTEGER :: nhori, nvert |
---|
313 | REAL :: zsto, zout, zjulian |
---|
314 | INTEGER,SAVE :: nid_tra ! pointe vers le fichier histrac.nc |
---|
315 | !$OMP THREADPRIVATE(nid_tra) |
---|
316 | REAL,DIMENSION(klon) :: zx_tmp_fi2d ! variable temporaire grille physique |
---|
317 | INTEGER :: itau_w ! pas de temps ecriture = nstep + itau_phy |
---|
318 | LOGICAL,PARAMETER :: ok_sync=.TRUE. |
---|
319 | ! |
---|
320 | ! Nature du traceur |
---|
321 | !------------------ |
---|
322 | LOGICAL,DIMENSION(:),ALLOCATABLE,SAVE :: aerosol ! aerosol(it) = true => aerosol => lessivage |
---|
323 | !$OMP THREADPRIVATE(aerosol) ! aerosol(it) = false => gaz |
---|
324 | REAL,DIMENSION(klon,klev) :: delp ! epaisseur de couche (Pa) |
---|
325 | ! |
---|
326 | ! Tendances de traceurs (Td) et flux de traceurs: |
---|
327 | !------------------------ |
---|
328 | REAL,DIMENSION(klon,klev) :: d_tr ! Td dans l'atmosphere |
---|
329 | REAL,DIMENSION(klon,klev) :: Mint |
---|
330 | REAL,DIMENSION(klon,klev,nbtr) :: zmfd1a |
---|
331 | REAL,DIMENSION(klon,klev,nbtr) :: zmfdam |
---|
332 | REAL,DIMENSION(klon,klev,nbtr) :: zmfphi2 |
---|
333 | ! Physique |
---|
334 | !---------- |
---|
335 | REAL,DIMENSION(klon,klev,nbtr) :: flestottr ! flux de lessivage dans chaque couche |
---|
336 | REAL,DIMENSION(klon,klev) :: zmasse ! densité atmosphérique Kg/m2 |
---|
337 | REAL,DIMENSION(klon,klev) :: ztra_th |
---|
338 | !PhH |
---|
339 | REAL,DIMENSION(klon,klev) :: zrho |
---|
340 | REAL,DIMENSION(klon,klev) :: zdz |
---|
341 | REAL :: evaplsc,dx,beta ! variable pour lessivage Genthon |
---|
342 | REAL,DIMENSION(klon) :: his_dh ! --- |
---|
343 | ! in-cloud scav variables |
---|
344 | REAL :: ql_incloud_ref ! ref value of in-cloud condensed water content |
---|
345 | |
---|
346 | !Controles: |
---|
347 | !--------- |
---|
348 | INTEGER,SAVE :: iflag_vdf_trac,iflag_con_trac,iflag_the_trac |
---|
349 | INTEGER,SAVE :: iflag_con_trac_omp, iflag_vdf_trac_omp,iflag_the_trac_omp |
---|
350 | !$OMP THREADPRIVATE(iflag_vdf_trac,iflag_con_trac,iflag_the_trac) |
---|
351 | |
---|
352 | LOGICAL,SAVE :: lessivage |
---|
353 | !$OMP THREADPRIVATE(lessivage) |
---|
354 | |
---|
355 | !RomP >>> |
---|
356 | INTEGER,SAVE :: iflag_lscav_omp,iflag_lscav |
---|
357 | REAL, SAVE :: ccntrAA_in,ccntrAA_omp |
---|
358 | REAL, SAVE :: ccntrENV_in,ccntrENV_omp |
---|
359 | REAL, SAVE :: coefcoli_in,coefcoli_omp |
---|
360 | |
---|
361 | LOGICAL,SAVE :: convscav_omp,convscav |
---|
362 | !$OMP THREADPRIVATE(iflag_lscav) |
---|
363 | !$OMP THREADPRIVATE(ccntrAA_in,ccntrENV_in,coefcoli_in) |
---|
364 | !$OMP THREADPRIVATE(convscav) |
---|
365 | !RomP <<< |
---|
366 | !###################################################################### |
---|
367 | ! -- INITIALIZATION -- |
---|
368 | !###################################################################### |
---|
369 | |
---|
370 | DO k=1,klev |
---|
371 | DO i=1,klon |
---|
372 | sourceBE(i,k)=0. |
---|
373 | Mint(i,k)=0. |
---|
374 | zrho(i,k)=0. |
---|
375 | zdz(i,k)=0. |
---|
376 | END DO |
---|
377 | END DO |
---|
378 | |
---|
379 | DO it=1, nbtr |
---|
380 | DO k=1,klev |
---|
381 | DO i=1,klon |
---|
382 | d_tr_insc(i,k,it)=0. |
---|
383 | d_tr_bcscav(i,k,it)=0. |
---|
384 | d_tr_evapls(i,k,it)=0. |
---|
385 | d_tr_ls(i,k,it)=0. |
---|
386 | d_tr_cv(i,k,it)=0. |
---|
387 | d_tr_cl(i,k,it)=0. |
---|
388 | d_tr_trsp(i,k,it)=0. |
---|
389 | d_tr_sscav(i,k,it)=0. |
---|
390 | d_tr_sat(i,k,it)=0. |
---|
391 | d_tr_uscav(i,k,it)=0. |
---|
392 | d_tr_lessi_impa(i,k,it)=0. |
---|
393 | d_tr_lessi_nucl(i,k,it)=0. |
---|
394 | qDi(i,k,it)=0. |
---|
395 | qPr(i,k,it)=0. |
---|
396 | qPa(i,k,it)=0. |
---|
397 | qMel(i,k,it)=0. |
---|
398 | qTrdi(i,k,it)=0. |
---|
399 | dtrcvMA(i,k,it)=0. |
---|
400 | zmfd1a(i,k,it)=0. |
---|
401 | zmfdam(i,k,it)=0. |
---|
402 | zmfphi2(i,k,it)=0. |
---|
403 | END DO |
---|
404 | END DO |
---|
405 | END DO |
---|
406 | |
---|
407 | DO it=1, nbtr |
---|
408 | DO i=1,klon |
---|
409 | d_tr_dry(i,it)=0. |
---|
410 | flux_tr_dry(i,it)=0. |
---|
411 | END DO |
---|
412 | END DO |
---|
413 | |
---|
414 | DO k = 1, klev |
---|
415 | DO i = 1, klon |
---|
416 | delp(i,k) = paprs(i,k)-paprs(i,k+1) |
---|
417 | END DO |
---|
418 | END DO |
---|
419 | |
---|
420 | IF (debutphy) THEN |
---|
421 | !!jyg |
---|
422 | !$OMP BARRIER |
---|
423 | ecrit_tra=86400. ! frequence de stokage en dur |
---|
424 | ! obsolete car remplace par des ecritures dans phys_output_write |
---|
425 | !RomP >>> |
---|
426 | ! |
---|
427 | !Config Key = convscav |
---|
428 | !Config Desc = Convective scavenging switch: 0=off, 1=on. |
---|
429 | !Config Def = .FALSE. |
---|
430 | !Config Help = |
---|
431 | ! |
---|
432 | !$OMP MASTER |
---|
433 | convscav_omp=.FALSE. |
---|
434 | call getin('convscav', convscav_omp) |
---|
435 | iflag_vdf_trac_omp=1 |
---|
436 | call getin('iflag_vdf_trac', iflag_vdf_trac_omp) |
---|
437 | iflag_con_trac_omp=1 |
---|
438 | call getin('iflag_con_trac', iflag_con_trac_omp) |
---|
439 | iflag_the_trac_omp=1 |
---|
440 | call getin('iflag_the_trac', iflag_the_trac_omp) |
---|
441 | !$OMP END MASTER |
---|
442 | !$OMP BARRIER |
---|
443 | convscav=convscav_omp |
---|
444 | iflag_vdf_trac=iflag_vdf_trac_omp |
---|
445 | iflag_con_trac=iflag_con_trac_omp |
---|
446 | iflag_the_trac=iflag_the_trac_omp |
---|
447 | write(lunout,*) 'phytrac passage dans routine conv avec lessivage', convscav |
---|
448 | ! |
---|
449 | !Config Key = iflag_lscav |
---|
450 | !Config Desc = Large scale scavenging parametrization: 0=none, 1=old(Genthon92), |
---|
451 | ! 2=1+PHeinrich, 3=Reddy_Boucher2004, 4=3+RPilon. |
---|
452 | !Config Def = 1 |
---|
453 | !Config Help = |
---|
454 | ! |
---|
455 | !$OMP MASTER |
---|
456 | iflag_lscav_omp=1 |
---|
457 | call getin('iflag_lscav', iflag_lscav_omp) |
---|
458 | ccntrAA_omp=1 |
---|
459 | ccntrENV_omp=1. |
---|
460 | coefcoli_omp=0.001 |
---|
461 | call getin('ccntrAA', ccntrAA_omp) |
---|
462 | call getin('ccntrENV', ccntrENV_omp) |
---|
463 | call getin('coefcoli', coefcoli_omp) |
---|
464 | !$OMP END MASTER |
---|
465 | !$OMP BARRIER |
---|
466 | iflag_lscav=iflag_lscav_omp |
---|
467 | ccntrAA_in=ccntrAA_omp |
---|
468 | ccntrENV_in=ccntrENV_omp |
---|
469 | coefcoli_in=coefcoli_omp |
---|
470 | ! |
---|
471 | SELECT CASE(iflag_lscav) |
---|
472 | CASE(0) |
---|
473 | WRITE(lunout,*) 'Large scale scavenging: none' |
---|
474 | CASE(1) |
---|
475 | WRITE(lunout,*) 'Large scale scavenging: C. Genthon, Tellus(1992), 44B, 371-389' |
---|
476 | CASE(2) |
---|
477 | WRITE(lunout,*) 'Large scale scavenging: C. Genthon, modified P. Heinrich' |
---|
478 | CASE(3) |
---|
479 | WRITE(lunout,*) 'Large scale scavenging: M. Shekkar Reddy and O. Boucher, JGR(2004), 109, D14202' |
---|
480 | CASE(4) |
---|
481 | WRITE(lunout,*) 'Large scale scavenging: Reddy and Boucher, modified R. Pilon' |
---|
482 | END SELECT |
---|
483 | !RomP <<< |
---|
484 | WRITE(*,*) 'FIRST TIME IN PHYTRAC : pdtphys(sec) = ',pdtphys,'ecrit_tra (sec) = ',ecrit_tra |
---|
485 | ALLOCATE( source(klon,nbtr), stat=ierr) |
---|
486 | IF (ierr /= 0) CALL abort_physic('phytrac', 'pb in allocation 1',1) |
---|
487 | |
---|
488 | ALLOCATE( aerosol(nbtr), stat=ierr) |
---|
489 | IF (ierr /= 0) CALL abort_physic('phytrac', 'pb in allocation 2',1) |
---|
490 | |
---|
491 | |
---|
492 | ! Initialize module for specific tracers |
---|
493 | SELECT CASE(type_trac) |
---|
494 | CASE('lmdz') |
---|
495 | CALL traclmdz_init(pctsrf,xlat,xlon,ftsol,tr_seri,t_seri,pplay,sh,pdtphys,aerosol,lessivage) |
---|
496 | CASE('inca') |
---|
497 | source(:,:)=init_source(:,:) |
---|
498 | CALL tracinca_init(aerosol,lessivage) |
---|
499 | CASE('repr') |
---|
500 | source(:,:)=0. |
---|
501 | CASE('co2i') |
---|
502 | source(:,:)=0. |
---|
503 | lessivage = .FALSE. |
---|
504 | aerosol(:) = .FALSE. |
---|
505 | pbl_flg(:) = 1 |
---|
506 | iflag_the_trac= 1 |
---|
507 | iflag_vdf_trac= 1 |
---|
508 | iflag_con_trac= 1 |
---|
509 | CASE('inco') |
---|
510 | source(:,1:nqCO2) = 0. ! from CO2i ModThL |
---|
511 | source(:,nqCO2+1:nbtr)=init_source(:,:) ! from INCA ModThL |
---|
512 | aerosol(1:nqCO2) = .FALSE. ! from CO2i ModThL |
---|
513 | CALL tracinca_init(aerosol(nqCO2+1:nbtr),lessivage) ! from INCA ModThL |
---|
514 | pbl_flg(1:nqCO2) = 1 ! From CO2i ModThL |
---|
515 | iflag_the_trac= 1 ! From CO2i |
---|
516 | iflag_vdf_trac= 1 ! From CO2i |
---|
517 | iflag_con_trac= 1 ! From CO2i |
---|
518 | #ifdef CPP_StratAer |
---|
519 | CASE('coag') |
---|
520 | source(:,:)=0. |
---|
521 | DO it= 1, nbtr_sulgas |
---|
522 | aerosol(it)=.FALSE. |
---|
523 | IF (it==id_H2SO4_strat) aerosol(it)=.TRUE. |
---|
524 | ENDDO |
---|
525 | DO it= nbtr_sulgas+1, nbtr |
---|
526 | aerosol(it)=.TRUE. |
---|
527 | ENDDO |
---|
528 | #endif |
---|
529 | END SELECT |
---|
530 | |
---|
531 | ! |
---|
532 | !--initialising coefficients for scavenging in the case of NP |
---|
533 | ! |
---|
534 | ALLOCATE(flag_cvltr(nbtr)) |
---|
535 | IF (iflag_con.EQ.3) THEN |
---|
536 | ! |
---|
537 | ALLOCATE(ccntrAA(nbtr)) |
---|
538 | ALLOCATE(ccntrENV(nbtr)) |
---|
539 | ALLOCATE(coefcoli(nbtr)) |
---|
540 | ! |
---|
541 | DO it=1, nbtr |
---|
542 | SELECT CASE(type_trac) |
---|
543 | CASE('lmdz') |
---|
544 | IF (convscav.and.aerosol(it)) THEN |
---|
545 | flag_cvltr(it)=.TRUE. |
---|
546 | ccntrAA(it) =ccntrAA_in !--a modifier par JYG a lire depuis fichier |
---|
547 | ccntrENV(it)=ccntrENV_in |
---|
548 | coefcoli(it)=coefcoli_in |
---|
549 | ELSE |
---|
550 | flag_cvltr(it)=.FALSE. |
---|
551 | ENDIF |
---|
552 | |
---|
553 | CASE('repr') |
---|
554 | flag_cvltr(it)=.FALSE. |
---|
555 | |
---|
556 | CASE('inca') |
---|
557 | ! IF ((it.EQ.id_Rn222) .OR. ((it.GE.id_SO2) .AND. (it.LE.id_NH3)) ) THEN |
---|
558 | ! !--gas-phase species |
---|
559 | ! flag_cvltr(it)=.FALSE. |
---|
560 | ! |
---|
561 | ! ELSEIF ( (it.GE.id_CIDUSTM) .AND. (it.LE.id_AIN) ) THEN |
---|
562 | ! !--insoluble aerosol species |
---|
563 | ! flag_cvltr(it)=.TRUE. |
---|
564 | ! ccntrAA(it)=0.7 |
---|
565 | ! ccntrENV(it)=0.7 |
---|
566 | ! coefcoli(it)=0.001 |
---|
567 | ! ELSEIF ( (it.EQ.id_Pb210) .OR. ((it.GE.id_CSSSM) .AND. (it.LE.id_SSN))) THEN |
---|
568 | ! !--soluble aerosol species |
---|
569 | ! flag_cvltr(it)=.TRUE. |
---|
570 | ! ccntrAA(it)=0.9 |
---|
571 | ! ccntrENV(it)=0.9 |
---|
572 | ! coefcoli(it)=0.001 |
---|
573 | ! ELSE |
---|
574 | ! WRITE(lunout,*) 'pb it=', it |
---|
575 | ! CALL abort_physic('phytrac','pb it scavenging',1) |
---|
576 | ! ENDIF |
---|
577 | !--test OB |
---|
578 | !--for now we do not scavenge in cvltr |
---|
579 | flag_cvltr(it)=.FALSE. |
---|
580 | |
---|
581 | CASE('co2i') |
---|
582 | !--co2 tracers are not scavenged |
---|
583 | flag_cvltr(it)=.FALSE. |
---|
584 | CASE('inco') ! Add ThL |
---|
585 | flag_cvltr(it)=.FALSE. |
---|
586 | #ifdef CPP_StratAer |
---|
587 | CASE('coag') |
---|
588 | IF (convscav.and.aerosol(it)) THEN |
---|
589 | flag_cvltr(it)=.TRUE. |
---|
590 | ccntrAA(it) =ccntrAA_in |
---|
591 | ccntrENV(it)=ccntrENV_in |
---|
592 | coefcoli(it)=coefcoli_in |
---|
593 | ELSE |
---|
594 | flag_cvltr(it)=.FALSE. |
---|
595 | ENDIF |
---|
596 | #endif |
---|
597 | |
---|
598 | END SELECT |
---|
599 | ENDDO |
---|
600 | ! |
---|
601 | ELSE ! iflag_con .ne. 3 |
---|
602 | flag_cvltr(:) = .FALSE. |
---|
603 | ENDIF |
---|
604 | ! |
---|
605 | ! Initialize diagnostic output |
---|
606 | ! ---------------------------- |
---|
607 | #ifdef CPP_IOIPSL |
---|
608 | ! INCLUDE "ini_histrac.h" |
---|
609 | #endif |
---|
610 | ! |
---|
611 | ! print out all tracer flags |
---|
612 | ! |
---|
613 | WRITE(lunout,*) 'print out all tracer flags' |
---|
614 | WRITE(lunout,*) 'type_trac =', type_trac |
---|
615 | WRITE(lunout,*) 'config_inca =', config_inca |
---|
616 | WRITE(lunout,*) 'iflag_con_trac =', iflag_con_trac |
---|
617 | WRITE(lunout,*) 'iflag_con =', iflag_con |
---|
618 | WRITE(lunout,*) 'convscav =', convscav |
---|
619 | WRITE(lunout,*) 'iflag_lscav =', iflag_lscav |
---|
620 | WRITE(lunout,*) 'aerosol =', aerosol |
---|
621 | WRITE(lunout,*) 'iflag_the_trac =', iflag_the_trac |
---|
622 | WRITE(lunout,*) 'iflag_thermals =', iflag_thermals |
---|
623 | WRITE(lunout,*) 'iflag_vdf_trac =', iflag_vdf_trac |
---|
624 | WRITE(lunout,*) 'pbl_flg =', pbl_flg |
---|
625 | WRITE(lunout,*) 'lessivage =', lessivage |
---|
626 | write(lunout,*) 'flag_cvltr = ', flag_cvltr |
---|
627 | |
---|
628 | IF (lessivage .AND. (type_trac .EQ. 'inca' .OR. type_trac .EQ. 'inco')) THEN ! Mod ThL |
---|
629 | CALL abort_physic('phytrac', 'lessivage=T config_inca=inca impossible',1) |
---|
630 | ! STOP |
---|
631 | ENDIF |
---|
632 | ! |
---|
633 | ENDIF ! of IF (debutphy) |
---|
634 | !############################################ END INITIALIZATION ####### |
---|
635 | |
---|
636 | DO k=1,klev |
---|
637 | DO i=1,klon |
---|
638 | zmasse(i,k)=(paprs(i,k)-paprs(i,k+1))/rg |
---|
639 | END DO |
---|
640 | END DO |
---|
641 | ! |
---|
642 | IF (id_be .GT. 0) THEN |
---|
643 | DO k=1,klev |
---|
644 | DO i=1,klon |
---|
645 | sourceBE(i,k)=srcbe(i,k) !RomP -> pour sortie histrac |
---|
646 | END DO |
---|
647 | END DO |
---|
648 | ENDIF |
---|
649 | |
---|
650 | !=============================================================================== |
---|
651 | ! -- Do specific treatment according to chemestry model or local LMDZ tracers |
---|
652 | ! |
---|
653 | !=============================================================================== |
---|
654 | SELECT CASE(type_trac) |
---|
655 | CASE('lmdz') |
---|
656 | ! -- Traitement des traceurs avec traclmdz |
---|
657 | CALL traclmdz(nstep, julien, gmtime, pdtphys, t_seri, paprs, pplay, & |
---|
658 | cdragh, coefh, yu1, yv1, ftsol, pctsrf, xlat, xlon,iflag_vdf_trac>=0,sh, & |
---|
659 | rh, pphi, ustar, wstar, ale_bl, ale_wake, u10m, v10m, & |
---|
660 | tr_seri, source, d_tr_cl,d_tr_dec, zmasse) !RomP |
---|
661 | |
---|
662 | CASE('inca') |
---|
663 | ! -- CHIMIE INCA config_inca = aero or chem -- |
---|
664 | ! Appel fait en fin de phytrac pour avoir les emissions modifiees par |
---|
665 | ! la couche limite et la convection avant le calcul de la chimie |
---|
666 | |
---|
667 | CASE('repr') |
---|
668 | ! -- CHIMIE REPROBUS -- |
---|
669 | CALL tracreprobus(pdtphys, gmtime, debutphy, julien, & |
---|
670 | presnivs, xlat, xlon, pphis, pphi, & |
---|
671 | t_seri, pplay, paprs, sh , & |
---|
672 | tr_seri) |
---|
673 | |
---|
674 | CASE('co2i') |
---|
675 | ! -- CO2 interactif -- |
---|
676 | ! -- source is updated with FF and BB emissions |
---|
677 | ! -- and net fluxes from ocean and orchidee |
---|
678 | ! -- sign convention : positive into the atmosphere |
---|
679 | |
---|
680 | CALL tracco2i(pdtphys, debutphy, & |
---|
681 | xlat, xlon, pphis, pphi, & |
---|
682 | t_seri, pplay, paprs, tr_seri, source) |
---|
683 | CASE('inco') ! Add ThL |
---|
684 | CALL tracco2i(pdtphys, debutphy, & |
---|
685 | xlat, xlon, pphis, pphi, & |
---|
686 | t_seri, pplay, paprs, tr_seri, source) |
---|
687 | |
---|
688 | #ifdef CPP_StratAer |
---|
689 | CASE('coag') |
---|
690 | ! --STRATOSPHERIC AER IN THE STRAT -- |
---|
691 | CALL traccoag(pdtphys, gmtime, debutphy, julien, & |
---|
692 | presnivs, xlat, xlon, pphis, pphi, & |
---|
693 | t_seri, pplay, paprs, sh, rh , & |
---|
694 | tr_seri) |
---|
695 | #endif |
---|
696 | |
---|
697 | END SELECT |
---|
698 | !====================================================================== |
---|
699 | ! -- Calcul de l'effet de la convection -- |
---|
700 | !====================================================================== |
---|
701 | |
---|
702 | IF (iflag_con_trac==1) THEN |
---|
703 | |
---|
704 | DO it=1, nbtr |
---|
705 | IF ( conv_flg(it) == 0 ) CYCLE |
---|
706 | IF (iflag_con.LT.2) THEN |
---|
707 | !--pas de transport convectif |
---|
708 | d_tr_cv(:,:,it)=0. |
---|
709 | |
---|
710 | ELSE IF (iflag_con.EQ.2) THEN |
---|
711 | !--ancien transport convectif de Tiedtke |
---|
712 | |
---|
713 | CALL nflxtr(pdtphys, pmfu, pmfd, pen_u, pde_u, pen_d, pde_d, & |
---|
714 | pplay, paprs, tr_seri(:,:,it), d_tr_cv(:,:,it)) |
---|
715 | ELSE |
---|
716 | !--nouveau transport convectif de Emanuel |
---|
717 | |
---|
718 | IF (flag_cvltr(it)) THEN |
---|
719 | !--nouveau transport convectif de Emanuel avec lessivage convectif |
---|
720 | ! |
---|
721 | ! |
---|
722 | ccntrAA_3d(:,:) =ccntrAA(it) |
---|
723 | ccntrENV_3d(:,:)=ccntrENV(it) |
---|
724 | coefcoli_3d(:,:)=coefcoli(it) |
---|
725 | |
---|
726 | !--beware this interface is a bit weird because it is called for each tracer |
---|
727 | !--with the full array tr_seri even if only item it is processed |
---|
728 | |
---|
729 | print*,'CV SCAV ',it,ccntrAA(it),ccntrENV(it) |
---|
730 | |
---|
731 | CALL cvltr_scav(pdtphys, da, phi,phi2,d1a,dam, mp,ep, & |
---|
732 | sigd,sij,wght_cvfd,clw,elij,epmlmMm,eplaMm, & |
---|
733 | pmflxr,pmflxs,evap,t_seri,wdtrainA,wdtrainM, & |
---|
734 | paprs,it,tr_seri,upwd,dnwd,itop_con,ibas_con, & |
---|
735 | ccntrAA_3d,ccntrENV_3d,coefcoli_3d, & |
---|
736 | d_tr_cv,d_tr_trsp,d_tr_sscav,d_tr_sat,d_tr_uscav,qDi,qPr,& |
---|
737 | qPa,qMel,qTrdi,dtrcvMA,Mint, & |
---|
738 | zmfd1a,zmfphi2,zmfdam) |
---|
739 | |
---|
740 | |
---|
741 | ELSE !---flag_cvltr(it).EQ.FALSE |
---|
742 | !--nouveau transport convectif de Emanuel mais pas de lessivage convectif |
---|
743 | |
---|
744 | !--beware this interface is a bit weird because it is called for each tracer |
---|
745 | !--with the full array tr_seri even if only item it is processed |
---|
746 | ! |
---|
747 | CALL cvltr_noscav(it,pdtphys, da, phi,mp,wght_cvfd,paprs,pplay, & !jyg |
---|
748 | tr_seri,upwd,dnwd,d_tr_cv) !jyg |
---|
749 | |
---|
750 | ENDIF |
---|
751 | |
---|
752 | ENDIF !--iflag |
---|
753 | |
---|
754 | !--on ajoute les tendances |
---|
755 | |
---|
756 | DO k = 1, klev |
---|
757 | DO i = 1, klon |
---|
758 | tr_seri(i,k,it) = tr_seri(i,k,it) + d_tr_cv(i,k,it) |
---|
759 | END DO |
---|
760 | END DO |
---|
761 | |
---|
762 | CALL minmaxqfi(tr_seri(:,:,it),0.,1.e33,'convection it = '//solsym(it)) |
---|
763 | |
---|
764 | END DO ! nbtr |
---|
765 | |
---|
766 | #ifdef CPP_StratAer |
---|
767 | IF (type_trac=='coag') THEN |
---|
768 | ! initialize wet deposition flux of sulfur |
---|
769 | budg_dep_wet_ocs(:)=0.0 |
---|
770 | budg_dep_wet_so2(:)=0.0 |
---|
771 | budg_dep_wet_h2so4(:)=0.0 |
---|
772 | budg_dep_wet_part(:)=0.0 |
---|
773 | ! compute wet deposition flux of sulfur (sum over gases and particles) |
---|
774 | ! and convert to kg(S)/m2/s |
---|
775 | DO i = 1, klon |
---|
776 | DO k = 1, klev |
---|
777 | DO it = 1, nbtr |
---|
778 | !do not include SO2 because most of it comes trom the troposphere |
---|
779 | IF (it==id_OCS_strat) THEN |
---|
780 | budg_dep_wet_ocs(i)=budg_dep_wet_ocs(i)+d_tr_cv(i,k,it)*(mSatom/mOCSmol) & |
---|
781 | & *(paprs(i,k)-paprs(i,k+1))/RG/pdtphys |
---|
782 | ELSEIF (it==id_SO2_strat) THEN |
---|
783 | budg_dep_wet_so2(i)=budg_dep_wet_so2(i)+d_tr_cv(i,k,it)*(mSatom/mSO2mol) & |
---|
784 | & *(paprs(i,k)-paprs(i,k+1))/RG/pdtphys |
---|
785 | ELSEIF (it==id_H2SO4_strat) THEN |
---|
786 | budg_dep_wet_h2so4(i)=budg_dep_wet_h2so4(i)+d_tr_cv(i,k,it)*(mSatom/mH2SO4mol) & |
---|
787 | & *(paprs(i,k)-paprs(i,k+1))/RG/pdtphys |
---|
788 | ELSEIF (it.GT.nbtr_sulgas) THEN |
---|
789 | budg_dep_wet_part(i)=budg_dep_wet_part(i)+d_tr_cv(i,k,it)*(mSatom/mH2SO4mol) & |
---|
790 | & *dens_aer_dry*4./3.*RPI*(mdw(it-nbtr_sulgas)/2.)**3 & |
---|
791 | & *(paprs(i,k)-paprs(i,k+1))/RG/pdtphys |
---|
792 | ENDIF |
---|
793 | ENDDO |
---|
794 | ENDDO |
---|
795 | ENDDO |
---|
796 | ENDIF |
---|
797 | #endif |
---|
798 | |
---|
799 | ENDIF ! convection |
---|
800 | |
---|
801 | !====================================================================== |
---|
802 | ! -- Calcul de l'effet des thermiques -- |
---|
803 | !====================================================================== |
---|
804 | |
---|
805 | DO it=1,nbtr |
---|
806 | DO k=1,klev |
---|
807 | DO i=1,klon |
---|
808 | d_tr_th(i,k,it)=0. |
---|
809 | tr_seri(i,k,it)=MAX(tr_seri(i,k,it),0.) |
---|
810 | ! the next safeguard causes some problem for stratospheric aerosol tracers (particle number) |
---|
811 | ! and there is little justification for it so it is commented out (4 December 2017) by OB |
---|
812 | ! if reinstated please keep the ifndef CPP_StratAer |
---|
813 | !#ifndef CPP_StratAer |
---|
814 | ! tr_seri(i,k,it)=MIN(tr_seri(i,k,it),1.e10) |
---|
815 | !#endif |
---|
816 | END DO |
---|
817 | END DO |
---|
818 | END DO |
---|
819 | |
---|
820 | IF (iflag_thermals.GT.0.AND.iflag_the_trac>0) THEN |
---|
821 | |
---|
822 | DO it=1, nbtr |
---|
823 | |
---|
824 | CALL thermcell_dq(klon,klev,1,pdtphys,fm_therm,entr_therm, & |
---|
825 | zmasse,tr_seri(1:klon,1:klev,it), & |
---|
826 | d_tr_th(1:klon,1:klev,it),ztra_th,0 ) |
---|
827 | |
---|
828 | DO k=1,klev |
---|
829 | DO i=1,klon |
---|
830 | d_tr_th(i,k,it)=pdtphys*d_tr_th(i,k,it) |
---|
831 | tr_seri(i,k,it)=MAX(tr_seri(i,k,it)+d_tr_th(i,k,it),0.) |
---|
832 | END DO |
---|
833 | END DO |
---|
834 | |
---|
835 | END DO ! it |
---|
836 | |
---|
837 | ENDIF ! Thermiques |
---|
838 | |
---|
839 | !====================================================================== |
---|
840 | ! -- Calcul de l'effet de la couche limite -- |
---|
841 | !====================================================================== |
---|
842 | |
---|
843 | IF (iflag_vdf_trac==1) THEN |
---|
844 | |
---|
845 | ! Injection during BL mixing |
---|
846 | ! |
---|
847 | #ifdef CPP_StratAer |
---|
848 | IF (type_trac=='coag') THEN |
---|
849 | |
---|
850 | ! initialize dry deposition flux of sulfur |
---|
851 | budg_dep_dry_ocs(:)=0.0 |
---|
852 | budg_dep_dry_so2(:)=0.0 |
---|
853 | budg_dep_dry_h2so4(:)=0.0 |
---|
854 | budg_dep_dry_part(:)=0.0 |
---|
855 | |
---|
856 | ! compute dry deposition velocity as function of surface type (numbers |
---|
857 | ! from IPSL note 23, 2002) |
---|
858 | v_dep_dry(:) = pctsrf(:,is_ter) * 2.5e-3 & |
---|
859 | & + pctsrf(:,is_oce) * 0.5e-3 & |
---|
860 | & + pctsrf(:,is_lic) * 2.5e-3 & |
---|
861 | & + pctsrf(:,is_sic) * 2.5e-3 |
---|
862 | |
---|
863 | ! compute surface dry deposition flux |
---|
864 | zrho(:,1)=pplay(:,1)/t_seri(:,1)/RD |
---|
865 | |
---|
866 | DO it=1, nbtr |
---|
867 | source(:,it) = - v_dep_dry(:) * tr_seri(:,1,it) * zrho(:,1) |
---|
868 | ENDDO |
---|
869 | |
---|
870 | ENDIF |
---|
871 | #endif |
---|
872 | |
---|
873 | DO it=1, nbtr |
---|
874 | ! |
---|
875 | IF( pbl_flg(it) /= 0 ) THEN |
---|
876 | ! |
---|
877 | CALL cltrac(pdtphys, coefh,t_seri, & |
---|
878 | tr_seri(:,:,it), source(:,it), & |
---|
879 | paprs, pplay, delp, & |
---|
880 | d_tr_cl(:,:,it),d_tr_dry(:,it),flux_tr_dry(:,it)) |
---|
881 | ! |
---|
882 | tr_seri(:,:,it)=tr_seri(:,:,it)+d_tr_cl(:,:,it) |
---|
883 | ! |
---|
884 | #ifdef CPP_StratAer |
---|
885 | IF (type_trac=='coag') THEN |
---|
886 | ! compute dry deposition flux of sulfur (sum over gases and particles) |
---|
887 | IF (it==id_OCS_strat) THEN |
---|
888 | budg_dep_dry_ocs(:)=budg_dep_dry_ocs(:)-source(:,it)*(mSatom/mOCSmol) |
---|
889 | ELSEIF (it==id_SO2_strat) THEN |
---|
890 | budg_dep_dry_so2(:)=budg_dep_dry_so2(:)-source(:,it)*(mSatom/mSO2mol) |
---|
891 | ELSEIF (it==id_H2SO4_strat) THEN |
---|
892 | budg_dep_dry_h2so4(:)=budg_dep_dry_h2so4(:)-source(:,it)*(mSatom/mH2SO4mol) |
---|
893 | ELSEIF (it.GT.nbtr_sulgas) THEN |
---|
894 | budg_dep_dry_part(:)=budg_dep_dry_part(:)-source(:,it)*(mSatom/mH2SO4mol)*dens_aer_dry & |
---|
895 | & *4./3.*RPI*(mdw(it-nbtr_sulgas)/2.)**3 |
---|
896 | ENDIF |
---|
897 | ENDIF |
---|
898 | #endif |
---|
899 | ! |
---|
900 | ENDIF |
---|
901 | ! |
---|
902 | ENDDO |
---|
903 | ! |
---|
904 | ELSE IF (iflag_vdf_trac==0) THEN |
---|
905 | ! |
---|
906 | ! Injection of source in the first model layer |
---|
907 | ! |
---|
908 | DO it=1,nbtr |
---|
909 | d_tr_cl(:,1,it)=source(:,it)*RG/delp(:,1)*pdtphys |
---|
910 | tr_seri(:,1,it)=tr_seri(:,1,it)+d_tr_cl(:,1,it) |
---|
911 | ENDDO |
---|
912 | d_tr_cl(:,2:klev,1:nbtr)=0. |
---|
913 | ! |
---|
914 | ELSE IF (iflag_vdf_trac==-1) THEN |
---|
915 | ! |
---|
916 | ! Nothing happens |
---|
917 | d_tr_cl=0. |
---|
918 | ! |
---|
919 | ELSE |
---|
920 | ! |
---|
921 | CALL abort_physic('iflag_vdf_trac', 'cas non prevu',1) |
---|
922 | ! |
---|
923 | ENDIF ! couche limite |
---|
924 | |
---|
925 | !====================================================================== |
---|
926 | ! Calcul de l'effet de la precipitation grande echelle |
---|
927 | ! POUR INCA le lessivage est fait directement dans INCA |
---|
928 | !====================================================================== |
---|
929 | |
---|
930 | IF (lessivage) THEN |
---|
931 | |
---|
932 | ql_incloud_ref = 10.e-4 |
---|
933 | ql_incloud_ref = 5.e-4 |
---|
934 | |
---|
935 | |
---|
936 | ! calcul du contenu en eau liquide au sein du nuage |
---|
937 | ql_incl = ql_incloud_ref |
---|
938 | ! choix du lessivage |
---|
939 | ! |
---|
940 | IF (iflag_lscav .EQ. 3 .OR. iflag_lscav .EQ. 4) THEN |
---|
941 | ! ******** Olivier Boucher version (3) possibly with modified ql_incl (4) |
---|
942 | ! |
---|
943 | DO it = 1, nbtr |
---|
944 | |
---|
945 | IF (aerosol(it)) THEN |
---|
946 | ! incloud scavenging and removal by large scale rain ! orig : ql_incl was replaced by 0.5e-3 kg/kg |
---|
947 | ! the value 0.5e-3 kg/kg is from Giorgi and Chameides (1986), JGR |
---|
948 | ! Liu (2001) proposed to use 1.5e-3 kg/kg |
---|
949 | |
---|
950 | !jyg< |
---|
951 | !! CALL lsc_scav(pdtphys,it,iflag_lscav,ql_incl,prfl,psfl,rneb,beta_fisrt, & |
---|
952 | CALL lsc_scav(pdtphys,it,iflag_lscav,aerosol,ql_incl,prfl,psfl,rneb,beta_fisrt, & |
---|
953 | !>jyg |
---|
954 | beta_v1,pplay,paprs,t_seri,tr_seri,d_tr_insc, & |
---|
955 | d_tr_bcscav,d_tr_evapls,qPrls) |
---|
956 | |
---|
957 | !large scale scavenging tendency |
---|
958 | DO k = 1, klev |
---|
959 | DO i = 1, klon |
---|
960 | d_tr_ls(i,k,it)=d_tr_insc(i,k,it)+d_tr_bcscav(i,k,it)+d_tr_evapls(i,k,it) |
---|
961 | tr_seri(i,k,it)=tr_seri(i,k,it)+d_tr_ls(i,k,it) |
---|
962 | ENDDO |
---|
963 | ENDDO |
---|
964 | CALL minmaxqfi(tr_seri(:,:,it),0.,1.e33,'lsc scav it = '//solsym(it)) |
---|
965 | ENDIF |
---|
966 | |
---|
967 | END DO !tr |
---|
968 | |
---|
969 | #ifdef CPP_StratAer |
---|
970 | IF (type_trac=='coag') THEN |
---|
971 | ! compute wet deposition flux of sulfur (sum over gases and |
---|
972 | ! particles) and convert to kg(S)/m2/s |
---|
973 | ! adding contribution of d_tr_ls to d_tr_cv (above) |
---|
974 | DO i = 1, klon |
---|
975 | DO k = 1, klev |
---|
976 | DO it = 1, nbtr |
---|
977 | IF (it==id_OCS_strat) THEN |
---|
978 | budg_dep_wet_ocs(i)=budg_dep_wet_ocs(i)+d_tr_ls(i,k,it)*(mSatom/mOCSmol) & |
---|
979 | & *(paprs(i,k)-paprs(i,k+1))/RG/pdtphys |
---|
980 | ELSEIF (it==id_SO2_strat) THEN |
---|
981 | budg_dep_wet_so2(i)=budg_dep_wet_so2(i)+d_tr_ls(i,k,it)*(mSatom/mSO2mol) & |
---|
982 | & *(paprs(i,k)-paprs(i,k+1))/RG/pdtphys |
---|
983 | ELSEIF (it==id_H2SO4_strat) THEN |
---|
984 | budg_dep_wet_h2so4(i)=budg_dep_wet_h2so4(i)+d_tr_ls(i,k,it)*(mSatom/mH2SO4mol) & |
---|
985 | & *(paprs(i,k)-paprs(i,k+1))/RG/pdtphys |
---|
986 | ELSEIF (it.GT.nbtr_sulgas) THEN |
---|
987 | budg_dep_wet_part(i)=budg_dep_wet_part(i)+d_tr_ls(i,k,it)*(mSatom/mH2SO4mol) & |
---|
988 | & *dens_aer_dry*4./3.*RPI*(mdw(it-nbtr_sulgas)/2.)**3 & |
---|
989 | & *(paprs(i,k)-paprs(i,k+1))/RG/pdtphys |
---|
990 | ENDIF |
---|
991 | ENDDO |
---|
992 | ENDDO |
---|
993 | ENDDO |
---|
994 | ENDIF |
---|
995 | #endif |
---|
996 | |
---|
997 | ELSE IF (iflag_lscav .EQ. 2) THEN ! frac_impa, frac_nucl |
---|
998 | ! ********* modified old version |
---|
999 | |
---|
1000 | d_tr_lessi_nucl(:,:,:) = 0. |
---|
1001 | d_tr_lessi_impa(:,:,:) = 0. |
---|
1002 | flestottr(:,:,:) = 0. |
---|
1003 | ! Tendance des aerosols nuclees et impactes |
---|
1004 | DO it = 1, nbtr |
---|
1005 | IF (aerosol(it)) THEN |
---|
1006 | his_dh(:)=0. |
---|
1007 | DO k = 1, klev |
---|
1008 | DO i = 1, klon |
---|
1009 | !PhH |
---|
1010 | zrho(i,k)=pplay(i,k)/t_seri(i,k)/RD |
---|
1011 | zdz(i,k)=(paprs(i,k)-paprs(i,k+1))/zrho(i,k)/RG |
---|
1012 | ! |
---|
1013 | ENDDO |
---|
1014 | ENDDO |
---|
1015 | |
---|
1016 | DO k=klev-1, 1, -1 |
---|
1017 | DO i=1, klon |
---|
1018 | ! d_tr_ls(i,k,it)=tr_seri(i,k,it)*(frac_impa(i,k)*frac_nucl(i,k)-1.) |
---|
1019 | dx=d_tr_ls(i,k,it) |
---|
1020 | his_dh(i)=his_dh(i)-dx*zrho(i,k)*zdz(i,k)/pdtphys ! kg/m2/s |
---|
1021 | evaplsc = prfl(i,k) - prfl(i,k+1) + psfl(i,k) - psfl(i,k+1) |
---|
1022 | ! Evaporation Partielle -> Liberation Partielle 0.5*evap |
---|
1023 | IF ( evaplsc .LT.0..and.abs(prfl(i,k+1)+psfl(i,k+1)).gt.1.e-10) THEN |
---|
1024 | evaplsc = (-evaplsc)/(prfl(i,k+1)+psfl(i,k+1)) |
---|
1025 | ! evaplsc est donc positif, his_dh(i) est positif |
---|
1026 | !-------------- |
---|
1027 | d_tr_evapls(i,k,it)=0.5*evaplsc*(d_tr_lessi_nucl(i,k+1,it) & |
---|
1028 | +d_tr_lessi_impa(i,k+1,it)) |
---|
1029 | !------------- d_tr_evapls(i,k,it)=-0.5*evaplsc*(d_tr_lsc(i,k+1,it)) |
---|
1030 | beta=0.5*evaplsc |
---|
1031 | if ((prfl(i,k)+psfl(i,k)).lt.1.e-10) THEN |
---|
1032 | beta=1.0*evaplsc |
---|
1033 | endif |
---|
1034 | dx=beta*his_dh(i)/zrho(i,k)/zdz(i,k)*pdtphys |
---|
1035 | his_dh(i)=(1.-beta)*his_dh(i) ! tracer from |
---|
1036 | d_tr_evapls(i,k,it)=dx |
---|
1037 | ENDIF |
---|
1038 | d_tr_ls(i,k,it)=tr_seri(i,k,it)*(frac_impa(i,k)*frac_nucl(i,k)-1.) & |
---|
1039 | +d_tr_evapls(i,k,it) |
---|
1040 | |
---|
1041 | !-------------- |
---|
1042 | d_tr_lessi_nucl(i,k,it) = d_tr_lessi_nucl(i,k,it) + & |
---|
1043 | ( 1 - frac_nucl(i,k) )*tr_seri(i,k,it) |
---|
1044 | d_tr_lessi_impa(i,k,it) = d_tr_lessi_impa(i,k,it) + & |
---|
1045 | ( 1 - frac_impa(i,k) )*tr_seri(i,k,it) |
---|
1046 | ! |
---|
1047 | ! Flux lessivage total |
---|
1048 | flestottr(i,k,it) = flestottr(i,k,it) - & |
---|
1049 | ( d_tr_lessi_nucl(i,k,it) + & |
---|
1050 | d_tr_lessi_impa(i,k,it) ) * & |
---|
1051 | ( paprs(i,k)-paprs(i,k+1) ) / & |
---|
1052 | (RG * pdtphys) |
---|
1053 | !! Mise a jour des traceurs due a l'impaction,nucleation |
---|
1054 | ! tr_seri(i,k,it)=tr_seri(i,k,it)*frac_impa(i,k)*frac_nucl(i,k) |
---|
1055 | !! calcul de la tendance liee au lessivage stratiforme |
---|
1056 | ! d_tr_ls(i,k,it)=tr_seri(i,k,it)*& |
---|
1057 | ! (1.-1./(frac_impa(i,k)*frac_nucl(i,k))) |
---|
1058 | !-------------- |
---|
1059 | ENDDO |
---|
1060 | ENDDO |
---|
1061 | ENDIF |
---|
1062 | ENDDO |
---|
1063 | ! ********* end modified old version |
---|
1064 | |
---|
1065 | ELSE IF (iflag_lscav .EQ. 1) THEN ! frac_impa, frac_nucl |
---|
1066 | ! ********* old version |
---|
1067 | |
---|
1068 | d_tr_lessi_nucl(:,:,:) = 0. |
---|
1069 | d_tr_lessi_impa(:,:,:) = 0. |
---|
1070 | flestottr(:,:,:) = 0. |
---|
1071 | !========================= |
---|
1072 | ! LESSIVAGE LARGE SCALE : |
---|
1073 | !========================= |
---|
1074 | |
---|
1075 | ! Tendance des aerosols nuclees et impactes |
---|
1076 | ! ----------------------------------------- |
---|
1077 | DO it = 1, nbtr |
---|
1078 | IF (aerosol(it)) THEN |
---|
1079 | DO k = 1, klev |
---|
1080 | DO i = 1, klon |
---|
1081 | d_tr_lessi_nucl(i,k,it) = d_tr_lessi_nucl(i,k,it) + & |
---|
1082 | ( 1 - frac_nucl(i,k) )*tr_seri(i,k,it) |
---|
1083 | d_tr_lessi_impa(i,k,it) = d_tr_lessi_impa(i,k,it) + & |
---|
1084 | ( 1 - frac_impa(i,k) )*tr_seri(i,k,it) |
---|
1085 | |
---|
1086 | ! |
---|
1087 | ! Flux lessivage total |
---|
1088 | ! ------------------------------------------------------------ |
---|
1089 | flestottr(i,k,it) = flestottr(i,k,it) - & |
---|
1090 | ( d_tr_lessi_nucl(i,k,it) + & |
---|
1091 | d_tr_lessi_impa(i,k,it) ) * & |
---|
1092 | ( paprs(i,k)-paprs(i,k+1) ) / & |
---|
1093 | (RG * pdtphys) |
---|
1094 | ! |
---|
1095 | ! Mise a jour des traceurs due a l'impaction,nucleation |
---|
1096 | ! ---------------------------------------------------------------------- |
---|
1097 | tr_seri(i,k,it)=tr_seri(i,k,it)*frac_impa(i,k)*frac_nucl(i,k) |
---|
1098 | ENDDO |
---|
1099 | ENDDO |
---|
1100 | ENDIF |
---|
1101 | ENDDO |
---|
1102 | |
---|
1103 | ! ********* end old version |
---|
1104 | ENDIF ! iflag_lscav . EQ. 1, 2, 3 or 4 |
---|
1105 | ! |
---|
1106 | ENDIF ! lessivage |
---|
1107 | |
---|
1108 | |
---|
1109 | ! -- CHIMIE INCA config_inca = aero or chem -- |
---|
1110 | IF (type_trac == 'inca' .OR. type_trac == 'inco') THEN ! ModThL |
---|
1111 | |
---|
1112 | CALL tracinca(& |
---|
1113 | nstep, julien, gmtime, lafin, & |
---|
1114 | pdtphys, t_seri, paprs, pplay, & |
---|
1115 | pmfu, upwd, ftsol, pctsrf, pphis, & |
---|
1116 | pphi, albsol, sh, ch, rh, & |
---|
1117 | cldfra, rneb, diafra, cldliq, & |
---|
1118 | itop_con, ibas_con, pmflxr, pmflxs, & |
---|
1119 | prfl, psfl, aerosol_couple, flxmass_w, & |
---|
1120 | tau_aero, piz_aero, cg_aero, ccm, & |
---|
1121 | rfname, & |
---|
1122 | tr_seri(:,:,1+nqCO2:nbtr), source(:,1+nqCO2:nbtr)) ! ModThL |
---|
1123 | ENDIF |
---|
1124 | !============================================================= |
---|
1125 | ! Ecriture des sorties |
---|
1126 | !============================================================= |
---|
1127 | #ifdef CPP_IOIPSL |
---|
1128 | ! INCLUDE "write_histrac.h" |
---|
1129 | #endif |
---|
1130 | |
---|
1131 | END SUBROUTINE phytrac |
---|
1132 | |
---|
1133 | END MODULE |
---|